How can I generate GUIDs in Excel?

VbaExcelGuid

Vba Problem Overview


I have an excel file with one order on each row, and I want each order to have a unique identifier, so there will be a Unique ID column. Every time I fill a row, I want Excel to automatically populate the Unique ID column for me. I did some research and was pointed in the direction of GUIDs. I found the following code:

Function GenGuid() As String
Dim TypeLib As Object
Dim Guid As String
Set TypeLib = CreateObject("Scriptlet.TypeLib")
Guid = TypeLib.Guid
' format is {24DD18D4-C902-497F-A64B-28B2FA741661}
Guid = Replace(Guid, "{", "")
Guid = Replace(Guid, "}", "")
Guid = Replace(Guid, "-", "")
GenGuid = Guid
End Function

but I am not sure how I can implement it. Any help would be greatly appreciated. Thank you in advance.

Vba Solutions


Solution 1 - Vba

The following Excel expression evaluates to a V4 GUID:

=CONCATENATE(DEC2HEX(RANDBETWEEN(0,4294967295),8),"-",DEC2HEX(RANDBETWEEN(0,65535),4),"-",DEC2HEX(RANDBETWEEN(16384,20479),4),"-",DEC2HEX(RANDBETWEEN(32768,49151),4),"-",DEC2HEX(RANDBETWEEN(0,65535),4),DEC2HEX(RANDBETWEEN(0,4294967295),8))

-or (depending on locale setting/decimal and list separators)-

=CONCATENATE(DEC2HEX(RANDBETWEEN(0;4294967295);8);"-";DEC2HEX(RANDBETWEEN(0;65535);4);"-";DEC2HEX(RANDBETWEEN(16384;20479);4);"-";DEC2HEX(RANDBETWEEN(32768;49151);4);"-";DEC2HEX(RANDBETWEEN(0;65535);4);DEC2HEX(RANDBETWEEN(0;4294967295);8))

Note that the first character of the third group is always 4 to signify a V4 (pseudo-random number generated) GUID/UUID per RFC 4122 section 4.4.

Also note that the first character of the fourth group is always between 8 and B per the same RFC.

Standard disclaimer: the resulting GUIDs/UUIDs are not cryptographically strong.

Edit: remove invisible characters

Solution 2 - Vba

I used the following function in v.2013 excel vba to create a GUID and is working well..

Public Function GetGUID() As String 
    GetGUID = Mid$(CreateObject("Scriptlet.TypeLib").GUID, 2, 36) 
End Function 

Solution 3 - Vba

I know this question is answered, but I think the code in question should look something like what's on this page: http://snipplr.com/view/37940/

Haven't tested, but this code seems to tap into the Windows API to get its GUID's - I would try putting that in a public module and typing =GetGUId() in an Excel cell to see what I'd get. If it works in VB6 you have a great deal of a good chance it works in VBA as well:

Private Type GUID
    Data1 As Long
    Data2 As Integer
    Data3 As Integer
    Data4(7) As Byte
End Type

Private Declare Function CoCreateGuid Lib "OLE32.DLL" (pGuid As GUID) As Long

Public Function GetGUID() As String
'(c) 2000 Gus Molina

    Dim udtGUID As GUID

    If (CoCreateGuid(udtGUID) = 0) Then

        GetGUID = _
            String(8 - Len(Hex$(udtGUID.Data1)), "0") & Hex$(udtGUID.Data1) & _
            String(4 - Len(Hex$(udtGUID.Data2)), "0") & Hex$(udtGUID.Data2) & _
            String(4 - Len(Hex$(udtGUID.Data3)), "0") & Hex$(udtGUID.Data3) & _
            IIf((udtGUID.Data4(0) < &H10), "0", "") & Hex$(udtGUID.Data4(0)) & _
            IIf((udtGUID.Data4(1) < &H10), "0", "") & Hex$(udtGUID.Data4(1)) & _
            IIf((udtGUID.Data4(2) < &H10), "0", "") & Hex$(udtGUID.Data4(2)) & _
            IIf((udtGUID.Data4(3) < &H10), "0", "") & Hex$(udtGUID.Data4(3)) & _
            IIf((udtGUID.Data4(4) < &H10), "0", "") & Hex$(udtGUID.Data4(4)) & _
            IIf((udtGUID.Data4(5) < &H10), "0", "") & Hex$(udtGUID.Data4(5)) & _
            IIf((udtGUID.Data4(6) < &H10), "0", "") & Hex$(udtGUID.Data4(6)) & _
            IIf((udtGUID.Data4(7) < &H10), "0", "") & Hex$(udtGUID.Data4(7))
    End If

End Function

Thanks Gus Molina!

If this code works (which I don't doubt), I think you'd get a new set of GUID's whenever the function gets evaluated, which means everytime the sheet gets calculated - when you're saving the workbook, for example. Make sure to copy-pastespecial-values if you need the GUID's for later use... which is somewhat likely.

Solution 4 - Vba

A VBA approach based on generating random numbers using the Rnd() function, and not on external API calls or Scriptlet.TypeLib:

Public Function CreateGUID() As String
    Do While Len(CreateGUID) < 32
        If Len(CreateGUID) = 16 Then
            '17th character holds version information
            CreateGUID = CreateGUID & Hex$(8 + CInt(Rnd * 3))
        End If
        CreateGUID = CreateGUID & Hex$(CInt(Rnd * 15))
    Loop
    CreateGUID = "{" & Mid(CreateGUID, 1, 8) & "-" & Mid(CreateGUID, 9, 4) & "-" & Mid(CreateGUID, 13, 4) & "-" & Mid(CreateGUID, 17, 4) & "-" & Mid(CreateGUID, 21, 12) & "}"
End Function

This essentially is a VBA implementation of NekojiruSou's answer (it also generates a v4 GUID), and carries the same limitations, but will work in VBA and might be easier to implement.

Note that you can omit the last line to not return the dashes and curly braces in the result.

Solution 5 - Vba

I found pretty solution here:
http://www.sql.ru/forum/actualutils.aspx?action=gotomsg&tid=751237&msg=8634441

Option Explicit

Private Type GUID
  Data1 As Long
  Data2 As Integer
  Data3 As Integer
  Data4(0 To 7) As Byte
End Type
Private Declare Function CoCreateGuid Lib "ole32" (pguid As GUID) As Long
Private Declare Function StringFromGUID2 Lib "ole32" ( _
  rguid As GUID, ByVal lpsz As Long, ByVal cchMax As Long) As Long

Public Function CreateGUID() As String
  Dim NewGUID As GUID
  CoCreateGuid NewGUID
  CreateGUID = Space$(38)
  StringFromGUID2 NewGUID, StrPtr(CreateGUID), 39
End Function

Solution 6 - Vba

Same same for german Excel version:

=VERKETTEN(DEZINHEX(ZUFALLSBEREICH(0;4294967295);8);"-";DEZINHEX(ZUFALLSBEREICH(0;65535);4);"-";DEZINHEX(ZUFALLSBEREICH(16384;20479);4);"-";DEZINHEX(ZUFALLSBEREICH(32768;49151);4);"-";DEZINHEX(ZUFALLSBEREICH(0;65535);4);DEZINHEX(ZUFALLSBEREICH(0;4294967295);8))

Solution 7 - Vba

Since windows update taken out "Scriptlet.TypeLib", try the following:

Declare Function CoCreateGuid Lib "ole32" (ByRef GUID As Byte) As Long
Public Function GenerateGUID() As String
    Dim ID(0 To 15) As Byte
    Dim N As Long
    Dim GUID As String
    Dim Res As Long
    Res = CoCreateGuid(ID(0))
    
    For N = 0 To 15
        GUID = GUID & IIf(ID(N) < 16, "0", "") & Hex$(ID(N))
        If Len(GUID) = 8 Or Len(GUID) = 13 Or Len(GUID) = 18 Or Len(GUID) = 23 Then
            GUID = GUID & "-"
        End If
    Next N
    GenerateGUID = GUID
End Function

Alternatively,

if you are connecting to SQL Server 2008 or higher, try to use the SQL NEWID() function instead.

Solution 8 - Vba

I recently ran into problems using CreateObject("Scriptlet.TypeLib") in some vba code.

So based on NekojiruSou excel functions wrote the following which should work without any specific excel functions. This can be used to develop a user defined function in excel.

Public Function Get_NewGUID() As String
    'Returns GUID as string 36 characters long

    Randomize

    Dim r1a As Long
    Dim r1b As Long
    Dim r2 As Long
    Dim r3 As Long
    Dim r4 As Long
    Dim r5a As Long
    Dim r5b As Long
    Dim r5c As Long

    'randomValue = CInt(Math.Floor((upperbound - lowerbound + 1) * Rnd())) + lowerbound
    r1a = RandomBetween(0, 65535)
    r1b = RandomBetween(0, 65535)
    r2 = RandomBetween(0, 65535)
    r3 = RandomBetween(16384, 20479)
    r4 = RandomBetween(32768, 49151)
    r5a = RandomBetween(0, 65535)
    r5b = RandomBetween(0, 65535)
    r5c = RandomBetween(0, 65535)

    Get_NewGUID = (PadHex(r1a, 4) & PadHex(r1b, 4) & "-" & PadHex(r2, 4) & "-" & PadHex(r3, 4) & "-" & PadHex(r4, 4) & "-" & PadHex(r5a, 4) & PadHex(r5b, 4) & PadHex(r5c, 4))

End Function

Public Function Floor(ByVal X As Double, Optional ByVal Factor As Double = 1) As Double
    'From: http://www.tek-tips.com/faqs.cfm?fid=5031
    ' X is the value you want to round
    ' Factor is the multiple to which you want to round
        Floor = Int(X / Factor) * Factor
End Function

Public Function RandomBetween(ByVal StartRange As Long, ByVal EndRange As Long) As Long
    'Based on https://msdn.microsoft.com/en-us/library/f7s023d2(v=vs.90).aspx
    '         randomValue = CInt(Math.Floor((upperbound - lowerbound + 1) * Rnd())) + lowerbound
        RandomBetween = CLng(Floor((EndRange - StartRange + 1) * Rnd())) + StartRange
End Function

Public Function PadLeft(text As Variant, totalLength As Integer, padCharacter As String) As String
    'Based on https://stackoverflow.com/questions/12060347/any-method-equivalent-to-padleft-padright
    ' with a little more checking of inputs

    Dim s As String
    Dim inputLength As Integer
    s = CStr(text)
    inputLength = Len(s)

    If padCharacter = "" Then
        padCharacter = " "
    ElseIf Len(padCharacter) > 1 Then
        padCharacter = Left(padCharacter, 1)
    End If

    If inputLength < totalLength Then
        PadLeft = String(totalLength - inputLength, padCharacter) & s
    Else
        PadLeft = s
    End If

End Function

Public Function PadHex(number As Long, length As Integer) As String
    PadHex = PadLeft(Hex(number), 4, "0")
End Function

Solution 9 - Vba

I created a VBA function that works both on mac and windows:

https://github.com/Martin-Carlsson/Business-Intelligence-Goodies/blob/master/Excel/GenerateGiud/GenerateGiud.bas

'Generates a guid, works on both mac and windows 
Function Guid() As String
	Guid = RandomHex(3) + "-" + _
		RandomHex(2) + "-" + _
		RandomHex(2) + "-" + _
		RandomHex(2) + "-" + _
		RandomHex(6)
End Function

'From: https://www.mrexcel.com/forum/excel-questions/301472-need-help-generate-hexadecimal-codes-randomly.html#post1479527
Private Function RandomHex(lngCharLength As Long)
	Dim i As Long
	Randomize
	For i = 1 To lngCharLength
		RandomHex = RandomHex & Right$("0" & Hex(Rnd() * 256), 2)
	Next
End Function

Solution 10 - Vba

This is based on a javascript implementation.

Private Function getGUID() As String
  getGUID = "xxxxxxxx-xxxx-4xxx-yxxx-xxxxxxxxxxxx"
  getGUID = Replace(getGUID, "y", Hex(Rnd() And &H3 Or &H8))
  Dim i As Long: For i = 1 To 30
    getGUID = Replace(getGUID, "x", Hex$(CLng(Rnd() * 15.9999)), 1, 1)
  Next
End Function

Solution 11 - Vba

If you are inserting records into a database you can use this way to make a GUID.

It is probably the most simplest and easiest way to implement as you don't need a complex VBA function as you use the built in SQL function.

The statement uses NewID(),

The syntax is as follows,

INSERT INTO table_name (ID,Column1,Column2,Column3)
VALUES (NewID(),value1,value2,value3) 

In VBA syntax it is as follows,

strSql = "INSERT INTO table_name " _
       & "(ID,Column1,Column2,Column3) " _
       & "VALUES (NewID(),value1,value2,value3)"

And if you need to concatenate values, just treat it as a string and concatenate as you would normally for a SQL statement,

strSql = "INSERT INTO table_name " _
       & "(ID,Column1,Column2,Column3) " _
       & "VALUES (" & "NewID()" & "," & "value1" & "," & "value2" & "," & "value3" & ")"

Solution 12 - Vba

For generating random guids using just the Rnd() function, not using any libraries or APIs, the simplest I can think of is this:

' UUID Version 4 (random)
Function GetUUID4()

    Dim guid As String
    Dim i As Integer
    Dim r As Integer
    
    guid = ""
    Randomize
    
    For i = 0 To 31
        ' random digit 0..15
        r = Rnd() * 15

        ' add dash separators
        If (i = 8) Or (i = 12) Or (i = 16) Or (i = 20) Then guid = guid & "-"

        ' uuid4 version info in 12th and 16th digits
        If (i = 12) Then r = 4
        If (i = 16) Then r = (r And 3 Or 8)

        ' add as hex digit
        guid = guid & Hex(r)
    Next i

    GetUUID4 = guid
End Function

Solution 13 - Vba

Function funGetGuid() As String

    Const URL As String = "http://www.guidgen.com/"
    Const strMask As String = "value="
    
    Dim l As Long
    Dim txt As String
    
    With CreateObject("MSXML2.XMLHTTP")
        .Open "GET", URL, False
        .send
        txt = .responseText
    End With
    
    Do
        l = InStr(l + 1, txt, strMask)
        If l = 0 Then Exit Do
        funGetGuid = Mid$(txt, l + Len(strMask) + 1, 36)
    Loop

End Function

Attributions

All content for this solution is sourced from the original question on Stackoverflow.

The content on this page is licensed under the Attribution-ShareAlike 4.0 International (CC BY-SA 4.0) license.

Content TypeOriginal AuthorOriginal Content on Stackoverflow
Questionabw333View Question on Stackoverflow
Solution 1 - VbaNekojiruSouView Answer on Stackoverflow
Solution 2 - VbarchackoView Answer on Stackoverflow
Solution 3 - VbaMathieu GuindonView Answer on Stackoverflow
Solution 4 - VbaErik AView Answer on Stackoverflow
Solution 5 - VbaAlekzanderView Answer on Stackoverflow
Solution 6 - VbaChakeView Answer on Stackoverflow
Solution 7 - VbarchackoView Answer on Stackoverflow
Solution 8 - VbamphaseView Answer on Stackoverflow
Solution 9 - VbaMartin CarlssonView Answer on Stackoverflow
Solution 10 - VbaSancarnView Answer on Stackoverflow
Solution 11 - VbaKyloRenView Answer on Stackoverflow
Solution 12 - VbaBdRView Answer on Stackoverflow
Solution 13 - Vbabart-pieterView Answer on Stackoverflow