read BIOS or HDD or Machine Serial Number

Collapse
This topic is closed.
X
X
 
  • Time
  • Show
Clear All
new posts
  • Gavin

    read BIOS or HDD or Machine Serial Number

    Hi, I'm a newbie to programming of any kind. I have posted this to other
    groups in a hope to get a response from anyone.

    Can any one tell me how to make my VB program read the Bios serial number
    (or would HDD be better, or both?) and put that info into VB prog so the
    program won't work on another computer. My program uses an MSAccess table.

    Much appreciated if you can help!

    Thanks
    Gavin






  • Samuel Hon

    #2
    Re: read BIOS or HDD or Machine Serial Number

    There is a api call to return the HD serial number. I cant remember it
    off the top of my head, maybe someone else can help...

    Comment

    • J French

      #3
      Re: read BIOS or HDD or Machine Serial Number

      On 8 Aug 2003 09:09:51 -0700, noreply@samuelh on.co.uk (Samuel Hon)
      wrote:
      [color=blue]
      >There is a api call to return the HD serial number. I cant remember it
      >off the top of my head, maybe someone else can help...[/color]

      GetVolumeInform ation

      Comment

      • mayayana

        #4
        Re: read BIOS or HDD or Machine Serial Number

        There's an undocumented VB function:

        Declare Sub GetMem1 Lib "msvbvm60.d ll" (ByVal MemAddress As Long, var As
        Byte)

        It lets you read one byte of memory at a time. Since the BIOS is loaded
        into RAM at startup you could read, say, 50 bytes of BIOS to get a string.
        I don't remember offhand what the area is reserved for BIOS, but I do know
        that you can pick out the BIOS date on 9x by reading 8 bytes starting with
        &HFFFF5 (ex.: 04/06/99 ).

        I don't think that NT lets you read that area, but I'm not sure about
        that.
        I did see a small system info. program awhile back that, among other things,
        would spit out the entire BIOS as text. You'd have to play around with it
        to
        see if something like that would be a possible solution.

        --
        --
        André Joubert <jaji92@sympati co.ca> wrote in message
        news:FiSYa.7604 $pq5.1037834@ne ws20.bellglobal .com...[color=blue]
        > That API DOES NOT return the HDD serial no. but only the volume serial
        > as selected by the format command. It will change every time you format[/color]
        your[color=blue]
        > disk. There will be one volume serial no. per partition. So on single HDD
        > with
        > 3 volumes (3 partitions) you get 3 volume serial no.
        >
        > André
        >
        >
        > "J French" <erewhon@nowher e.com> wrote in message
        > news:3f33d2dd.1 6421519@news.bt click.com...[color=green]
        > > On 8 Aug 2003 09:09:51 -0700, noreply@samuelh on.co.uk (Samuel Hon)
        > > wrote:
        > >[color=darkred]
        > > >There is a api call to return the HD serial number. I cant remember it
        > > >off the top of my head, maybe someone else can help...[/color]
        > >
        > > GetVolumeInform ation[/color]
        >
        >[/color]


        Comment

        • Matt

          #5
          Re: read BIOS or HDD or Machine Serial Number

          erewhon@nowhere .com (J French) wrote in message news:<3f34acc1. 1688691@news.bt click.com>...[color=blue]
          > On Fri, 8 Aug 2003 14:51:09 -0400, "André Joubert"
          > <jaji92@sympati co.ca> wrote:
          >[color=green]
          > >That API DOES NOT return the HDD serial no. but only the volume serial
          > >as selected by the format command. It will change every time you format your
          > >disk. There will be one volume serial no. per partition. So on single HDD
          > >with
          > >3 volumes (3 partitions) you get 3 volume serial no.[/color]
          >
          > Totally agreed, but that sounds like the API Samuel Hon was thinking
          > about
          >
          > The only other method I've heard of, is for SMART complient drives
          >
          > Private Function OpenSmart(drv_n um As IDE_DRIVE_NUMBE R) As Long
          > If IsWindowsNT Then
          > OpenSmart = CreateFile("\\. \PhysicalDrive" _
          > & CStr(drv_num), _
          > GENERIC_READ Or GENERIC_WRITE, _
          > FILE_SHARE_READ Or FILE_SHARE_WRIT E, _
          > ByVal 0&, OPEN_EXISTING, 0, 0)
          > Else
          > OpenSmart = CreateFile("\\. \SMARTVSD", _
          > 0, 0, ByVal 0&, CREATE_NEW, 0, 0)
          > End If
          > End Function
          >
          > And then do some hefty DeviceIOControl[/color]

          This is the code I use:

          Private Declare Function GetVolumeInform ation Lib "kernel32" _ Alias
          "GetVolumeInfor mationA" (ByVal lpRootPathName As String, ByVal _
          lpVolumeNameBuf fer As String, ByVal nVolumeNameSize As Long, _
          lpVolumeSerialN umber As Long, lpMaximumCompon entLength As Long, _
          lpFileSystemFla gs As Long, ByVal lpFileSystemNam eBuffer As String,
          ByVal _ nFileSystemName Size As Long) As Long
          Public lngVolumeID As Long

          'I use this in my form load event
          'Serial #
          Dim nRet As Long
          Dim VolName As String
          Dim MaxCompLen As Long
          Dim VolFlags As Long
          Dim VolFileSys As String

          VolName = Space$(256)
          VolFileSys = Space$(256)

          nRet = GetVolumeInform ation("C:\", VolName, Len(VolName), lngVolumeID,
          _
          MaxCompLen, VolFlags, VolFileSys, Len(VolFileSys) )
          Text1.Text = lngVolumeID ' Serial Number

          Comment

          • d j tailor

            #6
            Re: read BIOS or HDD or Machine Serial Number

            Hello gavin.
            Try the code below.It doesn't need explanation.


            Private Declare Function GetVolumeInform ation Lib _
            "kernel32.d ll" Alias "GetVolumeInfor mationA" _
            (ByVal lpRootPathName As String, _
            ByVal lpVolumeNameBuf fer As String, _
            ByVal nVolumeNameSize As Integer, _
            lpVolumeSerialN umber As Long, _
            lpMaximumCompon entLength As Long, _
            lpFileSystemFla gs As Long, _
            ByVal lpFileSystemNam eBuffer As String, _
            ByVal nFileSystemName Size As Long) As Long



            Public Function DriveSerialNumb er(ByVal Drive As String) As Long

            'usage: SN = DriveSerialNumb er("C:\")

            Dim lAns As Long
            Dim lRet As Long
            Dim sVolumeName As String, sDriveType As String
            Dim sDrive As String

            'Deal with one and two character input values
            sDrive = Drive
            If Len(sDrive) = 1 Then
            sDrive = sDrive & ":\"
            ElseIf Len(sDrive) = 2 And Right(sDrive, 1) = ":" Then
            sDrive = sDrive & "\"
            End If

            sVolumeName = String$(255, Chr$(0))
            sDriveType = String$(255, Chr$(0))

            lRet = GetVolumeInform ation(sDrive, sVolumeName, _
            255, lAns, 0, 0, sDriveType, 255)

            DriveSerialNumb er = lAns
            End Function

            Comment

            • R.Wieser

              #7
              Re: read BIOS or HDD or Machine Serial Number

              d j tailor <djt1@rediffmai l.com> schreef in berichtnieuws
              1534be1f.030810 0237.469b1ca5@p osting.google.c om...

              Hello d j,
              [color=blue]
              > Hello gavin.
              > Try the code below.It doesn't need explanation.
              >
              > Private Declare Function GetVolumeInform ation Lib _
              > "kernel32.d ll" Alias "GetVolumeInfor mationA" _[/color]

              [Snip]

              Actually, it *does* need some explanation ... Not on how it works, but
              rather on what it does. This function does not retrieve a serial-number as
              ment by the OP.

              The serial-number retrieved by the above call changes with every
              Format-action you do. It allso does retrieve different numbers for every
              logical drive in/on a physical disk, as well as floppies. With a bit of
              work you can alter that serial-number to be whatever you want (just don't
              give all your logical drives/floppies the same number :-)

              Reading the places the OP wants to retrieve serial-numbers from, my, ahem
              ..., "guess" is that he's looking for numbers that do not change (easily).
              Probably he's in the process of trying to lock some software to a specific
              computer.

              Alas, although a physical drive does have a fixed *manufacturers*
              serial-number (which is quite easily retrieved from within DOS), I have not
              found/seen/read of a method to retrieve it from within Windows.

              Regards,
              Rudy Wieser



              Comment

              • J French

                #8
                Re: read BIOS or HDD or Machine Serial Number

                On Fri, 08 Aug 2003 21:15:18 GMT, "mayayana"
                <mayayana4@mind spring.com> wrote:
                [color=blue]
                >There's an undocumented VB function:
                >
                >Declare Sub GetMem1 Lib "msvbvm60.d ll" (ByVal MemAddress As Long, var As
                >Byte)
                >
                > It lets you read one byte of memory at a time. Since the BIOS is loaded
                >into RAM at startup you could read, say, 50 bytes of BIOS to get a string.
                >I don't remember offhand what the area is reserved for BIOS, but I do know
                >that you can pick out the BIOS date on 9x by reading 8 bytes starting with
                >&HFFFF5 (ex.: 04/06/99 ).[/color]

                Mayayana,

                That is really interesting
                - sadly it is not supposed to work for NT, XP etc
                - also it is really MoveMemory in Drag (example below)

                However looking for it got me here:



                Interesting ... there is some meat in that - Thanks

                Demo to get BIOS Date - GetMem1 versus RTLMoveMemory

                Option Explicit

                Private Declare Sub GetMem1 _
                Lib "msvbvm60.d ll" _
                (ByVal MemAddress As Long, _
                var As Byte)

                Private Declare Sub MoveMemory _
                Lib "kernel32" _
                Alias "RtlMoveMem ory" _
                (ByVal Dest As Any, _
                ByVal Source As Any, _
                ByVal Bytes As Long)

                Private Sub Command1_Click( )
                Dim B As Byte, L9&
                For L9 = 0 To 7
                Call GetMem1(&HFFFF5 + L9, B)
                Me.Print Chr$(B);
                Next
                Me.Print
                For L9 = 0 To 7
                Call MoveMemory(VarP tr(B), ByVal &HFFFF5 + L9, 1)
                Me.Print Chr$(B);
                Next

                End Sub


                Comment

                • J French

                  #9
                  Re: read BIOS or HDD or Machine Serial Number

                  On Sun, 10 Aug 2003 14:17:11 +0200, "R.Wieser"
                  <rwieser-killthis-@xs4all.nl> wrote:

                  <snip>[color=blue]
                  >
                  >Alas, although a physical drive does have a fixed *manufacturers*
                  >serial-number (which is quite easily retrieved from within DOS), I have not
                  >found/seen/read of a method to retrieve it from within Windows.[/color]

                  There is a method
                  - I do not recommend it - it relies on a level of technology that one
                  of my drives does not support

                  I do not know where I got the code, however I doubt that they will
                  mind it being re-posted ... if otherwise ... apologies

                  - I strongly recommend NOT using this stuff
                  - it is asking for support calls
                  - however it is worth *knowing* about


                  ' 20th July 2002 from NG
                  ' Works for Drive 0 - not 1

                  'Hi,
                  '
                  'Most hard disks sold in the last few years support SMART
                  (Self-Monitoring,
                  'Analysis, and Reporting Technology) using Microsoft scripting you can
                  use
                  'this to return the hard disk physical serial number, NOT the volume
                  serial
                  'number. This will not change with a reformat, re-install of OS etc,
                  etc. It
                  'will ONLY change if you replace the hard disk.
                  '
                  'To do this, use add a reference for Microsoft Scripting Runtime.
                  '
                  'Add the following to a .bas module (this was assembled from MSDN
                  online
                  'somewhere...)

                  '************** ******START OF BAS MODULE********* ***********

                  Option Explicit

                  Private Type OSVERSIONINFO
                  dwOSVersionInfo Size As Long
                  dwMajorVersion As Long
                  dwMinorVersion As Long
                  dwBuildNumber As Long
                  dwPlatformId As Long
                  szCSDVersion As String * 128
                  End Type
                  Private Declare Function GetVersionEx Lib "kernel32" Alias
                  "GetVersion ExA" (LpVersionInfor mation As OSVERSIONINFO) As Long

                  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

                  Public 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

                  Public Enum IDE_DRIVE_NUMBE R
                  PRIMARY_MASTER
                  PRIMARY_SLAVE
                  SECONDARY_MASTE R
                  SECONDARY_SLAVE
                  End Enum

                  Private Declare Function CreateFile _
                  Lib "kernel32" Alias "CreateFile A" _
                  (ByVal lpFileName As String, ByVal dwDesiredAccess As Long,
                  ByVal dwShareMode As Long, ByVal lpSecurityAttri butes As Long, _
                  ByVal dwCreationDispo sition As Long, _
                  ByVal dwFlagsAndAttri butes 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, _
                  ByVal lpOverlapped As Long) As Long
                  Public Declare Sub CopyMemory _
                  Lib "kernel32" _
                  Alias "RtlMoveMem ory" (Destination As Any, _
                  Source As Any, ByVal Length As Long)

                  Private Const GENERIC_READ = &H80000000
                  Private Const GENERIC_WRITE = &H40000000

                  Private Const FILE_SHARE_READ = &H1
                  Private Const FILE_SHARE_WRIT E = &H2
                  Private Const OPEN_EXISTING = 3
                  Private Const FILE_ATTRIBUTE_ SYSTEM = &H4
                  Private Const CREATE_NEW = 1

                  Private Const INVALID_HANDLE_ VALUE = -1
                  Dim di As DRIVE_INFO

                  Public Const MAX_IDE_DRIVES = 4
                  ' // Max number of drives assuming primary/secondary, master/slave
                  topology
                  Public Const READ_ATTRIBUTE_ BUFFER_SIZE = 512
                  Public Const IDENTIFY_BUFFER _SIZE = 512
                  Public Const READ_THRESHOLD_ BUFFER_SIZE = 512
                  Public Const OUTPUT_DATA_SIZ E = IDENTIFY_BUFFER _SIZE + 16

                  'IOCTL commands
                  Public Const DFP_GET_VERSION = &H74080
                  Public Const DFP_SEND_DRIVE_ COMMAND = &H7C084
                  Public Const DFP_RECEIVE_DRI VE_DATA = &H7C088

                  '---------------------------------------------------------------------
                  ' GETVERSIONOUTPA RAMS contains the data returned from the
                  ' Get Driver Version function.
                  '---------------------------------------------------------------------
                  Public Type GETVERSIONOUTPA RAMS
                  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 GETVERSIONOUTPA RAMS
                  Public Const CAP_IDE_ID_FUNC TION = 1 ' ATA ID command
                  supported
                  Public Const CAP_IDE_ATAPI_I D = 2 ' ATAPI ID command
                  supported
                  Public Const CAP_IDE_EXECUTE _SMART_FUNCTION = 4 ' SMART commannds
                  supported

                  '---------------------------------------------------------------------
                  ' IDE registers
                  '---------------------------------------------------------------------
                  Public Type IDEREGS
                  bFeaturesReg As Byte ' // Used for specifying SMART "commands".
                  bSectorCountReg As Byte ' // IDE sector count register
                  bSectorNumberRe g 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.
                  '---------------------------------------------------------------------
                  Public 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.
                  Public Const IDE_ATAPI_ID = &HA1 ' Returns ID sector for
                  ATAPI.
                  Public Const IDE_ID_FUNCTION = &HEC ' Returns ID sector for
                  ATA.
                  Public Const IDE_EXECUTE_SMA RT_FUNCTION = &HB0 ' Performs SMART cmd.
                  ' Requires valid
                  bFeaturesReg,
                  ' bCylLowReg, and
                  bCylHighReg

                  ' Cylinder register values required when issuing SMART command
                  Public Const SMART_CYL_LOW = &H4F
                  Public Const SMART_CYL_HI = &HC2

                  '---------------------------------------------------------------------
                  ' Status returned from driver
                  '---------------------------------------------------------------------
                  Public 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

                  ' bDriverError values
                  Public Enum DRIVER_ERRORS
                  SMART_NO_ERROR = 0 ' No error
                  SMART_IDE_ERROR = 1 ' Error from IDE controller
                  SMART_INVALID_F LAG = 2 ' Invalid command flag
                  SMART_INVALID_C OMMAND = 3 ' Invalid command byte
                  SMART_INVALID_B UFFER = 4 ' Bad buffer (null, invalid addr..)
                  SMART_INVALID_D RIVE = 5 ' Drive number not valid
                  SMART_INVALID_I OCTL = 6 ' Invalid IOCTL
                  SMART_ERROR_NO_ MEM = 7 ' Could not lock user's buffer
                  SMART_INVALID_R EGISTER = 8 ' Some IDE Register not valid
                  SMART_NOT_SUPPO RTED = 9 ' Invalid cmd flag set
                  SMART_NO_IDE_DE VICE = 10 ' Cmd issued to device not present
                  ' although drive number is valid
                  ' 11-255 reserved
                  End Enum
                  '---------------------------------------------------------------------
                  ' The following struct defines the interesting part of the IDENTIFY
                  ' buffer:
                  '---------------------------------------------------------------------
                  Public Type IDSECTOR
                  wGenConfig As Integer
                  wNumCyls As Integer
                  wReserved As Integer
                  wNumHeads As Integer
                  wBytesPerTrack As Integer
                  wBytesPerSector As Integer
                  wSectorsPerTrac k As Integer
                  wVendorUnique(2 ) As Integer
                  sSerialNumber(1 9) As Byte
                  wBufferType As Integer
                  wBufferSize As Integer
                  wECCSize As Integer
                  sFirmwareRev(7) As Byte
                  sModelNumber(39 ) As Byte
                  wMoreVendorUniq ue As Integer
                  wDoubleWordIO As Integer
                  wCapabilities As Integer
                  wReserved1 As Integer
                  wPIOTiming As Integer
                  wDMATiming As Integer
                  wBS As Integer
                  wNumCurrentCyls As Integer
                  wNumCurrentHead s As Integer
                  wNumCurrentSect orsPerTrack As Integer
                  ulCurrentSector Capacity As Long
                  wMultSectorStuf f As Integer
                  ulTotalAddressa bleSectors As Long
                  wSingleWordDMA As Integer
                  wMultiWordDMA As Integer
                  bReserved(127) As Byte
                  End Type

                  '---------------------------------------------------------------------
                  ' Structure returned by SMART IOCTL for several commands
                  '---------------------------------------------------------------------
                  Public Type SENDCMDOUTPARAM S
                  cBufferSize As Long ' Size of bBuffer in
                  bytes(IDENTIFY_ BUFFER_SIZE in our case)
                  DRIVERSTATUS As DRIVERSTATUS ' Driver status structure.
                  bBuffer() 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"
                  '---------------------------------------------------------------------

                  Public Const SMART_READ_ATTR IBUTE_VALUES = &HD0
                  Public Const SMART_READ_ATTR IBUTE_THRESHOLD S = &HD1
                  Public Const SMART_ENABLE_DI SABLE_ATTRIBUTE _AUTOSAVE = &HD2
                  Public Const SMART_SAVE_ATTR IBUTE_VALUES = &HD3
                  Public Const SMART_EXECUTE_O FFLINE_IMMEDIAT E = &HD4
                  ' Vendor specific commands:
                  Public Const SMART_ENABLE_SM ART_OPERATIONS = &HD8
                  Public Const SMART_DISABLE_S MART_OPERATIONS = &HD9
                  Public Const SMART_RETURN_SM ART_STATUS = &HDA

                  '---------------------------------------------------------------------
                  ' The following structure defines the structure of a Drive Attribute
                  '---------------------------------------------------------------------

                  Public Const NUM_ATTRIBUTE_S TRUCTS = 30

                  Public Type DRIVEATTRIBUTE
                  bAttrID As Byte ' Identifies which attribute
                  wStatusFlags As Integer '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
                  '---------------------------------------------------------------------
                  ' Status Flags Values
                  '---------------------------------------------------------------------
                  Public Enum STATUS_FLAGS
                  PRE_FAILURE_WAR RANTY = &H1
                  ON_LINE_COLLECT ION = &H2
                  PERFORMANCE_ATT RIBUTE = &H4
                  ERROR_RATE_ATTR IBUTE = &H8
                  EVENT_COUNT_ATT RIBUTE = &H10
                  SELF_PRESERVING _ATTRIBUTE = &H20
                  End Enum

                  '---------------------------------------------------------------------
                  ' The following structure defines the structure of a Warranty
                  Threshold
                  ' Obsoleted in ATA4!
                  '---------------------------------------------------------------------

                  Public Type ATTRTHRESHOLD
                  bAttrID As Byte ' Identifies which attribute
                  bWarrantyThresh old As Byte ' Triggering value
                  bReserved(9) As Byte ' ...
                  End Type

                  '---------------------------------------------------------------------
                  ' Valid Attribute IDs
                  '---------------------------------------------------------------------
                  Public Enum ATTRIBUTE_ID
                  ATTR_INVALID = 0
                  ATTR_READ_ERROR _RATE = 1
                  ATTR_THROUGHPUT _PERF = 2
                  ATTR_SPIN_UP_TI ME = 3
                  ATTR_START_STOP _COUNT = 4
                  ATTR_REALLOC_SE CTOR_COUNT = 5
                  ATTR_READ_CHANN EL_MARGIN = 6
                  ATTR_SEEK_ERROR _RATE = 7
                  ATTR_SEEK_TIME_ PERF = 8
                  ATTR_POWER_ON_H RS_COUNT = 9
                  ATTR_SPIN_RETRY _COUNT = 10
                  ATTR_CALIBRATIO N_RETRY_COUNT = 11
                  ATTR_POWER_CYCL E_COUNT = 12
                  ATTR_SOFT_READ_ ERROR_RATE = 13
                  ATTR_G_SENSE_ER ROR_RATE = 191
                  ATTR_POWER_OFF_ RETRACT_CYCLE = 192
                  ATTR_LOAD_UNLOA D_CYCLE_COUNT = 193
                  ATTR_TEMPERATUR E = 194
                  ATTR_REALLOCATI ON_EVENTS_COUNT = 196
                  ATTR_CURRENT_PE NDING_SECTOR_CO UNT = 197
                  ATTR_UNCORRECTA BLE_SECTOR_COUN T = 198
                  ATTR_ULTRADMA_C RC_ERROR_RATE = 199
                  ATTR_WRITE_ERRO R_RATE = 200
                  ATTR_DISK_SHIFT = 220
                  ATTR_G_SENSE_ER ROR_RATEII = 221
                  ATTR_LOADED_HOU RS = 222
                  ATTR_LOAD_UNLOA D_RETRY_COUNT = 223
                  ATTR_LOAD_FRICT ION = 224
                  ATTR_LOAD_UNLOA D_CYCLE_COUNTII = 225
                  ATTR_LOAD_IN_TI ME = 226
                  ATTR_TORQUE_AMP LIFICATION_COUN T = 227
                  ATTR_POWER_OFF_ RETRACT_COUNT = 228
                  ATTR_GMR_HEAD_A MPLITUDE = 230
                  ATTR_TEMPERATUR EII = 231
                  ATTR_READ_ERROR _RETRY_RATE = 250
                  End Enum

                  Dim colAttrNames As Collection
                  '************** *************** *************** *************** *************** *
                  ' Open SMART to allow DeviceIoControl communications. Return SMART
                  handle
                  '************** *************** *************** *************** *************** *
                  Private Function OpenSmart(drv_n um As IDE_DRIVE_NUMBE R) As Long
                  If IsWindowsNT Then
                  OpenSmart = CreateFile("\\. \PhysicalDrive" _
                  & CStr(drv_num), _
                  GENERIC_READ Or GENERIC_WRITE, _
                  FILE_SHARE_READ Or FILE_SHARE_WRIT E, _
                  ByVal 0&, OPEN_EXISTING, 0, 0)
                  Else
                  OpenSmart = CreateFile("\\. \SMARTVSD", _
                  0, 0, ByVal 0&, CREATE_NEW, 0, 0)
                  End If
                  End Function

                  '************** *************** *************** *************** *************** *
                  ' CheckSMARTEnabl e - Check if SMART enable
                  ' FUNCTION: Send a SMART_ENABLE_SM ART_OPERATIONS command to the drive
                  ' bDriveNum = 0-3
                  '************** *************** *************** *************** *************** *

                  Private Function CheckSMARTEnabl e(ByVal hDrive As Long, _
                  DriveNum As IDE_DRIVE_NUMBE R) As Boolean
                  'Set up data structures for Enable SMART Command.
                  Dim SCIP As SENDCMDINPARAMS
                  Dim SCOP As SENDCMDOUTPARAM S
                  Dim lpcbBytesReturn ed As Long
                  With SCIP
                  .cBufferSize = 0
                  With .irDriveRegs
                  .bFeaturesReg = SMART_ENABLE_SM ART_OPERATIONS
                  .bSectorCountRe g = 1
                  .bSectorNumberR eg = 1
                  .bCylLowReg = SMART_CYL_LOW
                  .bCylHighReg = SMART_CYL_HI
                  'Compute the drive number.
                  .bDriveHeadReg = &HA0 ' Or (DriveNum And 1) * 16
                  .bCommandReg = IDE_EXECUTE_SMA RT_FUNCTION
                  End With
                  .bDriveNumber = DriveNum
                  End With
                  CheckSMARTEnabl e = DeviceIoControl (hDrive, _
                  DFP_SEND_DRIVE_ COMMAND, SCIP, _
                  Len(SCIP) - 4, _
                  SCOP, Len(SCOP) - 4, lpcbBytesReturn ed, ByVal
                  0&)
                  End Function

                  '************** *************** *************** *************** *************** *

                  ' DoIdentify
                  ' Function: Send an IDENTIFY command to the drive
                  ' DriveNum = 0-3
                  ' IDCmd = IDE_ID_FUNCTION or IDE_ATAPI_ID
                  '************** *************** *************** *************** *************** *

                  Private Function IdentifyDrive(B yVal hDrive As Long, _
                  ByVal IDCmd As Byte, _
                  ByVal DriveNum As IDE_DRIVE_NUMBE R) As
                  Boolean
                  Dim SCIP As SENDCMDINPARAMS
                  Dim IDSEC As IDSECTOR
                  Dim bArrOut(OUTPUT_ DATA_SIZE - 1) As Byte
                  Dim sMsg As String
                  Dim lpcbBytesReturn ed As Long
                  Dim barrfound(100) As Long
                  Dim i As Long
                  Dim lng As Long
                  ' Set up data structures for IDENTIFY command.
                  With SCIP
                  .cBufferSize = IDENTIFY_BUFFER _SIZE
                  .bDriveNumber = CByte(DriveNum)
                  With .irDriveRegs
                  .bFeaturesReg = 0
                  .bSectorCountRe g = 1
                  .bSectorNumberR eg = 1
                  .bCylLowReg = 0
                  .bCylHighReg = 0
                  ' Compute the drive number.
                  .bDriveHeadReg = &HA0
                  If Not IsWindowsNT Then _
                  .bDriveHeadReg = .bDriveHeadReg _
                  Or (DriveNum And 1) * 16
                  ' The command can either be IDE identify or ATAPI identify.
                  .bCommandReg = CByte(IDCmd)
                  End With
                  End With
                  If DeviceIoControl (hDrive, DFP_RECEIVE_DRI VE_DATA, _
                  SCIP, Len(SCIP) - 4, _
                  bArrOut(0), OUTPUT_DATA_SIZ E, _
                  lpcbBytesReturn ed, ByVal 0&) Then
                  IdentifyDrive = True
                  CopyMemory IDSEC, bArrOut(16), Len(IDSEC)
                  di.Model = SwapStringBytes (StrConv(IDSEC. sModelNumber,
                  vbUnicode))
                  di.FirmWare = SwapStringBytes (StrConv(IDSEC. sFirmwareRev,
                  vbUnicode))
                  di.SerialNumber = SwapStringBytes (StrConv(IDSEC. sSerialNumber,
                  vbUnicode))
                  di.Cilinders = IDSEC.wNumCyls
                  di.Heads = IDSEC.wNumHeads
                  di.SecPerTrack = IDSEC.wSectorsP erTrack
                  End If
                  End Function

                  '************** *************** *************** *************** *************** *
                  ' ReadAttributesC md
                  ' FUNCTION: Send a SMART_READ_ATTR IBUTE_VALUES command to the drive
                  ' bDriveNum = 0-3
                  '************** *************** *************** *************** *************** *

                  Private Function ReadAttributesC md(ByVal hDrive As Long, _
                  DriveNum As IDE_DRIVE_NUMBE R) As
                  Boolean
                  Dim cbBytesReturned As Long
                  Dim SCIP As SENDCMDINPARAMS
                  Dim drv_attr As DRIVEATTRIBUTE
                  Dim bArrOut(OUTPUT_ DATA_SIZE - 1) As Byte
                  Dim sMsg As String
                  Dim i As Long
                  With SCIP
                  ' Set up data structures for Read Attributes SMART Command.
                  .cBufferSize = READ_ATTRIBUTE_ BUFFER_SIZE
                  .bDriveNumber = DriveNum
                  With .irDriveRegs
                  .bFeaturesReg = SMART_READ_ATTR IBUTE_VALUES
                  .bSectorCountRe g = 1
                  .bSectorNumberR eg = 1
                  .bCylLowReg = SMART_CYL_LOW
                  .bCylHighReg = SMART_CYL_HI
                  ' Compute the drive number.
                  .bDriveHeadReg = &HA0
                  If Not IsWindowsNT Then _
                  .bDriveHeadReg = .bDriveHeadReg Or _
                  (DriveNum And 1) * 16
                  .bCommandReg = IDE_EXECUTE_SMA RT_FUNCTION
                  End With
                  End With
                  ReadAttributesC md = DeviceIoControl (hDrive, DFP_RECEIVE_DRI VE_DATA,
                  _
                  SCIP, Len(SCIP) - 4, _
                  bArrOut(0), _
                  OUTPUT_DATA_SIZ E, _
                  cbBytesReturned , ByVal 0&)
                  On Error Resume Next
                  For i = 0 To NUM_ATTRIBUTE_S TRUCTS - 1
                  If bArrOut(18 + i * 12) > 0 Then
                  di.Attributes(d i.NumAttributes ).AttrID = bArrOut(18 + i * 12)
                  di.Attributes(d i.NumAttributes ).AttrName _
                  = "Unknown value (" & bArrOut(18 + i * 12) &
                  ")"
                  ' di.Attributes(d i.NumAttributes ).AttrName = colAttrNames
                  (CStr(bArrOut(1 8 + i * 12)))
                  di.NumAttribute s = di.NumAttribute s + 1
                  ReDim Preserve di.Attributes(d i.NumAttributes )
                  CopyMemory di.Attributes(d i.NumAttributes ).StatusFlags, _
                  bArrOut(19 + i * 12), 2
                  di.Attributes(d i.NumAttributes ).AttrValue = bArrOut(21 + i *
                  12)
                  di.Attributes(d i.NumAttributes ).WorstValue = bArrOut(22 + i *
                  12)
                  End If
                  Next i
                  End Function

                  Private Function ReadThresholdsC md(ByVal hDrive As Long, _
                  DriveNum As IDE_DRIVE_NUMBE R) As Boolean
                  Dim cbBytesReturned As Long
                  Dim SCIP As SENDCMDINPARAMS
                  Dim IDSEC As IDSECTOR
                  Dim bArrOut(OUTPUT_ DATA_SIZE - 1) As Byte
                  Dim sMsg As String
                  Dim thr_attr As ATTRTHRESHOLD
                  Dim i As Long, j As Long
                  With SCIP
                  ' Set up data structures for Read Attributes SMART Command.
                  .cBufferSize = READ_THRESHOLD_ BUFFER_SIZE
                  .bDriveNumber = DriveNum
                  With .irDriveRegs
                  .bFeaturesReg = SMART_READ_ATTR IBUTE_THRESHOLD S
                  .bSectorCountRe g = 1
                  .bSectorNumberR eg = 1
                  .bCylLowReg = SMART_CYL_LOW
                  .bCylHighReg = SMART_CYL_HI
                  ' Compute the drive number.
                  .bDriveHeadReg = &HA0
                  If Not IsWindowsNT Then _
                  .bDriveHeadReg = .bDriveHeadReg Or _
                  (DriveNum And 1) * 16
                  .bCommandReg = IDE_EXECUTE_SMA RT_FUNCTION
                  End With
                  End With
                  ReadThresholdsC md = DeviceIoControl (hDrive, _
                  DFP_RECEIVE_DRI VE_DATA, SCIP, _
                  Len(SCIP) - 4, bArrOut(0), _
                  OUTPUT_DATA_SIZ E, cbBytesReturned , ByVal 0&)
                  For i = 0 To NUM_ATTRIBUTE_S TRUCTS - 1
                  CopyMemory thr_attr, bArrOut(18 + i * Len(thr_attr)),
                  Len(thr_attr)
                  If thr_attr.bAttrI D > 0 Then
                  For j = 0 To UBound(di.Attri butes)
                  If thr_attr.bAttrI D = di.Attributes(j ).AttrID Then
                  di.Attributes(j ).ThresholdValu e =
                  thr_attr.bWarra ntyThreshold
                  Exit For
                  End If
                  Next j
                  End If
                  Next i
                  End Function

                  Private Function GetSmartVersion (ByVal hDrive As Long, VersionParams
                  As GETVERSIONOUTPA RAMS) As Boolean
                  Dim cbBytesReturned As Long
                  GetSmartVersion = DeviceIoControl (hDrive, _
                  DFP_GET_VERSION , ByVal 0&, 0, _
                  VersionParams, _
                  Len(VersionPara ms), _
                  cbBytesReturned , ByVal 0&)
                  End Function

                  Public Function GetDriveInfo(Dr iveNum As IDE_DRIVE_NUMBE R) As
                  DRIVE_INFO
                  Dim hDrive As Long
                  Dim VerParam As GETVERSIONOUTPA RAMS
                  Dim cb As Long

                  di.bDriveType = 0
                  di.NumAttribute s = 0

                  ReDim di.Attributes(0 )

                  hDrive = OpenSmart(Drive Num)
                  If hDrive = INVALID_HANDLE_ VALUE Then Exit Function
                  If Not GetSmartVersion (hDrive, VerParam) Then Exit Function
                  If Not IsBitSet(VerPar am.bIDEDeviceMa p, DriveNum) Then Exit
                  Function
                  di.bDriveType = 1 + Abs(IsBitSet(Ve rParam.bIDEDevi ceMap, DriveNum
                  + 4))
                  If Not CheckSMARTEnabl e(hDrive, DriveNum) Then Exit Function
                  FillAttrNameCol lection
                  Call IdentifyDrive(h Drive, IDE_ID_FUNCTION , DriveNum)
                  Call ReadAttributesC md(hDrive, DriveNum)
                  Call ReadThresholdsC md(hDrive, DriveNum)
                  GetDriveInfo = di
                  CloseHandle hDrive
                  Set colAttrNames = Nothing
                  End Function

                  Private Function IsWindowsNT() As Boolean
                  Dim verinfo As OSVERSIONINFO
                  verinfo.dwOSVer sionInfoSize = Len(verinfo)
                  If (GetVersionEx(v erinfo)) = 0 Then Exit Function
                  If verinfo.dwPlatf ormId = 2 Then IsWindowsNT = True
                  End Function

                  Private Function IsBitSet(iBitSt ring As Byte, ByVal lBitNo As Integer)
                  As Boolean
                  If lBitNo = 7 Then
                  IsBitSet = iBitString < 0
                  Else
                  IsBitSet = iBitString And (2 ^ lBitNo)
                  End If
                  End Function

                  Private Function SwapStringBytes (ByVal sIn As String) As String
                  Dim sTemp As String
                  Dim i As Integer
                  sTemp = Space(Len(sIn))
                  For i = 1 To Len(sIn) - 1 Step 2
                  Mid(sTemp, i, 1) = Mid(sIn, i + 1, 1)
                  Mid(sTemp, i + 1, 1) = Mid(sIn, i, 1)
                  Next i
                  SwapStringBytes = sTemp
                  End Function

                  Public Sub FillAttrNameCol lection()
                  Set colAttrNames = New Collection
                  With colAttrNames
                  .Add "ATTR_INVAL ID", "0"
                  .Add "READ_ERROR_RAT E", "1"
                  .Add "THROUGHPUT_PER F", "2"
                  .Add "SPIN_UP_TI ME", "3"
                  .Add "START_STOP_COU NT", "4"
                  .Add "REALLOC_SECTOR _COUNT", "5"
                  .Add "READ_CHANNEL_M ARGIN", "6"
                  .Add "SEEK_ERROR_RAT E", "7"
                  .Add "SEEK_TIME_PERF ", "8"
                  .Add "POWER_ON_HRS_C OUNT", "9"
                  .Add "SPIN_RETRY_COU NT", "10"
                  .Add "CALIBRATION_RE TRY_COUNT", "11"
                  .Add "POWER_CYCLE_CO UNT", "12"
                  .Add "SOFT_READ_ERRO R_RATE", "13"
                  .Add "G_SENSE_ERROR_ RATE", "191"
                  .Add "POWER_OFF_RETR ACT_CYCLE", "192"
                  .Add "LOAD_UNLOAD_CY CLE_COUNT", "193"
                  .Add "TEMPERATUR E", "194"
                  .Add "REALLOCATION_E VENTS_COUNT", "196"
                  .Add "CURRENT_PENDIN G_SECTOR_COUNT" , "197"
                  .Add "UNCORRECTABLE_ SECTOR_COUNT", "198"
                  .Add "ULTRADMA_CRC_E RROR_RATE", "199"
                  .Add "WRITE_ERROR_RA TE", "200"
                  .Add "DISK_SHIFT ", "220"
                  .Add "G_SENSE_ERROR_ RATEII", "221"
                  .Add "LOADED_HOU RS", "222"
                  .Add "LOAD_UNLOAD_RE TRY_COUNT", "223"
                  .Add "LOAD_FRICTION" , "224"
                  .Add "LOAD_UNLOAD_CY CLE_COUNTII", "225"
                  .Add "LOAD_IN_TI ME", "226"
                  .Add "TORQUE_AMPLIFI CATION_COUNT", "227"
                  .Add "POWER_OFF_RETR ACT_COUNT", "228"
                  .Add "GMR_HEAD_AMPLI TUDE", "230"
                  .Add "TEMPERATUREII" , "231"
                  .Add "READ_ERROR_RET RY_RATE", "250"
                  End With
                  End Sub


                  '************** ******END OF BAS MODULE********* ***********

                  'In the example assume a label called label2 on a form, could easily
                  be a
                  'string etc etc....

                  'Add the following to your code:

                  ' Dim drv_info As DRIVE_INFO
                  '
                  ' drv_info = GetDriveInfo(0)
                  ' With drv_info
                  ' If .bDriveType = 0 Then Label2.Caption = "[Not present]"
                  ' If .bDriveType = 2 Then Label2.Caption = "[ATAPI drive - info
                  not available]"
                  ' If .bDriveType = 1 Then
                  ' Label2.Caption = Trim(.SerialNum ber)
                  ' End If
                  ' End With
                  '
                  'Label2 will display the actual physical serial number of the drive,
                  NOT the
                  'volume number.



                  Comment

                  • mayayana

                    #10
                    Re: read BIOS or HDD or Machine Serial Number

                    [color=blue]
                    > - sadly it is not supposed to work for NT, XP etc[/color]

                    Yes, I thought that memory range was off-limits in NT.
                    I suppose it's a good idea to wear a helmet when bike-riding
                    (or a WMI class when accessing system info.) but it does take
                    some of the fun out of it.
                    [color=blue]
                    > - also it is really MoveMemory in Drag (example below)
                    >
                    > However looking for it got me here:
                    >
                    > http://www.xbeat.net/vbspeed/i_VBVM6...l#Introduction
                    >[/color]

                    I hadn't thought of it being the same idea as MoveMemory;
                    that makes sense. I'd also never thought to research it, so thanks
                    to you, too! I downloaded that page. It's the only reference to GetMem1
                    that I've ever seen aside from the code snippet I had.



                    Comment

                    • J French

                      #11
                      Re: read BIOS or HDD or Machine Serial Number

                      On Sun, 10 Aug 2003 13:52:58 GMT, "mayayana"
                      <mayayana4@mind spring.com> wrote:

                      <snip>[color=blue]
                      > I hadn't thought of it being the same idea as MoveMemory;
                      >that makes sense. I'd also never thought to research it, so thanks
                      >to you, too! I downloaded that page. It's the only reference to GetMem1
                      >that I've ever seen aside from the code snippet I had.[/color]

                      For quite some time I have been trying to find the 'undocumented' VB
                      functions/subs

                      - that page looks as if it might have some more stuff in it
                      - but right now I've filed it for 'when sober'

                      Thanks - that was a good pointer


                      Comment

                      • J French

                        #12
                        Re: read BIOS or HDD or Machine Serial Number

                        On Sun, 10 Aug 2003 16:28:47 +0200, "R.Wieser"
                        <rwieser-killthis-@xs4all.nl> wrote:

                        <snip>[color=blue]
                        >I've stored the (integral) message in my snippets-directory, to be found if
                        >I ever need it :-)
                        >
                        >Thanks for sharing it.
                        >
                        >Regards,
                        > Rudy Wieser[/color]

                        As did I, be careful using it ....

                        Comment

                        • R.Wieser

                          #13
                          Re: read BIOS or HDD or Machine Serial Number

                          J French <erewhon@nowher e.com> schreef in berichtnieuws
                          3f3671c6.183766 54@news.btclick .com...

                          Hello J,
                          [color=blue]
                          > On Sun, 10 Aug 2003 16:28:47 +0200, "R.Wieser"
                          > <rwieser-killthis-@xs4all.nl> wrote:
                          >
                          > <snip>[color=green]
                          > >I've stored the (integral) message in my snippets-directory, to be found[/color][/color]
                          if[color=blue][color=green]
                          > >I ever need it :-)
                          > >
                          > >Thanks for sharing it.
                          > >
                          > >Regards,
                          > > Rudy Wieser[/color]
                          >
                          > As did I, be careful using it ....[/color]

                          I will. I've stored the whole message, including the warning therein.
                          Whenever I will read the message I will read your warning too :-)

                          Regards,
                          Rudy Wieser



                          Comment

                          • André Joubert

                            #14
                            Re: read BIOS or HDD or Machine Serial Number

                            By the way I use SmartVSD.VXD on Windows XP without any problems, but for
                            some reason on Windows 98 SE I always get -1 (Invalid handle).
                            Any idea why?

                            André

                            P.S. Oops I think I previously sent this to the wrong address. Sorry for
                            that if you recognize yourself.


                            "J French" <erewhon@nowher e.com> wrote in message
                            news:3f34acc1.1 688691@news.btc lick.com...[color=blue]
                            >
                            > Totally agreed, but that sounds like the API Samuel Hon was thinking
                            > about
                            >
                            > The only other method I've heard of, is for SMART complient drives
                            >
                            > Private Function OpenSmart(drv_n um As IDE_DRIVE_NUMBE R) As Long
                            > If IsWindowsNT Then
                            > OpenSmart = CreateFile("\\. \PhysicalDrive" _
                            > & CStr(drv_num), _
                            > GENERIC_READ Or GENERIC_WRITE, _
                            > FILE_SHARE_READ Or FILE_SHARE_WRIT E, _
                            > ByVal 0&, OPEN_EXISTING, 0, 0)
                            > Else
                            > OpenSmart = CreateFile("\\. \SMARTVSD", _
                            > 0, 0, ByVal 0&, CREATE_NEW, 0, 0)
                            > End If
                            > End Function
                            >
                            > And then do some hefty DeviceIOControl[/color]


                            Comment

                            • J French

                              #15
                              Re: read BIOS or HDD or Machine Serial Number

                              On Sun, 10 Aug 2003 15:26:23 -0400, "André Joubert"
                              <jaji92@sympati co.ca> wrote:
                              [color=blue]
                              >By the way I use SmartVSD.VXD on Windows XP without any problems, but for
                              >some reason on Windows 98 SE I always get -1 (Invalid handle).
                              >Any idea why?
                              >
                              >André
                              >
                              >P.S. Oops I think I previously sent this to the wrong address. Sorry for
                              >that if you recognize yourself.[/color]

                              You definitely need a different .VXD for 95/98
                              - that may be the problem

                              - the other thing is the CreateFile

                              Private Function OpenSmart(drv_n um As IDE_DRIVE_NUMBE R) As Long
                              If IsWindowsNT Then
                              OpenSmart = CreateFile("\\. \PhysicalDrive" _
                              & CStr(drv_num), _
                              GENERIC_READ Or GENERIC_WRITE, _
                              FILE_SHARE_READ Or FILE_SHARE_WRIT E, _
                              ByVal 0&, OPEN_EXISTING, 0, 0)
                              Else
                              OpenSmart = CreateFile("\\. \SMARTVSD", _
                              0, 0, ByVal 0&, CREATE_NEW, 0, 0)
                              End If
                              End Function

                              It is also possible that your 95/98 drive does not support SMART
                              - one of my drives certainly does not
                              - oddly enough it is the older one ....


                              Comment

                              Working...