⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 cdiskinfo.cls

📁 读取磁盘序列号 读取磁盘序列号 读取磁盘序列号
💻 CLS
📖 第 1 页 / 共 2 页
字号:
VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
  Persistable = 0  'NotPersistable
  DataBindingBehavior = 0  'vbNone
  DataSourceBehavior  = 0  'vbNone
  MTSTransactionMode  = 0  'NotAnMTSObject
END
Attribute VB_Name = "CDiskInfo"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Explicit

'--------------------------------------------------------------------------
'   模  块: 取磁盘硬件信息处理类
'   版  本: 1.0
'   文件名: CDiskInfo.cls
'   作者: 林天炮
'   修改日期:2003-03-13
'
'   功能说明:获取硬盘序列号、型号、磁道扇区信息等
'   版权说明:此为共享代码,根据微软提供的例程改编,可以任意修改及使用,
'             作者对此模块运行所引起的错误不承担任何责任。
'
'             引用此模块时须保留作者署名,有意见或错误请发送至ltpao@sina.com
'
'   注意事项:支持Windows 95 OSR2, Windows 98, Windows NT, Windows 2000
'             XP没有测试,估计没问题,在Win9X下必须保证存在SMARTVSD.vxd
'--------------------------------------------------------------------------

'/****************************************************************************
'*                                                                           *
'* THIS CODE AND INFORMATION IS PROVIDED "AS IS" WITHOUT WARRANTY OF ANY     *
'* KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE       *
'* IMPLIED WARRANTIES OF MERCHANTABILITY AND/OR FITNESS FOR A PARTICULAR     *
'* PURPOSE.                                                                  *
'*                                                                           *
'* Copyright 1993-98  Microsoft Corporation.  All Rights Reserved.           *
'*                                                                           *
'****************************************************************************/

Private Const MAX_IDE_DRIVES As Long = 4   ' Max number of drives assuming primary/secondary, master/slave topology
Private Const READ_ATTRIBUTE_BUFFER_SIZE As Long = 512
Private Const IDENTIFY_BUFFER_SIZE As Long = 512
Private Const READ_THRESHOLD_BUFFER_SIZE As Long = 512

'
' IOCTL commands
'
Private Const DFP_GET_VERSION As Long = &H74080
Private Const DFP_SEND_DRIVE_COMMAND As Long = &H7C084
Private Const DFP_RECEIVE_DRIVE_DATA As Long = &H7C088

'---------------------------------------------------------------------
' GETVERSIONOUTPARAMS contains the data returned from the
' Get Driver Version function.
'---------------------------------------------------------------------
Private Type GETVERSIONOUTPARAMS
    bVersion As Byte       ' Binary driver version.
    bRevision As Byte      ' Binary driver revision.
    bReserved As Byte      ' Not used.
    bIDEDeviceMap As Byte  ' Bit map of IDE devices.
    fCapabilities As Long  ' Bit mask of driver capabilities.
    dwReserved(3) As Long  ' For future use.
End Type

'
' Bits returned in the fCapabilities member of GETVERSIONOUTPARAMS
'
Private Const CAP_IDE_ID_FUNCTION As Long = 1               ' ATA ID command supported
Private Const CAP_IDE_ATAPI_ID As Long = 2                  ' ATAPI ID command supported
Private Const CAP_IDE_EXECUTE_SMART_FUNCTION As Long = 4    ' SMART commannds supported

'---------------------------------------------------------------------
' IDE registers
'---------------------------------------------------------------------
Private Type IDEREGS
    bFeaturesReg As Byte       ' Used for specifying SMART "commands".
    bSectorCountReg As Byte    ' IDE sector count register
    bSectorNumberReg As Byte   ' IDE sector number register
    bCylLowReg As Byte         ' IDE low order cylinder value
    bCylHighReg As Byte        ' IDE high order cylinder value
    bDriveHeadReg As Byte      ' IDE drive/head register
    bCommandReg As Byte        ' Actual IDE command.
    bReserved As Byte          ' reserved for future use.  Must be zero.
End Type

'---------------------------------------------------------------------
' SENDCMDINPARAMS contains the input parameters for the
' Send Command to Drive function.
'---------------------------------------------------------------------
Private Type SENDCMDINPARAMS
    cBufferSize As Long        ' Buffer size in bytes
    irDriveRegs As IDEREGS     ' Structure with drive register values.
    bDriveNumber As Byte       ' Physical drive number to send
                                ' command to (0,1,2,3).
    bReserved(2) As Byte       ' Reserved for future expansion.
    dwReserved(3) As Long      ' For future use.
    bBuffer(0) As Byte         ' Input buffer.
End Type

'
' Valid values for the bCommandReg member of IDEREGS.
'
Private Const IDE_ATAPI_ID As Long = &HA1  ' Returns ID sector for ATAPI.
Private Const IDE_ID_FUNCTION As Long = &HEC  ' Returns ID sector for ATA.
Private Const IDE_EXECUTE_SMART_FUNCTION As Long = &HB0  ' Performs SMART cmd.
                                            ' Requires valid bFeaturesReg,
                                            ' bCylLowReg, and bCylHighReg
'
' Cylinder register values required when issuing SMART command
'
Private Const SMART_CYL_LOW As Long = &H4F
Private Const SMART_CYL_HI As Long = &HC2

'---------------------------------------------------------------------
' Status returned from driver
'---------------------------------------------------------------------
Private Type DRIVERSTATUS
    bDriverError As Byte       ' Error code from driver,
                                ' or 0 if no error.
    bIDEStatus As Byte         ' Contents of IDE Error register.
                                ' Only valid when bDriverError
                                ' is SMART_IDE_ERROR.
    bReserved(1) As Byte       ' Reserved for future expansion.
    dwReserved(1) As Long      ' Reserved for future expansion.
End Type

'
' bDriverError values
'
Private Const SMART_NO_ERROR As Long = 0  ' No error
Private Const SMART_IDE_ERROR As Long = 1  ' Error from IDE controller
Private Const SMART_INVALID_FLAG As Long = 2  ' Invalid command flag
Private Const SMART_INVALID_COMMAND As Long = 3  ' Invalid command byte
Private Const SMART_INVALID_BUFFER As Long = 4  ' Bad buffer (null, invalid addr..)
Private Const SMART_INVALID_DRIVE As Long = 5  ' Drive number not valid
Private Const SMART_INVALID_IOCTL As Long = 6   ' Invalid IOCTL
Private Const SMART_ERROR_NO_MEM As Long = 7  ' Could not lock user's buffer
Private Const SMART_INVALID_REGISTER As Long = 8  ' Some IDE Register not valid
Private Const SMART_NOT_SUPPORTED As Long = 9  ' Invalid cmd flag set
Private Const SMART_NO_IDE_DEVICE As Long = 10 ' Cmd issued to device not present
                                    ' although drive number is valid
' 11-255 reserved

'---------------------------------------------------------------------
' Structure returned by SMART IOCTL for several commands
'---------------------------------------------------------------------
Private Type SENDCMDOUTPARAMS
    cBufferSize As Long        ' Size of bBuffer in bytes
    drvStatus As DRIVERSTATUS  ' Driver status structure.
    bBuffer(0) As Byte         ' Buffer of arbitrary length in which to store the data read from the                                          ' drive.
End Type

'---------------------------------------------------------------------
' Feature register defines for SMART "sub commands"
'---------------------------------------------------------------------
Private Const SMART_READ_ATTRIBUTE_VALUES As Long = &HD0    ' ATA4: Renamed
                                                        ' SMART READ DATA
Private Const SMART_READ_ATTRIBUTE_THRESHOLDS As Long = &HD1    ' Obsoleted in ATA4!
Private Const SMART_ENABLE_DISABLE_ATTRIBUTE_AUTOSAVE As Long = &HD2
Private Const SMART_SAVE_ATTRIBUTE_VALUES As Long = &HD3
Private Const SMART_EXECUTE_OFFLINE_IMMEDIATE As Long = &HD4    ' ATA4
' Vendor specific commands:
Private Const SMART_ENABLE_SMART_OPERATIONS As Long = &HD8
Private Const SMART_DISABLE_SMART_OPERATIONS As Long = &HD9
Private Const SMART_RETURN_SMART_STATUS As Long = &HDA


'---------------------------------------------------------------------
' The following structure defines the structure of a Drive Attribute
'---------------------------------------------------------------------
Private Type DRIVEATTRIBUTE
    bAttrID As Byte        ' Identifies which attribute
    wStatusFlags As Integer    ' see bit definitions below
    bAttrValue As Byte     ' Current normalized value
    bWorstValue As Byte    ' How bad has it ever been?
    bRawValue(5) As Byte   ' Un-normalized value
    bReserved As Byte      ' ...
End Type

'---------------------------------------------------------------------
' The following structure defines the structure of a Warranty Threshold
' Obsoleted in ATA4!
'---------------------------------------------------------------------
Private Type ATTRTHRESHOLD
    bAttrID As Byte            ' Identifies which attribute
    bWarrantyThreshold As Byte ' Triggering value
    bReserved(9) As Byte      ' ...
End Type

'---------------------------------------------------------------------
' The following struct defines the interesting part of the IDENTIFY
' buffer:
'---------------------------------------------------------------------
Private Type IDSECTOR
    wGenConfig As Integer
    wNumCyls As Integer
    wReserved As Integer
    wNumHeads As Integer
    wBytesPerTrack As Integer
    wBytesPerSector As Integer
    wSectorsPerTrack As Integer
    wVendorUnique(2) As Integer
    sSerialNumber(19) As Byte
    wBufferType As Integer
    wBufferSize As Integer
    wECCSize As Integer
    sFirmwareRev(7) As Byte
    sModelNumber(39) As Byte
    wMoreVendorUnique As Integer
    wDoubleWordIO As Integer
    wCapabilities As Integer
    wReserved1 As Integer
    wPIOTiming As Integer
    wDMATiming As Integer
    wBS As Integer
    wNumCurrentCyls As Integer
    wNumCurrentHeads As Integer
    wNumCurrentSectorsPerTrack As Integer
    ulCurrentSectorCapacity As Long
    wMultSectorStuff As Integer
    ulTotalAddressableSectors As Long
    wSingleWordDMA As Integer
    wMultiWordDMA As Integer
    bReserved(127) As Byte
End Type

'---------------------------------------------------------------------
' Valid Attribute IDs
'---------------------------------------------------------------------
Private Const ATTR_INVALID As Long = 0
Private Const ATTR_READ_ERROR_RATE As Long = 1
Private Const ATTR_THROUGHPUT_PERF As Long = 2
Private Const ATTR_SPIN_UP_TIME As Long = 3
Private Const ATTR_START_STOP_COUNT As Long = 4
Private Const ATTR_REALLOC_SECTOR_COUNT As Long = 5
Private Const ATTR_READ_CHANNEL_MARGIN As Long = 6
Private Const ATTR_SEEK_ERROR_RATE As Long = 7
Private Const ATTR_SEEK_TIME_PERF As Long = 8
Private Const ATTR_POWER_ON_HRS_COUNT As Long = 9
Private Const ATTR_SPIN_RETRY_COUNT As Long = 10
Private Const ATTR_CALIBRATION_RETRY_COUNT As Long = 11
Private Const ATTR_POWER_CYCLE_COUNT As Long = 12

'---------------------------------------------------------------------
' Status Flags Values
'---------------------------------------------------------------------
Private Const PRE_FAILURE_WARRANTY As Long = &H1
Private Const ON_LINE_COLLECTION As Long = &H2
Private Const PERFORMANCE_ATTRIBUTE As Long = &H4
Private Const ERROR_RATE_ATTRIBUTE As Long = &H8
Private Const EVENT_COUNT_ATTRIBUTE As Long = &H10
Private Const SELF_PRESERVING_ATTRIBUTE As Long = &H20

Private Const NUM_ATTRIBUTE_STRUCTS As Long = 30


Private Const INVALID_HANDLE_VALUE = -1

Private Const VER_PLATFORM_WIN32s = 0
Private Const VER_PLATFORM_WIN32_WINDOWS = 1
Private Const VER_PLATFORM_WIN32_NT = 2
Private Type OSVERSIONINFO
        dwOSVersionInfoSize As Long
        dwMajorVersion As Long
        dwMinorVersion As Long
        dwBuildNumber As Long
        dwPlatformId As Long
        szCSDVersion As String * 128      '  Maintenance string for PSS usage
End Type
Private Declare Function GetVersionEx Lib "KERNEL32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Private Const CREATE_NEW = 1
Private Const GENERIC_READ = &H80000000
Private Const GENERIC_WRITE = &H40000000
Private Const FILE_SHARE_READ = &H1
Private Const FILE_SHARE_WRITE = &H2
Private Const OPEN_EXISTING = 3
Private Declare Function CreateFile Lib "KERNEL32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, ByVal lpSecurityAttributes As Long, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile 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, ByVal lpOverlapped As Long) As Long
Private Declare Sub CopyMemory Lib "KERNEL32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Declare Function CloseHandle Lib "KERNEL32" (ByVal hObject As Long) As Long

'
' Define global buffers.
'
Private m_DiskInfo As IDSECTOR

'---------------------------------------------------------------------
' Open SMART to allow DeviceIoControl communications.
'---------------------------------------------------------------------
Private Function OpenSMART(ByVal nDrive As Byte) As Long
    Dim hSMARTIOCTL As Long
    hSMARTIOCTL = INVALID_HANDLE_VALUE
    Dim hd As String
    Dim VersionInfo As OSVERSIONINFO
    VersionInfo.dwOSVersionInfoSize = Len(VersionInfo)
    GetVersionEx VersionInfo
    Select Case VersionInfo.dwPlatformId

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -