Results 1 to 37 of 37

Thread: [RESOLVED] How can i get the Serial number of Hard Disk.

  1. #1

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Resolved [RESOLVED] How can i get the Serial number of Hard Disk.

    How can i get Serial number of Hard Disk, i.e. provided by the manufacturer.

  2. #2
    PowerPoster SamOscarBrown's Avatar
    Join Date
    Aug 2012
    Location
    NC, USA
    Posts
    9,126

    Re: How can i get the Serial number of Hard Disk.

    Does this work for you?

    Debug.Print Format(Hex(CreateObject("scripting.filesystemobject").GetDrive("c").SerialNumber), "@@@@-@@@@")

  3. #3
    PowerPoster SamOscarBrown's Avatar
    Join Date
    Aug 2012
    Location
    NC, USA
    Posts
    9,126

    Re: How can i get the Serial number of Hard Disk.

    That MIGHT be just volume serial number...I don't know my Manufacturer's serial number for the (actual) hard disk, but when I run that, I get "A" serial number (obviously for 'C-Drive'). SO, not sure if that is what you are looking for or not.

  4. #4
    PowerPoster ChrisE's Avatar
    Join Date
    Jun 2017
    Location
    Frankfurt
    Posts
    3,034

    Re: How can i get the Serial number of Hard Disk.

    Hi Sam,

    I am guessing like you what the OP want's
    here my guess..
    Code:
    Option Explicit
    
    Private Declare Function GetVolumeInformation Lib "kernel32" _
            Alias "GetVolumeInformationA" (ByVal lpRootPathName _
            As String, ByVal pVolumeNameBuffer As String, ByVal _
            nVolumeNameSize As Long, lpVolumeSerialNumber As Long, _
            lpMaximumComponentLength As Long, lpFileSystemFlags As _
            Long, ByVal lpFileSystemNameBuffer As String, ByVal _
            nFileSystemNameSize As Long) As Long
    
    Const MAX_FILENAME_LEN As Long = 256&
    
    Private Sub Command1_Click()
        Label1.Caption = Abs(SerNum("c"))
    End Sub
    
    Public Function SerNum(Drive$) As Long
        Dim No As Long, s As String * MAX_FILENAME_LEN
        
        Call GetVolumeInformation(Drive & ":\", s, MAX_FILENAME_LEN, _
                                  No, 0&, 0&, s, MAX_FILENAME_LEN)
        SerNum = No
    End Function
    
    Private Sub Form_Load()
        Command1.Caption = "read Serial number"
    End Sub
    regards
    Chris
    to hunt a species to extinction is not logical !
    since 2010 the number of Tigers are rising again in 2016 - 3900 were counted. with Baby Callas it's 3901, my wife and I had 2-3 months the privilege of raising a Baby Tiger.

  5. #5
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,817

    Re: How can i get the Serial number of Hard Disk.

    Or this, which returns the same number and doesn't use the scripting system.

    Code:
    
    Option Explicit
    Private Declare Function GetVolumeInformation Lib "kernel32" Alias "GetVolumeInformationA" (ByVal lpRootPathName As String, ByVal lpVolumeNameBuffer As String, ByVal nVolumeNameSize As Long, lpVolumeSerialNumber As Long, lpMaximumComponentLength As Long, lpFileSystemFlags As Long, ByVal lpFileSystemNameBuffer As String, ByVal nFileSystemNameSize As Long) As Long
    
    Public Function SerialNumberOfDrive(sSingleLetter As String) As Long
        Dim Serial As Long
        Dim VName As String
        Dim FSName As String
        '
        VName = String$(255, vbNullChar)
        FSName = String$(255, vbNullChar)
        'Get the volume information
        GetVolumeInformation sSingleLetter & ":\\", VName, 255, Serial, 0, 0, FSName, 255
        SerialNumberOfDrive = Serial
    End Function
    
    
    Enjoy,
    Elroy

    EDIT1: Ahhh, Chris beat me to it.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  6. #6

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: How can i get the Serial number of Hard Disk.

    Hi everybody for the help. I do like this forum for such support. In these past one month i did a lot of coding work for my project and after a long time i am doing programming in VB.

    After a long search i found something helpful but i stuck at some point. I think it dont return values in 64bit system. Trying to correct it. but still need help....

    http://www.vbforums.com/showthread.p...er-(firmware-)

  7. #7
    PowerPoster ChrisE's Avatar
    Join Date
    Jun 2017
    Location
    Frankfurt
    Posts
    3,034

    Re: How can i get the Serial number of Hard Disk.

    ???

    I am lost as to what you want now

    regards
    Chris
    to hunt a species to extinction is not logical !
    since 2010 the number of Tigers are rising again in 2016 - 3900 were counted. with Baby Callas it's 3901, my wife and I had 2-3 months the privilege of raising a Baby Tiger.

  8. #8

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: How can i get the Serial number of Hard Disk.

    Hi ChrisE,

    I want to get the manufacturers serial number of Hard Disk. Not the Partition volume serial Number. The code in the link at #6 may work. But as it is not returning any value i think the problem is with 64 bit. As i am using 64bit OS. The code was written for 32bit (if i am right).

    so my question is how to get "manufacturers serial number of Hard Disk. Not the Partition volume serial Number."

  9. #9
    PowerPoster ChrisE's Avatar
    Join Date
    Jun 2017
    Location
    Frankfurt
    Posts
    3,034

    Re: How can i get the Serial number of Hard Disk.

    Hi,

    try this...
    Code:
    Private Sub Command2_Click()
    Dim oWMI As Object
    Dim sComputer As String
    Dim oItems As Object
    Dim oItem As Object
     
    'your Computer
    sComputer = "."
     
    ' WMI-Objekt
    Set oWMI = GetObject("winmgmts:{impersonationLevel=impersonate}!\\" _
      & sComputer & "\root\cimv2")
     
    ' WMI-query
    Set oItems = oWMI.ExecQuery("Select * from Win32_DiskDrive")
    For Each oItem In oItems
      On Error Resume Next
      List1.AddItem "Index: " & oItem.Index
      List1.AddItem "InterfaceType: " & oItem.InterfaceType
      List1.AddItem "DeviceID: " & oItem.DeviceID
      List1.AddItem "Model: " & oItem.Model
     
      'Manufactur-Serial No. (>= Vista)
      List1.AddItem "SerialNo: " & oItem.SerialNumber
     List1.AddItem "-------------------------------------" & vbCrLf
      On Error GoTo 0
    Next
    Set oItem = Nothing
    Set oItems = Nothing
    Set oWMI = Nothing
    End Sub
    to hunt a species to extinction is not logical !
    since 2010 the number of Tigers are rising again in 2016 - 3900 were counted. with Baby Callas it's 3901, my wife and I had 2-3 months the privilege of raising a Baby Tiger.

  10. #10

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: How can i get the Serial number of Hard Disk.

    Thank you. It solved my problem. One clarification please. The output in "SerialNo" will get changed after formatting or remain unchanged.

  11. #11
    PowerPoster ChrisE's Avatar
    Join Date
    Jun 2017
    Location
    Frankfurt
    Posts
    3,034

    Re: How can i get the Serial number of Hard Disk.

    Quote Originally Posted by Urgentbody View Post
    Thank you. It solved my problem. One clarification please. The output in "SerialNo" will get changed after formatting or remain unchanged.
    well you will have to try it out. The sample in Post #4 will read a new "SerialNo" after formatting.

    regards
    Chris
    to hunt a species to extinction is not logical !
    since 2010 the number of Tigers are rising again in 2016 - 3900 were counted. with Baby Callas it's 3901, my wife and I had 2-3 months the privilege of raising a Baby Tiger.

  12. #12
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,817

    Re: How can i get the Serial number of Hard Disk.

    And I think it might depend on what you mean by "formatting".

    A "format" from Windows doesn't really do much of anything. It just deletes the root directory structure and builds a new/empty one. For a FAT system, I could tell you precisely what it does. However, I'm not totally familiar with that low-level stuff on NTFS systems.

    However, a "true format" will completely ignore everything on a hard-disk, and rebuild all the sectors from scratch. This isn't typically done with canned Windows utilities, but typically with a utility from the hard-disk's manufacturer.

    So, I would think that a Windows format may leave the serial number intact, where a low-level format would, almost by necessity, probably overwrite it (but it might try to read it and replace it once reformatted, but that may also depend on the manufacturer and the format utility used).

    Best Regards,
    Elroy

    EDIT1: Also, it may depend on how the serial number is stored. If it's stored in some ROM chip on the hard-disk's controller board, then no formatting of any kind should tamper with it. I don't know if there are standards for this or not. If not, I suspect different hard-disk manufacturers may do it differently.
    Last edited by Elroy; Oct 1st, 2017 at 01:44 PM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  13. #13
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: How can i get the Serial number of Hard Disk.

    WMI is not something you want to rely upon. It is a hazardous tool meant only for administrator usage, so the service might not be present at all, might be stopped, or might be secured against non-admin use.

    It also has another problem... before Windows 8 it reports drive serial numbers incorrectly:

    Byte Order Issue with the SerialNumber member of the WMI Win32_DiskDrive class


    I had previously posted a non-WMI solution here:

    http://www.vbforums.com/showthread.p...=1#post4791279


    Now that I know about the "correction" in Windows 8 and beyond I have altered that code to work properly. I have tested it on Windows 10, and now on Windows Home Server 2011 (basically Windows 7/Windows Server 2008 R2).

    The attachment contains a small demo project that enumerates all drives.

    The DriveInfo class accepts a drive letter assignment to its Letter property. This causes it to look up drive information. After that you can interrogate several other properties such as the SerialNumber property.
    Attached Files Attached Files
    Last edited by dilettante; Oct 4th, 2017 at 11:09 AM. Reason: Updated attachment to 2.1

  14. #14

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: How can i get the Serial number of Hard Disk.

    Hi, dilettante

    You are The one. your solutions are always top class. I really appreciate that. Thanks to the Forum.

  15. #15
    Frenzied Member
    Join Date
    Jan 2010
    Posts
    1,103

    Re: How can i get the Serial number of Hard Disk.

    Quote Originally Posted by Urgentbody View Post
    Hi, dilettante

    You are The one. your solutions are always top class. I really appreciate that. Thanks to the Forum.
    Instead of praise, you should provide feedback of the testing result on different OS to help for bugs or improvements.

    Results:
    I found the USB portable HD returns variant results:
    Win10 32 bits Laptop: SerialNumber = "100"
    Win10 64 bits Desktop: SerialNumber = "100"
    Win7 32 bits Desktop: SerialNumber = "binary?"
    Last edited by Jonney; Oct 2nd, 2017 at 11:11 PM.

  16. #16
    Frenzied Member
    Join Date
    Dec 2008
    Location
    Melbourne Australia
    Posts
    1,487

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    I second what Jonney said.
    Also, you should click on 'rate this post' on the bottom left of the post that helped you.

  17. #17
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Always test something like this thoroughly before relying on it for anything serious. You also need to stay on top of it because conditions may change.

    For example my earlier version seemed to work fine, then Microsoft changed things in Windows 8 and suddenly it was broken.

  18. #18

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: How can i get the Serial number of Hard Disk.

    Hi,
    I am on vacation and only laptop with me Win 7 Ulti 64Bit. The code is working perfect. Latter on i will check on other systems.

    Thank You.

  19. #19

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Tracing HDD Serial Number

    The test on Win 7 64bit. The findings of the Posts in

    http://www.vbforums.com/showthread.p...r-of-Hard-Disk

    #9

    The code correctly finding S/N of External Hard Disc but failed to track USB flash drive S/N and HDD S/N

    #13

    The code correctly finds S/N for USB flash drive and HDD but for external hard disc it flips each two characters.

  20. #20
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Tracing HDD Serial Number

    Annoying, hmm?

    I'm not sure what path gets taken for USB HDDs so I'll try experimenting to see if that case can be corrected. You might think this would be a pretty solid thing, but the information really isn't important to Windows or most applications. Since it is normally only used for inventory purposes Microsoft probably didn't have much incentive for getting it right and making it more easily accessible.

    I suppose "flipped characters" don't matter much in a copy protection scheme or something unless somebody moves from pre-Win8 to Win8-or-later. At that point letter-swapping might break any existing registration data.

  21. #21
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Tracing HDD Serial Number

    I have replaced the attachment here:

    http://www.vbforums.com/showthread.p...=1#post5220521

    Now there is a version 2.1 that might work better. Can you try it on Windows 7?

  22. #22

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: Tracing HDD Serial Number

    Yes its absolutely true that in copy protection its useful and that i was searching for.

    The version 2.1 is now tracing the External HDD S/N correctly. But now its reading HDD SerialNumber = "02020202020202020202a5027463345553434574" exactly the same as in code #9 but in a flipped manner to each 2 characters.

  23. #23
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Tracing HDD Serial Number

    Ouch. That's disappointing.

    You must have a drive that returns the serial number as ASCII hex digits, something I commented out as obsolete. When I left it in there I was getting garbage characters for the serial number of a USB HDD.

    I'll have to play with it more to see if I can create a version that can tell the difference between a string of hex and a string that only contains hex digit characters.

    This isn't easy because of the inconsistent results for different drives and buses.

  24. #24
    PowerPoster ChrisE's Avatar
    Join Date
    Jun 2017
    Location
    Frankfurt
    Posts
    3,034

    Re: Tracing HDD Serial Number

    Hi,
    I friend of mine gave me this (not my Code)

    Code:
    'Author : H.A.YOUNES
    
    
    
    Option Explicit
     
    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 Const CREATE_NEW = 1
    Private Const INVALID_HANDLE_VALUE = -1
    Private Const VER_PLATFORM_WIN32_NT = 2
    Private Const IDENTIFY_BUFFER_SIZE = 512
    Private Const OUTPUT_DATA_SIZE = IDENTIFY_BUFFER_SIZE + 16
    
    '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
    
    '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     'Bytes reserved
       dwReserved(3)   As Long     'DWORDS reserved
       bBuffer()      As Byte      'Input buffer.
    End Type
    
    'Valid values for the bCommandReg member of IDEREGS.
    Private Const IDE_ID_FUNCTION = &HEC            'Returns ID sector for ATA.
    Private Const IDE_EXECUTE_SMART_FUNCTION = &HB0 'Performs SMART cmd.
                                                    'Requires valid bFeaturesReg,
                                                    'bCylLowReg, and bCylHighReg
    
    'Cylinder register values required when issuing SMART command
    Private Const SMART_CYL_LOW = &H4F
    Private Const SMART_CYL_HI = &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
       dwReserved(1) As Long
     End Type
    
    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
    
    'Structure returned by SMART IOCTL commands
    Private Type SENDCMDOUTPARAMS
      cBufferSize   As Long         'Size of Buffer in bytes
      DRIVERSTATUS  As DRIVERSTATUS 'Driver status structure
      bBuffer()    As Byte          'Buffer of arbitrary length for data read from drive
    End Type
    
    'Vendor specific feature register defines
    'for SMART "sub commands"
    Private Const SMART_ENABLE_SMART_OPERATIONS = &HD8
    
    'Status Flags Values
    Public Enum STATUS_FLAGS
       PRE_FAILURE_WARRANTY = &H1
       ON_LINE_COLLECTION = &H2
       PERFORMANCE_ATTRIBUTE = &H4
       ERROR_RATE_ATTRIBUTE = &H8
       EVENT_COUNT_ATTRIBUTE = &H10
       SELF_PRESERVING_ATTRIBUTE = &H20
    End Enum
    
    'IOCTL commands
    Private Const DFP_GET_VERSION = &H74080
    Private Const DFP_SEND_DRIVE_COMMAND = &H7C084
    Private Const DFP_RECEIVE_DRIVE_DATA = &H7C088
    
    Private Type ATTR_DATA
       AttrID As Byte
       AttrName As String
       AttrValue As Byte
       ThresholdValue As Byte
       WorstValue As Byte
       StatusFlags As STATUS_FLAGS
    End Type
    
    Private Type DRIVE_INFO
       bDriveType As Byte
       SerialNumber As String
       Model As String
       FirmWare As String
       Cilinders As Long
       Heads As Long
       SecPerTrack As Long
       BytesPerSector As Long
       BytesperTrack As Long
       NumAttributes As Byte
       Attributes() As ATTR_DATA
    End Type
    
    Private Enum IDE_DRIVE_NUMBER
       PRIMARY_MASTER
       PRIMARY_SLAVE
       SECONDARY_MASTER
       SECONDARY_SLAVE
       TERTIARY_MASTER
       TERTIARY_SLAVE
       QUARTIARY_MASTER
       QUARTIARY_SLAVE
    End Enum
    
    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 CloseHandle Lib "kernel32" _
      (ByVal hObject 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 Sub CopyMemory Lib "kernel32" _
       Alias "RtlMoveMemory" _
      (hpvDest As Any, _
       hpvSource As Any, _
       ByVal cbCopy As Long)
      
    Private Type OSVERSIONINFO
       OSVSize As Long
       dwVerMajor As Long
       dwVerMinor As Long
       dwBuildNumber As Long
       PlatformID As Long
       szCSDVersion As String * 128
    End Type
    
    Private Declare Function GetVersionEx Lib "kernel32" _
       Alias "GetVersionExA" _
      (LpVersionInformation As OSVERSIONINFO) As Long
    
    
    
    Private Sub Form_Load()
    
       Command1.Caption = "Get Drive Info"
          Dim di As DRIVE_INFO
    di = GetDriveInfo(0)
    Me.Caption = Trim$(di.Model) & vbCrLf
    Me.Caption = Me.Caption & " - " & Trim$(di.SerialNumber)
    
    End Sub
    
    
    Private Sub Command1_Click()
    
       Dim di As DRIVE_INFO
       Dim drvNumber As Long
       
       For drvNumber = PRIMARY_MASTER To QUARTIARY_SLAVE
       
          di = GetDriveInfo(drvNumber)
          
          List1.AddItem "Drive " & drvNumber
          
          With di
          
             Select Case .bDriveType
                Case 0
                   List1.AddItem vbTab & "[Not present]"
                Case 1
                   List1.AddItem vbTab & "Model:" & vbTab & Trim$(.Model)
                   List1.AddItem vbTab & "Serial No:" & vbTab & Trim$(.SerialNumber)
                Case 2
                   List1.AddItem vbTab & "[ATAPI drive - info not available]"
                Case Else
                   List1.AddItem vbTab & "[drive type not known]"
             End Select
             
          End With
          
       Next
       
    End Sub
    
    
    Private Function GetDriveInfo(drvNumber As IDE_DRIVE_NUMBER) As DRIVE_INFO
        
       Dim hDrive As Long
       Dim di As DRIVE_INFO
       
       hDrive = SmartOpen(drvNumber)
       
       If hDrive <> INVALID_HANDLE_VALUE Then
       
          If SmartGetVersion(hDrive) = True Then
          
             With di
                .bDriveType = 0
                .NumAttributes = 0
                ReDim .Attributes(0)
                .bDriveType = 1
             End With
             
             If SmartCheckEnabled(hDrive, drvNumber) Then
                
                If IdentifyDrive(hDrive, IDE_ID_FUNCTION, drvNumber, di) = True Then
             
                   GetDriveInfo = di
                   
                End If   'IdentifyDrive
             End If   'SmartCheckEnabled
          End If   'SmartGetVersion
       End If   'hDrive <> INVALID_HANDLE_VALUE
       
       CloseHandle hDrive
       
    End Function
    
    
    Private Function IdentifyDrive(ByVal hDrive As Long, _
                                   ByVal IDCmd As Byte, _
                                   ByVal drvNumber As IDE_DRIVE_NUMBER, _
                                   di As DRIVE_INFO) As Boolean
        
      'Function: Send an IDENTIFY command to the drive
      'drvNumber = 0-3
      'IDCmd = IDE_ID_FUNCTION or IDE_ATAPI_ID
       Dim SCIP As SENDCMDINPARAMS
       Dim IDSEC As IDSECTOR
       Dim bArrOut(OUTPUT_DATA_SIZE - 1) As Byte
       Dim cbBytesReturned As Long
       
       With SCIP
          .cBufferSize = IDENTIFY_BUFFER_SIZE
          .bDriveNumber = CByte(drvNumber)
            
          With .irDriveRegs
             .bFeaturesReg = 0
             .bSectorCountReg = 1
             .bSectorNumberReg = 1
             .bCylLowReg = 0
             .bCylHighReg = 0
             .bDriveHeadReg = &HA0 'compute the drive number
             If Not IsWinNT4Plus Then
                .bDriveHeadReg = .bDriveHeadReg Or ((drvNumber And 1) * 16)
             End If
             'the command can either be IDE
             'identify or ATAPI identify.
             .bCommandReg = CByte(IDCmd)
          End With
       End With
       
       If DeviceIoControl(hDrive, _
                          DFP_RECEIVE_DRIVE_DATA, _
                          SCIP, _
                          Len(SCIP) - 4, _
                          bArrOut(0), _
                          OUTPUT_DATA_SIZE, _
                          cbBytesReturned, _
                          ByVal 0&) Then
                          
          CopyMemory IDSEC, bArrOut(16), Len(IDSEC)
    
          di.Model = StrConv(SwapBytes(IDSEC.sModelNumber), vbUnicode)
          di.SerialNumber = StrConv(SwapBytes(IDSEC.sSerialNumber), vbUnicode)
          
          IdentifyDrive = True
          
        End If
        
    End Function
    
    
    Private Function IsWinNT4Plus() As Boolean
    
      'returns True if running Windows NT4 or later
       Dim osv As OSVERSIONINFO
    
       osv.OSVSize = Len(osv)
    
       If GetVersionEx(osv) = 1 Then
       
          IsWinNT4Plus = (osv.PlatformID = VER_PLATFORM_WIN32_NT) And _
                         (osv.dwVerMajor >= 4)
     
       End If
    
    End Function
    
    
    Private Function SmartCheckEnabled(ByVal hDrive As Long, _
                                       drvNumber As IDE_DRIVE_NUMBER) As Boolean
       
      'SmartCheckEnabled - Check if SMART enable
      'FUNCTION: Send a SMART_ENABLE_SMART_OPERATIONS command to the drive
      'bDriveNum = 0-3
       Dim SCIP As SENDCMDINPARAMS
       Dim SCOP As SENDCMDOUTPARAMS
       Dim cbBytesReturned As Long
       
       With SCIP
       
          .cBufferSize = 0
          
          With .irDriveRegs
               .bFeaturesReg = SMART_ENABLE_SMART_OPERATIONS
               .bSectorCountReg = 1
               .bSectorNumberReg = 1
               .bCylLowReg = SMART_CYL_LOW
               .bCylHighReg = SMART_CYL_HI
    
               .bDriveHeadReg = &HA0
                If Not IsWinNT4Plus Then
                   .bDriveHeadReg = .bDriveHeadReg Or ((drvNumber And 1) * 16)
                End If
               .bCommandReg = IDE_EXECUTE_SMART_FUNCTION
               
           End With
           
           .bDriveNumber = drvNumber
           
       End With
       
       SmartCheckEnabled = DeviceIoControl(hDrive, _
                                          DFP_SEND_DRIVE_COMMAND, _
                                          SCIP, _
                                          Len(SCIP) - 4, _
                                          SCOP, _
                                          Len(SCOP) - 4, _
                                          cbBytesReturned, _
                                          ByVal 0&)
    End Function
    
    
    Private Function SmartGetVersion(ByVal hDrive As Long) As Boolean
       
       Dim cbBytesReturned As Long
       Dim GVOP As GETVERSIONOUTPARAMS
       
       SmartGetVersion = DeviceIoControl(hDrive, _
                                         DFP_GET_VERSION, _
                                         ByVal 0&, 0, _
                                         GVOP, _
                                         Len(GVOP), _
                                         cbBytesReturned, _
                                         ByVal 0&)
       
    End Function
    
    
    Private Function SmartOpen(drvNumber As IDE_DRIVE_NUMBER) As Long
    
      'Open SMART to allow DeviceIoControl
      'communications and return SMART handle
    
       If IsWinNT4Plus() Then
          
          SmartOpen = CreateFile("\\.\PhysicalDrive" & CStr(drvNumber), _
                                 GENERIC_READ Or GENERIC_WRITE, _
                                 FILE_SHARE_READ Or FILE_SHARE_WRITE, _
                                 ByVal 0&, _
                                 OPEN_EXISTING, _
                                 0&, _
                                 0&)
    
       Else
          
          SmartOpen = CreateFile("\\.\SMARTVSD", _
                                  0&, 0&, _
                                  ByVal 0&, _
                                  CREATE_NEW, _
                                  0&, _
                                  0&)
       End If
       
    End Function
    
    
    Private Function SwapBytes(b() As Byte) As Byte()
       
      'Note: VB4-32 and VB5 do not support the
      'return of arrays from a function. For
      'developers using these VB versions there
      'are two workarounds to this restriction:
      '
      '1) Change the return data type ( As Byte() )
      '   to As Variant (no brackets). No change
      '   to the calling code is required.
      '
      '2) Change the function to a sub, remove
      '   the last line of code (SwapBytes = b()),
      '   and take advantage of the fact the
      '   original byte array is being passed
      '   to the function ByRef, therefore any
      '   changes made to the passed data are
      '   actually being made to the original data.
      '   With this workaround the calling code
      '   also requires modification:
      '
      '      di.Model = StrConv(SwapBytes(IDSEC.sModelNumber), vbUnicode)
      '
      '   ... to ...
      '
      '      Call SwapBytes(IDSEC.sModelNumber)
      '      di.Model = StrConv(IDSEC.sModelNumber, vbUnicode)
       
       Dim bTemp As Byte
       Dim cnt As Long
    
       For cnt = LBound(b) To UBound(b) Step 2
          bTemp = b(cnt)
          b(cnt) = b(cnt + 1)
          b(cnt + 1) = bTemp
       Next cnt
          
       SwapBytes = b()
          
    End Function
    regards
    Chris
    to hunt a species to extinction is not logical !
    since 2010 the number of Tigers are rising again in 2016 - 3900 were counted. with Baby Callas it's 3901, my wife and I had 2-3 months the privilege of raising a Baby Tiger.

  25. #25
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Here is another update that might refine the results a little more for some hard drives.

    This version tries collapsing "hex digits" to ASCII, then if the resulting "ASCII" looks like a valid serial number (alphanumeric, hyphens, spaces) it keeps that. Otherwise it reports the "digits" as the serial number.

    Sort of a heuristic process but as far as I can tell disk serial numbers were done in several ways over the years.
    Attached Files Attached Files
    Last edited by dilettante; Oct 5th, 2017 at 04:58 PM. Reason: more info about 2.2

  26. #26
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Tracing HDD Serial Number

    Here is yet another page worth reading:

    WMI Disk serial number

    Basically it comes down to the strings the vendor provides, and whether or not a given version of Windows swaps the characters.

  27. #27
    PowerPoster ChrisE's Avatar
    Join Date
    Jun 2017
    Location
    Frankfurt
    Posts
    3,034

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Hi dilettante,

    I tried you program in Post# 25

    I recieve an Error when loading = DeviceIoControl 1
    Debugging line showed
    Code:
    Public Property Let Letter(ByVal RHS As String)
        Dim hDevice As Long
        Dim spQuery As STORAGE_PROPERTY_QUERY
        Dim sdDesc As STORAGE_DEVICE_DESCRIPTOR
        Dim BytesReturned As Long
        Dim Size As Long
        Dim Bytes() As Byte
        Dim I As Integer
        Dim Temp As Byte
        Dim Temps() As Byte
        Dim UsbSerial As String
        
        RHS = UCase$(Left$(RHS, 1))
        If RHS Like "[A-Z]" Then
            mLetter = RHS
            
            hDevice = CreateFile("\\.\" & mLetter & ":", _
                                 0, _
                                 FILE_SHARE_READ Or FILE_SHARE_WRITE, _
                                 0, _
                                 OPEN_EXISTING, _
                                 0, _
                                 0)
            If hDevice = INVALID_HANDLE_VALUE Then
                Err.Raise &H80047100, TypeName(Me), "CreateFile error " & CStr(Err.LastDllError)
            Else
                If DeviceIoControl(hDevice, _
                                   IOCTL_STORAGE_QUERY_PROPERTY, _
                                   VarPtr(spQuery), _
                                   Len(spQuery), _
                                   VarPtr(sdDesc), _
                                   Len(sdDesc), _
                                   BytesReturned, _
                                   0) = 0 Then
                    Err.Raise &H80047104, _
                              TypeName(Me), _
                              "DeviceIoControl error " & CStr(Err.LastDllError)
                Else
                    CloseHandle hDevice
                    With sdDesc
                        mBusType = .BusType
                        mDeviceType = .DeviceType
                        mRemovable = .RemovableMedia <> 0
    '.......
    System: Win XP Sp3

    regards
    Chris
    to hunt a species to extinction is not logical !
    since 2010 the number of Tigers are rising again in 2016 - 3900 were counted. with Baby Callas it's 3901, my wife and I had 2-3 months the privilege of raising a Baby Tiger.

  28. #28

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    The Win7 output for#25 is

    SerialNumber = "02020202020202020202a5027463345553434574"

    same result as the output in Vr 2.1

  29. #29
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Quote Originally Posted by Urgentbody View Post
    The Win7 output for#25 is

    SerialNumber = "02020202020202020202a5027463345553434574"

    same result as the output in Vr 2.1
    Sorry about that. This is a tough one. Without the same hardware to test it is hard to get it right.

    It looks like we have an ASCII serial number sent as hex digits here, but reversed so they are not being detected as a valid hex-format serial number but version 2.2 of my class.

    This attachment just has a modified (2.3) DriveInfo.cls, try replacing the 2.2 version with this one.
    Attached Files Attached Files

  30. #30
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Quote Originally Posted by ChrisE View Post
    I tried you program in Post# 25

    I recieve an Error when loading = DeviceIoControl 1
    I'm not sure why this error is occurring. Error 1 should be "Incorrect function." However IOCTL_STORAGE_QUERY_PROPERTY control code appears to be good even on Windows XP.

  31. #31
    PowerPoster ChrisE's Avatar
    Join Date
    Jun 2017
    Location
    Frankfurt
    Posts
    3,034

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Hi,

    stops here..
    Code:
     If DeviceIoControl(hDevice, _
                                   IOCTL_STORAGE_QUERY_PROPERTY, _
                                   VarPtr(spQuery), _
                                   Len(spQuery), _
                                   VarPtr(sdDesc), _
                                   Len(sdDesc), _
                                   BytesReturned, _
                                   0) = 0 Then
                    Err.Raise &H80047104, _
                              TypeName(Me), _
                              "DeviceIoControl error " & CStr(Err.LastDllError)
    If I get Time next week I'll try again, and Report if I could get it solved

    regards
    Chris
    to hunt a species to extinction is not logical !
    since 2010 the number of Tigers are rising again in 2016 - 3900 were counted. with Baby Callas it's 3901, my wife and I had 2-3 months the privilege of raising a Baby Tiger.

  32. #32

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Perfect,
    Now the problem fixed. no more garbage characters.

  33. #33
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Quote Originally Posted by Urgentbody View Post
    Now the problem fixed. no more garbage characters.
    Until somebody finds another combination of OS, drive, and bus that fails.

  34. #34

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Hi,
    Code at #29 gives the following error on a Win 7 Ultimate, whereas i have checked it on 4 different Win 7 Ultimate with no error.

    Error &H80047104 DeviceIoControl error 1
    Drive letter: "C"

    Error &H80047104 DeviceIoControl error 1
    Drive letter: "D"

    Error &H80047104 DeviceIoControl error 1
    Drive letter: "E"

    Error &H80047104 DeviceIoControl error 1
    Drive letter: "F"

    what may be the reason?

  35. #35
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    System error 1 is ERROR_INVALID_FUNCTION. I have no idea why you are getting this. You may have to do some research.

    See IOCTL_STORAGE_QUERY_PROPERTY control code.
    Last edited by dilettante; Oct 19th, 2017 at 12:31 PM.

  36. #36
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    One thing you might try is this change:

    Code:
    Private Type STORAGE_DEVICE_DESCRIPTOR
        Version As Long '0
        Size As Long '4
        DeviceType As Byte '8
        DeviceTypeModifier As Byte '9
        RemovableMedia As Byte '10
        CommandQueueing As Byte '11
        VendorIdOffset As Long '12
        ProductIdOffset As Long '16
        ProductRevisionOffset As Long '20
        SerialNumberOffset As Long '24
        BusType As BUS_TYPES '28
        RawPropertiesLength As Long '32
        RawDeviceProperties(36 To 511) As Byte '36
    End Type
    I.e. increasing the size of the buffer, more bytes for RawDeviceProperties. Just a wild guess though.

  37. #37

    Thread Starter
    Lively Member
    Join Date
    Sep 2017
    Posts
    79

    Re: [RESOLVED] How can i get the Serial number of Hard Disk.

    Thank you dilettante,
    255 --> 511 didnt solved.
    However trying to further investigate storage query

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width