📄 removeusbdriver.bas
字号:
Attribute VB_Name = "RemoveUsbDriver"
'****************************************************************************
'人人为我,我为人人
'枕善居收藏整理
'发布日期:2008/08/06
'描 述:USB卸载助手 - 让USB设备卸载从此简单...
'网 站:http://www.Mndsoft.com/ (VB6源码博客)
'网 站:http://www.VbDnet.com/ (VB.NET源码博客,主要基于.NET2005)
'e-mail :Mndsoft@163.com
'e-mail :Mndsoft@126.com
'OICQ :88382850
' 如果您有新的好的代码别忘记给枕善居哦!
'****************************************************************************
Rem # # # # # # # # # # # # # # # # # # # # # # # #
Rem # 名称 RemoveUsbDriver #
Rem # 功能 卸载USB #
Rem # 说明 卸载USB的模块。 #
Rem # # # # # # # # # # # # # # # # # # # # # # # #
Option Explicit
Private Type GUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(0 To 7) As Byte
End Type
Private Type SP_DEVICE_INTERFACE_DETAIL_DATA
cbSize As Long
strDevicePath As String * 260
End Type
Private Type SP_DEVICE_INTERFACE_DATA
cbSize As Long
InterfaceClassGuid As GUID
flags As Long
Reserved As Long
End Type
Private Type SP_DEVINFO_DATA
cbSize As Long
ClassGuid As GUID
DevInst As Long
Reserved As Long
End Type
Private Type STORAGE_DEVICE_NUMBER
dwDeviceType As Long
dwDeviceNumber As Long
dwPartitionNumber As Long
End Type
Private Enum PNP_VETO_TYPE
PNP_VetoTypeUnknown
PNP_VetoLegacyDevice
PNP_VetoPendingClose
PNP_VetoWindowsApp
PNP_VetoWindowsService
PNP_VetoOutstandingOpen
PNP_VetoDevice
PNP_VetoDriver
PNP_VetoIllegalDeviceRequest
PNP_VetoInsufficientPower
PNP_VetoNonDisableable
PNP_VetoLegacyDriver
PNP_VetoInsufficientRights
End Enum
Private Const DIGCF_PRESENT = &H2
Private Const DIGCF_DEVICEINTERFACE = &H10
Private Const GENERIC_READ = &H80000000
Private Const FILE_SHARE_READ = &H1
Private Const OPEN_EXISTING = 3
Private Const FILE_SHARE_WRITE = &H2
Private Const IOCTL_STORAGE_BASE As Long = &H2D
Private Const METHOD_BUFFERED = 0
Private Const FILE_ANY_ACCESS = 0
Private Declare Function SetupDiGetClassDevs Lib "setupapi.dll" Alias "SetupDiGetClassDevsA" (ByVal ClassGuid As Long, ByVal Enumerator As Long, ByVal HwndParent As Long, ByVal flags As Long) As Long
Private Declare Function SetupDiEnumDeviceInterfaces Lib "setupapi.dll" (ByVal DeviceInfoSet As Long, ByVal DeviceInfoData As Long, ByRef InterfaceClassGuid As GUID, ByVal MemberIndex As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA) As Long
Private Declare Function SetupDiGetDeviceInterfaceDetail Lib "setupapi.dll" Alias "SetupDiGetDeviceInterfaceDetailA" (ByVal DeviceInfoSet As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA, DeviceInterfaceDetailData As Any, ByVal DeviceInterfaceDetailDataSize As Long, ByRef RequiredSize As Long, DeviceInfoData As Any) As Long
Private Declare Function SetupDiDestroyDeviceInfoList Lib "setupapi.dll" (ByVal DeviceInfoSet As Long) As Long
Private Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Private Declare Function CM_Get_Parent Lib "cfgmgr32.dll" (pdwDevInst As Long, ByVal dwDevInst As Long, ByVal ulFlags As Long) As Long
Private Declare Function CM_Request_Device_EjectW Lib "setupapi.dll" (ByVal dwDevInst As Long, ByVal pVetoType As Long, ByVal pszVetoName As String, ByVal ulNameLength As Long, ByVal ulFlags As Long) As Long
Private Declare Function DeviceIoControl Lib "kernel32" (ByVal hDevice As Long, ByVal dwIoControlCode As Long, lpInBuffer As Any, ByVal nInBufferSize As Long, lpOutBuffer As Any, ByVal nOutBufferSize As Long, lpBytesReturned As Long, lpOverlapped As Any) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function GetDriveType Lib "kernel32" Alias "GetDriveTypeA" (ByVal nDrive As String) As Long
Private Declare Function QueryDosDevice Lib "kernel32" Alias "QueryDosDeviceA" (ByVal lpDeviceName As String, ByVal lpTargetPath As String, ByVal ucchMax As Long) As Long
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Function CTL_CODE(ByVal lDeviceType As Long, ByVal lFunction As Long, ByVal lMethod As Long, ByVal lAccess As Long) As Long
CTL_CODE = (lDeviceType * 2 ^ 16&) Or (lAccess * 2 ^ 14&) Or (lFunction * 2 ^ 2) Or (lMethod)
End Function
Private Function IOCTL_STORAGE_GET_DEVICE_NUMBER() As Long
IOCTL_STORAGE_GET_DEVICE_NUMBER = CTL_CODE(IOCTL_STORAGE_BASE, &H420, METHOD_BUFFERED, FILE_ANY_ACCESS)
End Function
Private Function GetDrivesDevInstByDeviceNumber(ByVal lngDeviceNumber As Long, ByVal uDriveType As Long, ByVal szDosDeviceName As String) As Long
Dim objGuid As GUID, hDevInfo As Long, dwIndex As Long, lngRes As Long, dwSize As Long
Dim objSpdid As SP_DEVICE_INTERFACE_DATA, objSpdd As SP_DEVINFO_DATA, objPspdidd As SP_DEVICE_INTERFACE_DETAIL_DATA
Dim hDrive As Long, objSdn As STORAGE_DEVICE_NUMBER, dwBytesReturned As Long
Dim dwReturn As Long
With objGuid
.Data2 = &HB6BF
.Data3 = &H11D0&
.Data4(0) = &H94&
.Data4(1) = &HF2&
.Data4(2) = &H0&
.Data4(3) = &HA0&
.Data4(4) = &HC9&
.Data4(5) = &H1E&
.Data4(6) = &HFB&
.Data4(7) = &H8B&
Select Case uDriveType
Case 2
If InStr(szDosDeviceName, "\Floppy") Then
.Data1 = &H53F56311
Else
.Data1 = &H53F56307
End If
Case 3
.Data1 = &H53F56307
Case 5
.Data1 = &H53F56308
End Select
End With
hDevInfo = SetupDiGetClassDevs(VarPtr(objGuid), 0, 0, DIGCF_PRESENT Or DIGCF_DEVICEINTERFACE)
If hDevInfo = -1 Then
GetDrivesDevInstByDeviceNumber = 0
Exit Function
End If
objSpdid.cbSize = Len(objSpdid)
Do While 1
lngRes = SetupDiEnumDeviceInterfaces(hDevInfo, 0, objGuid, dwIndex, objSpdid)
If lngRes = 0 Then Exit Do
dwSize = 0
Call SetupDiGetDeviceInterfaceDetail(hDevInfo, objSpdid, ByVal 0&, 0, dwSize, ByVal 0&)
If dwSize <> 0 And dwSize <= 1024 Then
objPspdidd.cbSize = 5
objSpdd.cbSize = Len(objSpdd)
lngRes = SetupDiGetDeviceInterfaceDetail(hDevInfo, objSpdid, objPspdidd, ByVal dwSize, dwReturn, objSpdd)
If lngRes > 0 Then
hDrive = CreateFile(objPspdidd.strDevicePath, 0, FILE_SHARE_READ Or FILE_SHARE_WRITE, ByVal 0&, OPEN_EXISTING, 0, 0)
If hDrive <> -1 Then
lngRes = DeviceIoControl(hDrive, IOCTL_STORAGE_GET_DEVICE_NUMBER, ByVal 0&, 0, objSdn, Len(objSdn), dwBytesReturned, ByVal 0&)
If lngRes Then
If lngDeviceNumber = objSdn.dwDeviceNumber Then
Call CloseHandle(hDrive)
SetupDiDestroyDeviceInfoList hDevInfo
GetDrivesDevInstByDeviceNumber = objSpdd.DevInst
Exit Function
End If
End If
Call CloseHandle(hDrive)
End If
End If
End If
dwIndex = dwIndex + 1
Loop
Call SetupDiDestroyDeviceInfoList(hDevInfo)
End Function
Public Function RemoveUsbDrive(ByVal szDosDeviceName As String, ByVal blnIsShowNote As Boolean) As Boolean
Dim strDrive As String, dwDeviceNumber As Long, hVolume As Long, objSdn As STORAGE_DEVICE_NUMBER, dwBytesReturned As Long
Dim lngRes As Long, uDriveType As Long, strDosDriveName As String, hDevInst As Long, uType As PNP_VETO_TYPE
Dim strVetoName As String, blnSuccess As Boolean, dwDevInstParent As Long, i As Integer, pVetoType As Long
strDrive = Right(szDosDeviceName, 2)
dwDeviceNumber = -1
hVolume = CreateFile(szDosDeviceName, 0, FILE_SHARE_READ Or FILE_SHARE_WRITE, ByVal 0&, OPEN_EXISTING, 0, 0)
If hVolume = -1 Then
RemoveUsbDrive = False
Exit Function
End If
lngRes = DeviceIoControl(hVolume, IOCTL_STORAGE_GET_DEVICE_NUMBER, ByVal 0&, 0, objSdn, Len(objSdn), dwBytesReturned, ByVal 0&)
If lngRes Then
dwDeviceNumber = objSdn.dwDeviceNumber
End If
Call CloseHandle(hVolume)
If dwDeviceNumber = -1 Then
RemoveUsbDrive = False
Exit Function
End If
uDriveType = GetDriveType(strDrive)
strDosDriveName = String(280, Chr(0))
lngRes = QueryDosDevice(strDrive, strDosDriveName, 280)
strDosDriveName = Left(strDosDriveName, InStr(strDosDriveName, Chr(0)) - 1)
If lngRes = 0 Then
RemoveUsbDrive = False
Exit Function
End If
hDevInst = GetDrivesDevInstByDeviceNumber(dwDeviceNumber, uDriveType, strDosDriveName)
If hDevInst = 0 Then
RemoveUsbDrive = False
Exit Function
End If
strVetoName = String(260, Chr(0))
lngRes = CM_Get_Parent(dwDevInstParent, hDevInst, 0)
For i = 0 To 3
If blnIsShowNote Then
lngRes = CM_Request_Device_EjectW(dwDevInstParent, ByVal VarPtr(pVetoType), vbNullString, 0, 0)
Else
lngRes = CM_Request_Device_EjectW(dwDevInstParent, uType, strVetoName, 260, 0)
End If
If lngRes = 0 And uType = PNP_VetoTypeUnknown Then
blnSuccess = True
Exit For
End If
Sleep 300
Next
RemoveUsbDrive = blnSuccess
End Function
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -