Consulting

Results 1 to 8 of 8

Thread: Solved: Extract unique Windows identifier using VB6?

  1. #1
    VBAX Regular andrew93's Avatar
    Joined
    Aug 2005
    Location
    Auckland, New Zealand
    Posts
    68
    Location

    Solved: Extract unique Windows identifier using VB6?

    Hi everyone.

    I'm trying to extract a unique identifier from my PC using VB6 (OS = Win 98). It was suggested I extract the 'MAC' address of the network card using code from (apologies for linking to another site but searches on this site turned up nothing) here.

    I'm having a problem with the code in that the first line (i.e. Option Explicit Public) is highlighted in red and the code will not run. I have copied the code in full at the foot of my post (apologies if this is not good netiquette). I created a new project, added a module and then pasted the code. I can't get any further than that (even if I create a form and button to display the value) because of the first line. If I try to run the code, I get an error saying 'compile error, expected : end of statement'. I'm new to VB and am not sure how to correct this error. Do you have any suggestions as to how I can fix this error?

    Or if you have an alternative suggestion for extracting a unique identifier for a Windows PC, I'd be happy to hear your opinion.

    Thanks in Advance
    Andrew

    FYI, the code :

    Option Explicit Public
    
    Const NCBASTAT As Long = H33
    Public Const NCBNAMSZ As Long = 16
    Public Const HEAP_ZERO_MEMORY As Long = H8
    Public Const HEAP_GENERATE_EXCEPTIONS As Long = H4
    Public Const NCBRESET As Long = H32
    
    Public Type NET_CONTROL_BLOCK 'NCB
       ncb_command As Byte
       ncb_retcode As Byte
       ncb_lsn As Byte
       ncb_num As Byte
       ncb_buffer As Long
       ncb_length As Integer
       ncb_callname As String * NCBNAMSZ
       ncb_name As String * NCBNAMSZ
       ncb_rto As Byte
       ncb_sto As Byte
       ncb_post As Long
       ncb_lana_num As Byte
       ncb_cmd_cplt As Byte
       ncb_reserve(9) As Byte ' Reserved, must be 0
       ncb_event As Long
    End Type
    
    Public Type ADAPTER_STATUS
       adapter_address(5) As Byte
       rev_major As Byte
       reserved0 As Byte
       adapter_type As Byte
       rev_minor As Byte
       duration As Integer
       frmr_recv As Integer
       frmr_xmit As Integer
       iframe_recv_err As Integer
       xmit_aborts As Integer
       xmit_success As Long
       recv_success As Long
       iframe_xmit_err As Integer
       recv_buff_unavail As Integer
       t1_timeouts As Integer
       ti_timeouts As Integer
       Reserved1 As Long
       free_ncbs As Integer
       max_cfg_ncbs As Integer
       max_ncbs As Integer
       xmit_buf_unavail As Integer
       max_dgram_size As Integer
       pending_sess As Integer
       max_cfg_sess As Integer
       max_sess As Integer
       max_sess_pkt_size As Integer
       name_count As Integer
    End Type
      
    Public Type NAME_BUFFER
    	name As String * NCBNAMSZ
    	name_num As Integer
    	name_flags As Integer
    End Type
    
    Public Type ASTAT
       adapt As ADAPTER_STATUS
       NameBuff(30) As NAME_BUFFER
    End Type
    
    Public Declare Function Netbios Lib "netapi32.dll" (pncb As NET_CONTROL_BLOCK) As Byte
    	
    Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, ByVal hpvSource As Long, ByVal cbCopy As Long)
    	
    Public Declare Function GetProcessHeap Lib "kernel32" () As Long
    Public Declare Function HeapAlloc Lib "kernel32" (ByVal hHeap As Long, ByVal dwFlags As Long, ByVal dwBytes As Long) As Long
    	
    Public Declare Function HeapFree Lib "kernel32" (ByVal hHeap As Long, ByVal dwFlags As Long, lpMem As Any) As Long
    
    Public Function GetMACAddress() As String 'retrieve the MAC Address for the network controller
      'installed, returning a formatted string
      
       Dim tmp As String
       Dim pASTAT As Long
       Dim NCB As NET_CONTROL_BLOCK
       Dim AST As ASTAT 'The IBM NetBIOS 3.0 specifications defines four basic
      'NetBIOS environments under the NCBRESET command. Win32
      'follows the OS/2 Dynamic Link Routine (DLR) environment.
      'This means that the first NCB issued by an application
      'must be a NCBRESET, with the exception of NCBENUM.
      'The Windows NT implementation differs from the IBM
      'NetBIOS 3.0 specifications in the NCB_CALLNAME field.
       NCB.ncb_command = NCBRESET
       Call Netbios(NCB)
      
      'To get the Media Access Control (MAC) address for an
      'ethernet adapter programmatically, use the Netbios()
      'NCBASTAT command and provide a "*" as the name in the
      'NCB.ncb_CallName field (in a 16-chr string).
       NCB.ncb_callname = "* "
       NCB.ncb_command = NCBASTAT
      
      'For machines with multiple network adapters you need to
      'enumerate the LANA numbers and perform the NCBASTAT
      'command on each. Even when you have a single network
      'adapter, it is a good idea to enumerate valid LANA numbers
      'first and perform the NCBASTAT on one of the valid LANA
      'numbers. It is considered bad programming to hardcode the
      'LANA number to 0 (see the comments section below).
       NCB.ncb_lana_num = 0
       NCB.ncb_length = Len(AST)
      
       pASTAT = HeapAlloc(GetProcessHeap(), HEAP_GENERATE_EXCEPTIONS _
    			Or HEAP_ZERO_MEMORY, NCB.ncb_length)
    		   
       If pASTAT = 0 Then
    	  Debug.Print "memory allocation failed!"
    	  Exit Function
       End If
      
       NCB.ncb_buffer = pASTAT
       Call Netbios(NCB)
      
       CopyMemory AST, NCB.ncb_buffer, Len(AST)
      
    tmp = Format$(Hex(AST.adapt.adapter_address(0)), "00") & " " & Format$(Hex(AST.adapt.adapter_address(1)), "00") & " " & Format$(Hex(AST.adapt.adapter_address(2)), "00") & " " & Format$(Hex(AST.adapt.adapter_address(3)), "00") & " " & Format$(Hex(AST.adapt.adapter_address(4)), "00") & " " & Format$(Hex(AST.adapt.adapter_address(5)), "00")
    		  
       HeapFree GetProcessHeap(), 0, pASTAT
      
       GetMACAddress = tmp
    
    End Function

  2. #2
    Moderator VBAX Master Tommy's Avatar
    Joined
    May 2004
    Location
    Houston, TX
    Posts
    1,184
    Location
    Hi andrew93,

    Welcome to VBAX!

    The only things I found wrong were, the word Public should have been on the next line with "Const NCBASTAT As Long = &H33" and the ampersign in front of the hex values.


    [VBA]
    Option Explicit
    Public Const NCBASTAT As Long = &H33 '<- added &
    Public Const NCBNAMSZ As Long = 16
    Public Const HEAP_ZERO_MEMORY As Long = &H8 '<- added &
    Public Const HEAP_GENERATE_EXCEPTIONS As Long = &H4 '<- added &
    Public Const NCBRESET As Long = &H32 '<- added &
    Public Type NET_CONTROL_BLOCK 'NCB
    ncb_command As Byte
    ncb_retcode As Byte
    ncb_lsn As Byte
    ncb_num As Byte
    ncb_buffer As Long
    ncb_length As Integer
    ncb_callname As String * NCBNAMSZ
    ncb_name As String * NCBNAMSZ
    ncb_rto As Byte
    ncb_sto As Byte
    ncb_post As Long
    ncb_lana_num As Byte
    ncb_cmd_cplt As Byte
    ncb_reserve(9) As Byte ' Reserved, must be 0
    ncb_event As Long
    End Type
    Public Type ADAPTER_STATUS
    adapter_address(5) As Byte
    rev_major As Byte
    reserved0 As Byte
    adapter_type As Byte
    rev_minor As Byte
    duration As Integer
    frmr_recv As Integer
    frmr_xmit As Integer
    iframe_recv_err As Integer
    xmit_aborts As Integer
    xmit_success As Long
    recv_success As Long
    iframe_xmit_err As Integer
    recv_buff_unavail As Integer
    t1_timeouts As Integer
    ti_timeouts As Integer
    Reserved1 As Long
    free_ncbs As Integer
    max_cfg_ncbs As Integer
    max_ncbs As Integer
    xmit_buf_unavail As Integer
    max_dgram_size As Integer
    pending_sess As Integer
    max_cfg_sess As Integer
    max_sess As Integer
    max_sess_pkt_size As Integer
    name_count As Integer
    End Type

    Public Type NAME_BUFFER
    name As String * NCBNAMSZ
    name_num As Integer
    name_flags As Integer
    End Type
    Public Type ASTAT
    adapt As ADAPTER_STATUS
    NameBuff(30) As NAME_BUFFER
    End Type
    Public Declare Function Netbios Lib "netapi32.dll" (pncb As NET_CONTROL_BLOCK) As Byte

    Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, _
    ByVal hpvSource As Long, ByVal cbCopy As Long)

    Public Declare Function GetProcessHeap Lib "kernel32" () As Long
    Public Declare Function HeapAlloc Lib "kernel32" (ByVal hHeap As Long, _
    ByVal dwFlags As Long, ByVal dwBytes As Long) As Long

    Public Declare Function HeapFree Lib "kernel32" _
    (ByVal hHeap As Long, ByVal dwFlags As Long, lpMem As Any) As Long
    Public Function GetMACAddress() As String 'retrieve the MAC Address for the network controller
    'installed, returning a formatted string

    Dim tmp As String
    Dim pASTAT As Long
    Dim NCB As NET_CONTROL_BLOCK
    Dim AST As ASTAT 'The IBM NetBIOS 3.0 specifications defines four basic
    'NetBIOS environments under the NCBRESET command. Win32
    'follows the OS/2 Dynamic Link Routine (DLR) environment.
    'This means that the first NCB issued by an application
    'must be a NCBRESET, with the exception of NCBENUM.
    'The Windows NT implementation differs from the IBM
    'NetBIOS 3.0 specifications in the NCB_CALLNAME field.
    NCB.ncb_command = NCBRESET
    Call Netbios(NCB)

    'To get the Media Access Control (MAC) address for an
    'ethernet adapter programmatically, use the Netbios()
    'NCBASTAT command and provide a "*" as the name in the
    'NCB.ncb_CallName field (in a 16-chr string).
    NCB.ncb_callname = "* "
    NCB.ncb_command = NCBASTAT

    'For machines with multiple network adapters you need to
    'enumerate the LANA numbers and perform the NCBASTAT
    'command on each. Even when you have a single network
    'adapter, it is a good idea to enumerate valid LANA numbers
    'first and perform the NCBASTAT on one of the valid LANA
    'numbers. It is considered bad programming to hardcode the
    'LANA number to 0 (see the comments section below).
    NCB.ncb_lana_num = 0
    NCB.ncb_length = Len(AST)

    pASTAT = HeapAlloc(GetProcessHeap(), HEAP_GENERATE_EXCEPTIONS _
    Or HEAP_ZERO_MEMORY, NCB.ncb_length)

    If pASTAT = 0 Then
    Debug.Print "memory allocation failed!"
    Exit Function
    End If

    NCB.ncb_buffer = pASTAT
    Call Netbios(NCB)

    CopyMemory AST, NCB.ncb_buffer, Len(AST)

    tmp = Format$(Hex(AST.adapt.adapter_address(0)), "00") & " " _
    & Format$(Hex(AST.adapt.adapter_address(1)), "00") & " " & _
    Format$(Hex(AST.adapt.adapter_address(2)), "00") & " " & _
    Format$(Hex(AST.adapt.adapter_address(3)), "00") & " " & _
    Format$(Hex(AST.adapt.adapter_address(4)), "00") & " " & _
    Format$(Hex(AST.adapt.adapter_address(5)), "00")

    HeapFree GetProcessHeap(), 0, pASTAT

    GetMACAddress = tmp
    End Function

    [/VBA]
    HTH

  3. #3
    Administrator
    VP-Knowledge Base
    VBAX Guru MOS MASTER's Avatar
    Joined
    Apr 2005
    Location
    Breda, The Netherlands
    Posts
    3,281
    Location
    Hi and welcome to VBAX!

    Depending on your OS version this will work as well:[vba]
    Sub GetPhysAddress()
    Dim oWMIService As Object
    Dim oColAdapters As Object
    Dim oObjAdapter As Object

    Set oWMIService = GetObject("winmgmts:" & "!\\.\root\cimv2")
    Set oColAdapters = oWMIService.ExecQuery _
    ("Select * from Win32_NetworkAdapterConfiguration Where IPEnabled = True")

    For Each oObjAdapter In oColAdapters
    MsgBox "Adapter Physical address: " & oObjAdapter.MACAddress
    Next

    Set oObjAdapter = Nothing
    Set oColAdapters = Nothing
    Set oWMIService = Nothing
    End Sub
    [/vba]

    HTH,
    _________
    Groetjes,

    Joost Verdaasdonk
    M.O.S. Master

    Mark your thread solved, when it has been, by hitting the Thread Tools dropdown at the top of the thread.
    (I don't answer questions asked through E-mail or PM's)

  4. #4
    VBAX Regular andrew93's Avatar
    Joined
    Aug 2005
    Location
    Auckland, New Zealand
    Posts
    68
    Location
    Hi

    Thanks for the replies.

    I made the amendments per Tommy's post and it works perfectly thanks.

    Thanks for the much simpler code MOS MASTER but I tried it and it failed on the Win98 PC - I will have to see if it works on the Win XP PC. In particular it failed on this line : "Set oWMIService = GetObject("winmgmts:" & "!\\.\root\cimv2")". There was a runtime error 432 (file or class name not found). But I will give it a go on the other PC and see what happens.

    Thanks again to you both for your speedy and knowledgable replies!

    Andrew

  5. #5
    Administrator
    VP-Knowledge Base
    VBAX Guru MOS MASTER's Avatar
    Joined
    Apr 2005
    Location
    Breda, The Netherlands
    Posts
    3,281
    Location
    Hi Andrew,

    You're welcome.

    Indeed '98 was not the kind of OS I had in mind with this code NT to start with at least.

    Buth all should run fine on XP...at least it does over here. (Allthough I only use Pro version's of all my OS's)
    _________
    Groetjes,

    Joost Verdaasdonk
    M.O.S. Master

    Mark your thread solved, when it has been, by hitting the Thread Tools dropdown at the top of the thread.
    (I don't answer questions asked through E-mail or PM's)

  6. #6
    Moderator VBAX Master Tommy's Avatar
    Joined
    May 2004
    Location
    Houston, TX
    Posts
    1,184
    Location
    Just for more input

    It works on XP home with SP2. The only difference is the formating, ":" instead of " ".
    WMI Monikers hmmm seen 'em never used 'em looks like I need to look at 'em an start usin' 'em

    MOOSE POWER!

  7. #7
    Administrator
    VP-Knowledge Base
    VBAX Guru MOS MASTER's Avatar
    Joined
    Apr 2005
    Location
    Breda, The Netherlands
    Posts
    3,281
    Location
    Hi Buddy,

    True different versions can have different identifiers!

    But believe me WMI (Windows Management Instrumentation) is extremly powerfull.

    So it's word investigating!
    _________
    Groetjes,

    Joost Verdaasdonk
    M.O.S. Master

    Mark your thread solved, when it has been, by hitting the Thread Tools dropdown at the top of the thread.
    (I don't answer questions asked through E-mail or PM's)

  8. #8
    VBAX Newbie
    Joined
    Mar 2006
    Posts
    1
    Location

    Vba to view MAC address

    Ive read your info regards the MAC code and have a querry - I have tried the long vba version and it seems to work fine on win98 to XP if there is a Network card installed ( not part of the motherboard ) but if there is not a card installed and you rely on the motherboard to get the MAC address then the vba code does not work and the short version does - my question is - is there a way to convert the short version to display the MAC address if the long version does not work and for both methods to view in cells not display boxes? this would help solve a problem I have had for a while.

Posting Permissions

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