Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29267 Discussions

HDD serial number not volume number

portoon
Beginner
1,122 Views

Hi all ?

I am looking for a code (FORTRAN will be fine) that can extract the HDD serial number (manufacture's number).
Is there any one who knew well about this?

Thanks.

0 Kudos
2 Replies
Jugoslav_Dujic
Valued Contributor II
1,122 Views
Quoting - portoon

Hi all ?

I am looking for a code (FORTRAN will be fine) that can extract the HDD serial number (manufacture's number).
Is there any one who knew well about this?


Accidentaly, I've read a recent comp.os.ms-windows.programmer.win32 thread about the subject yesterday.

Basically, you need to call DeviceIOControl API with IOCTL_STORAGE_QUERY_PROPERTY and read the string from STORAGE_DEVICE_DESCRIPTOR.SerialNumberOffset. Here's a sample, in C; (googling for keywords above will give you a variety of similar codes, of varying degree of complexity):

http://www.askmehelpdesk.com/advice/t-6466.html

However, there seems to be a catch, because not all disk vendors store that serial number, and in that case you must go through hoops to get the information.

See the freeware diskid32 application, and its source code .
0 Kudos
yamajun2
Beginner
1,122 Views
Quoting - portoon

Hi all ?

I am looking for a code (FORTRAN will be fine) that can extract the HDD serial number (manufacture's number).
Is there any one who knew well about this?

Thanks.


Hi,
Here is a program to obtain HDD serial number.
The site I referenced is here.
http://www.usefullcode.net/2007/02/hdd.html
With Vista, you have to run the executable file as admin (right click exe-file, chose run as admin).
I hope this will help you.

Yamajun

[cpp]PROGRAM disk
USE kernel32
IMPLICIT NONE
INTEGER(HANDLE) :: hDevice         
INTEGER(LPDWORD):: lpBytesReturned = 0
INTEGER(BOOL)   :: iret
!
TYPE :: t_IDENTIFY_DEVICE_OUTDATA
 SEQUENCE
 TYPE (t_SENDCMDOUTPARAMS):: snd_cmd_out
 CHARACTER(511):: DriverStatus ! typedefs  DRIVERSTATUS 
END TYPE
!
TYPE (t_SENDCMDINPARAMS) :: snd_cmd
TYPE (t_IDENTIFY_DEVICE_OUTDATA) :: out_data
!
INTEGER, PARAMETER :: DFP_RECEIVE_DRIVE_DATA = Z'0007c088'
INTEGER, PARAMETER :: ATAPI_IDENTIFY_DEVICE  = Z'EC'
!
INTEGER :: i, ndrive
CHARACTER(19) :: fn
!
ndrive = 0 ! First drive 0, Second Drive 1 ...
WRITE(fn, '(a, i1, a)') '.PhysicalDrive', ndrive, CHAR(0) !C string
!
hDevice = CreateFile(fn, IOR(GENERIC_READ, GENERIC_WRITE),IOR(FILE_SHARE_READ, FILE_SHARE_WRITE), &
                      NULL, OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, NULL)
IF (hDevice == INVALID_HANDLE_VALUE) THEN 
 PRINT *, GetLastError()
 iret = CloseHandle(hDevice)
 STOP 'error CreateFile'
END IF 
!
snd_cmd%irDriveRegs%bCommandReg = Z'EC' !ATAPI_IDENTIFY_DEVICE
snd_cmd%irDriveRegs%bDriveHeadReg = IOR(Z'A0', ISHFT(IAND(ndrive, 1), 4)) 
snd_cmd%cBufferSize = sizeof(out_data) ! 511?
snd_cmd%bDriveNumber = ndrive
!
iret = DeviceIoControl(hDevice, DFP_RECEIVE_DRIVE_DATA, LOC(snd_cmd), sizeof(snd_cmd), LOC(out_data), sizeof(out_data), LOC(lpBytesReturned), NULL)
!
IF (iret == 0) THEN 
 PRINT *, GetLastError()
 iret = CloseHandle(hDevice)
 STOP 'error DeviceIoControl'
END IF 
!
! the order of "out_data%DriverStatus" is 2byte little endian
!
! http://www.usefullcode.net/2007/02/hdd.html
!
WRITE(*, '(a)', ADVANCE='NO') 'Serial Number = '
DO i = 21, 40, 2 ! ?
 WRITE(*, '(2a1)', ADVANCE='NO') out_data%DriverStatus(i:i), out_data%DriverStatus(i - 1:i - 1)
END DO
WRITE(*, *)
WRITE(*, '(a)', ADVANCE='NO') 'Model         = '
DO i = 55, 93, 2 ! ?
 WRITE(*, '(2a1)', ADVANCE='NO') out_data%DriverStatus(i:i), out_data%DriverStatus(i - 1:i - 1)
END DO
WRITE(*, *)
!
PAUSE 
!
STOP
END PROGRAM disk[/cpp]
0 Kudos
Reply