UUID.st
author fm
Tue, 24 Jun 2008 15:32:55 +0200
changeset 2018 316b0a396e86
parent 2017 d08521448dc0
child 2021 21f1faba832a
permissions -rw-r--r--
decodeFromLiterlArray

"
 COPYRIGHT (c) 2002 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic2' }"

ByteArray variableByteSubclass:#UUID
	instanceVariableNames:''
	classVariableNames:'CachedMACAddress Lock SequenceNumber LastTime Increment
		NameSpaceDNS NameSpaceDN NameSpaceURL NameSpaceOID'
	poolDictionaries:''
	category:'Net-Communication-Support'
!

!UUID class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2002 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    128-bit Universal Unique Ids (UUIDs) as defined by OpenGroup/DCE
        http://www.opengroup.org/onlinepubs/9629399/apdxa.htm.

    See also RFC4122.

    A UUID is unique in time and space (at least until about Year 3400).

    Several fields if the UUID are interpreted as integers, so host/network byte
    order is relevant. UUIDs are stored in a ByteArray in network byte order (MSB-first),
    so they may be exported/imported between different machines.

    You can import UUIDs in host byte order using #fromNativeBytes:

    [author:]

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!UUID class methodsFor:'initialization'!

initialize
    "I want to get informed about image restarts"

    Lock isNil ifTrue:[
        Lock := RecursionLock new name:'UUID'.
        LastTime := 0.
        Increment := 0.
        ObjectMemory addDependent:self.

        NameSpaceDNS := self fromBytes:#[16r6B 16rA7 16rB8 16r10 16r9D 16rAD 16r11 16rD1 16r80 16rB4 16r0 16rC0 16r4F 16rD4 16r30 16rC8].
        NameSpaceURL := self fromBytes:#[16r6B 16rA7 16rB8 16r11 16r9D 16rAD 16r11 16rD1 16r80 16rB4 16r0 16rC0 16r4F 16rD4 16r30 16rC8].
        NameSpaceOID := self fromBytes:#[16r6B 16rA7 16rB8 16r12 16r9D 16rAD 16r11 16rD1 16r80 16rB4 16r0 16rC0 16r4F 16rD4 16r30 16rC8].
        NameSpaceDN  := self fromBytes:#[16r6B 16rA7 16rB8 16r14 16r9D 16rAD 16r11 16rD1 16r80 16rB4 16r0 16rC0 16r4F 16rD4 16r30 16rC8].
    ]
!

update:something with:aParameter from:changedObject
    "flush cached MAC address (may have been restarted on another host)"

    (something == #restarted) ifTrue:[
        CachedMACAddress := nil.
        SequenceNumber := nil.
    ]
! !

!UUID class methodsFor:'instance creation'!

basicNew
    ^ super basicNew:16
!

basicNew:size
    "allow creating with exact size. We need this for XMLStandardDecoder"

    size ~~ 16 ifTrue:[
        ^ self shouldNotImplement.
    ].
    ^ super basicNew:size.
!

decodeFromLiteralArray:anArray
    anArray size == 2 ifTrue:[
        "/ UUID 'uuid-string'
        ^ self readFrom:(anArray at:2).
    ].
    "/ UUID bytes...
    ^ super decodeFromLiteralArray:anArray "/ self readFrom:(anArray at:2)

    "
     (UUID decodeFromLiteralArray:#(UUID '5b023ce0-41f1-11dd-b99f-001558137da0'))
       literalArrayEncoding   
    "
!

fromBytes:aByteArray
    "set uuid from aByteArray.
     aByteArray must be 16 bytes in network byte order (MSB-first)"

    |uuid|

    uuid := super basicNew:16.
    uuid replaceFrom:1 to:16 with:aByteArray.
    ^ uuid.

    "    
     UUID fromBytes:#[16r01 16r02 16r03 16r04
                      16r05 16r06 16r07 16r08
                      16r09 16r10 16r11 16r12
                      16r13 16r14 16r15 16r16]. 
    "
!

fromBytes:aByteArray msb:msb
    "Set the UUID from aByteArray. UUIDS are stored internally as MSB-first. 
     So, alway set
        msb = true      if reading from network or persistent storage"

    |uuid|

    uuid := self fromBytes:aByteArray.
    msb ifFalse:[
        self adjustByteOrder:uuid.
    ].

    ^ uuid

    "
     UUID fromBytes:#[16r01 16r02 16r03 16r04
                      16r05 16r06 16r07 16r08
                      16r09 16r10 16r11 16r12
                      16r13 16r14 16r15 16r16] msb:false. 
    "
    "
     UUID fromBytes:#[16r01 16r02 16r03 16r04
                      16r05 16r06 16r07 16r08
                      16r09 16r10 16r11 16r12
                      16r13 16r14 16r15 16r16] msb:true.    
    "
!

fromNativeBytes:aByteArray
    "convert bytes to uuid.
     aByteArray represents a UUID in host byte order 
     - e.g. an UUID fetched from the Windows OS"

    |uuid|

    uuid := self fromBytes:aByteArray.
    self isBigEndian ifFalse:[
        self adjustByteOrder:uuid.
    ].
    ^ uuid.

    "    
     UUID fromNativeBytes:#[16r01 16r02 16r03 16r04
                              16r05 16r06 16r07 16r08
                              16r09 16r10 16r11 16r12
                              16r13 16r14 16r15 16r16]. 

    "
!

genRandomUUID
    "generate a new random UUID"

    ^ (super basicNew:16) genRandomUUID

    "
      self genRandomUUID
    "
!

genUUID
    "generate a uuid.
     If a physical mac address can be retrieved from the OS,
     a mac-address/timestamp uuid is generated,
     otherwise a random uuid will be generated."

    ^ (super basicNew:16) genUUID

    "
     self genUUID
    "
!

new
    ^ (super basicNew:16) genUUID

    "
     self new 
    "
!

new:size
    "allow creating with exact size. We need this for XMLStandardDecoder"

    size ~~ 16 ifTrue:[
        ^ self shouldNotImplement.
    ].
    ^ super new:size.
!

readFrom:aStringOrStream onError:errorBlock
    |d offs s uuid t byte|

    Error handle:[:ex |
        ^ errorBlock value.
    ] do:[
        s := aStringOrStream readStream.
        uuid := super basicNew:16.

        s skipSeparators.
        s peek == ${ ifTrue:[s next].
        s skipSeparators.

        t := s next:8.
        d := Integer readFrom:t radix:16 onError:[^ errorBlock value].
        uuid unsignedLongAt:1 put:d bigEndian:true.
        offs := 5.

        s next.         "skip $-"

        1 to:2 do:[:i |
            t := s next:4.
            d := Integer readFrom:t radix:16 onError:[^ errorBlock value].
            uuid unsignedShortAt:offs put:d bigEndian:true.
            offs := offs + 2.
            s next.     "skip $-"
        ].

        1 to:2 do:[:i |
            t := s next:2.
            d := Integer readFrom:t radix:16 onError:[^ errorBlock value].
            uuid at:offs put:d.
            offs := offs + 1.
        ].
        s next.         "skip $-"

        1 to:6 do:[:i |
            t := s next:2.
            byte := Integer readFrom:t radix:16 onError:[^ errorBlock value].
            uuid at:offs put:byte.
            offs := offs + 1.
        ].
    ].
    ^ uuid

    "
     UUID readFrom:'5ab2e9b4-3d48-11d2-9ea4-80c5140aaa77' 
     UUID fromString:'5ab2e9b4-3d48-11d2-9ea4-80c5140aaa77' 
     UUID fromString:'00000001-0000-0000-C000-000000000046'
     UUID fromString:'00000001-0000-0000-C000-000000004600'
     UUID fromString:'00000001-0000-0000-C000-000000460000'
     UUID fromString:'00000001-0000-0000-C000-000046000000'
     UUID fromString:'00000001-0000-0000-C000-004600000000'
     UUID fromString:'00000001-0000-0000-C000-460000000000'
     UUID fromString:'00000001-0000-0000-C046-000000000000'
     UUID fromString:'00000001-0000-0046-C000-000000000000'
     UUID fromString:'00000001-0000-4600-C000-000000000000'
     UUID fromString:'00000001-0046-0000-C000-000000000000'
     UUID fromString:'00000001-4600-0000-C000-000000000000'
     UUID fromString:'00000100-4600-0000-C000-000000000000'
     UUID fromString:'00010000-4600-0000-C000-000000000000'
     UUID fromString:'10000000-4600-0000-C000-000000000000'
    "

    "Modified: / 10-10-2007 / 23:03:47 / cg"
! !

!UUID class methodsFor:'helpers'!

adjustByteOrder:aByteArray
    "change the byte order of the uuid"

    |d|

    d := aByteArray unsignedLongAt:1 bigEndian:false.
    aByteArray unsignedLongAt:1 put:d bigEndian:true.

    d := aByteArray unsignedShortAt:1+4 bigEndian:false.
    aByteArray unsignedShortAt:1+4 put:d bigEndian:true.

    d := aByteArray unsignedShortAt:1+4+2 bigEndian:false.
    aByteArray unsignedShortAt:1+4+2 put:d bigEndian:true.
!

getDtssUtcTime
    "return the DTSS based time in 100 nsec intervals
     DTSS UTC base time is October 15, 1582 (the start of the Gregorian Calendar)."

     "Unix base time is January 1, 1970.
      The difference between both is: 122192928000000000"

"   
        (Timestamp epoch asDate subtractDate:(Date day:15 month:10 year:1582))
        *  (24 * 60 * 60)
"

    ^ (Timestamp now getMilliseconds + 12219292800000) * 10000.
!

getValidMACAddress
    "return the first valid MAC address (i.e. having at least one byte ~~ 0)"

    CachedMACAddress isNil ifTrue:[
        |dictOfIf ipAddr|

        CachedMACAddress := false.      "cache the fact, that there is no MAC address" 
        [
            dictOfIf := OperatingSystem getNetworkMACAddresses.

            dictOfIf do:[:macAddress |
                (macAddress contains:[:byte | byte ~~ 0]) ifTrue:[
                    ^ CachedMACAddress := macAddress
                ].
            ].
        ] on:PrimitiveFailure do:[:ex| "ignore"].
    ].

    ^ CachedMACAddress

    "
       CachedMACAddress := nil.
       self getValidMACAddress
    "

    "Modified: / 17-11-2004 / 01:45:53 / cg"
! !

!UUID methodsFor:'accessing'!

clockSeqHiAndReserved
    ^ self at:9
!

clockSeqLow
    ^ self at:10
!

node
    ^ self copyFrom:11 to:16
!

timeHighAndVersion
    ^ self unsignedShortAt:7 bigEndian:true
!

timeLow
    ^ self unsignedLongAt:1 bigEndian:true
!

timeMid
    ^ self unsignedShortAt:5 bigEndian:true
! !

!UUID methodsFor:'converting'!

asBytes
    "convert this UUID to a ByteArray in network byte order (MSB-first)"

    |bytes|

    bytes := ByteArray new:16.
    bytes replaceFrom:1 to:16 with:self.
    ^ bytes

    "
     |bytes|
        
     bytes := #[16r01 16r02 16r03 16r04
                      16r05 16r06 16r07 16r08
                      16r09 16r10 16r11 16r12
                      16r13 16r14 16r15 16r16].
     (UUID fromBytes:bytes) asBytes ~= bytes ifTrue:[self halt] 
    "
!

asBytesMSB:msb
    "convert this UUID to a ByteArray.
     If msb == false, it is converted into LSB-first byte ordering"

    |bytes|

    bytes := self asBytes.

    msb ifFalse:[
        self class adjustByteOrder:bytes.
    ].
    ^ bytes

    "Modified: / 10-10-2007 / 22:51:09 / cg"
!

asNativeBytes
    "convert this uuid to a ByteArray in host byte order.
     Use this only to pass the UUID to the OS (Windows)"

    |bytes|

    bytes := self asBytes.
    self class isBigEndian ifFalse:[
        self class adjustByteOrder:bytes.
    ].
    ^ bytes.
! !

!UUID methodsFor:'generating uuids'!

genRandomUUID
    "answer a randomly generated uuid as defined in RFC4122 section 4.4"

    self replaceFrom:1 to:16 with:(RandomGenerator new nextBytes:16).
    "multiplex the 4 bit version number (Version 4 -> Random UUID) in high bits of byte 7"
    self at:7 put:(((self at:7) bitAnd:16r0F) bitOr:16r40).
    self at:9 put:(((self at:9) bitAnd:16r3F) bitOr:16r80).

    "
      self new genRandomUUID
    "

    "
      1 to: 100 do:[ : el |
          Transcript show:el.
          Transcript show:': '.
          Transcript showCR:(UUID new genRandomUUID).
      ].
    "
!

genTimestampUUID
    "generate a timestamp (and mac-address) based uuid"

    |macBytes utcTime seqNr|

    macBytes := self class getValidMACAddress.
    macBytes size ~~ 6 ifTrue:[
        self error:'no mac address - cannot generate UUID'.
    ].

    "use 60 bit counter of 100ns ticks since 00:00:00 15.oct 1582 (sigh)"
    utcTime := self class getDtssUtcTime.

    Lock critical:[
        SequenceNumber isNil ifTrue:[
            SequenceNumber := RandomGenerator new nextIntegerBetween:0 and:16383.
        ].
        utcTime > (LastTime+Increment) ifTrue:[
            Increment := 0.
        ] ifFalse:[
            LastTime = utcTime ifTrue:[
                "clock didn't advance since last call. Simply add a tick"
                Increment := Increment + 1.
            ] ifFalse:[
                "clock went backwards - increment SequenceNumber"
                Increment := 0.
                SequenceNumber := SequenceNumber + 1.
                SequenceNumber >= 16384 ifTrue:[SequenceNumber := 0].
            ].
        ].
        
        LastTime := utcTime.
        utcTime := utcTime + Increment.
        seqNr := SequenceNumber.
    ].


    "time low: long"
    self unsignedLongAt:1 put:(utcTime bitAnd:16rFFFFFFFF) bigEndian:true.

    "time med: short"
    utcTime := utcTime bitShift:-32.
    self unsignedShortAt:5 put:(utcTime bitAnd:16rFFFF) bigEndian:true.

    "time high and version: short
     multiplex the 4 bit version number in highest 4 bits (version 1 -> time based version)"
    self unsignedShortAt:7 put:((utcTime bitShift:-16) bitOr:16r1000) bigEndian:true.

    "2 sequence bytes + reserved bits (this is not a short!!)"
    self at:9  put:(((seqNr bitShift:-8) bitAnd:16r3F) bitOr:16r80).
    self at:10 put:(seqNr bitAnd:16rFF).

    "48 bits of MAC-Address"
    self replaceFrom:11 to:16 with:macBytes startingAt:1.

    "
      self new genTimestampUUID
    "

    "
      1 to: 100 do:[ : el |
          Transcript show:el.
          Transcript show:': '.
          Transcript showCR:(UUID new genTimestampUUID).
      ].
    "
!

genUUID
    "generate a uuid - the existing uuid bytes are overwritten.
     If a physical mac address can be retrieved from the OS,
     a mac-address/timestamp uuid is generated,
     otherwise a random uuid will be generated."

    CachedMACAddress isNil ifTrue:[
        self class getValidMACAddress.
    ].
    CachedMACAddress == false ifTrue:[
        "no mac address - generate random UUID"
        ^ self genRandomUUID.
    ].
    ^ self genTimestampUUID.

    "
      self genUUID
    "

    "
      1 to: 100 do:[ : el |
          Transcript show:el.
          Transcript show:': '.
          Transcript showCR:(UUID genUUID).
      ].
    "
! !

!UUID methodsFor:'printing'!

displayString
    ^ self printString
!

printOn:aStream
    |d tmpStream|

    tmpStream := '' writeStream.

"/    d := self unsignedLongAt:1 bigEndian:true.
"/    d printOn:tmpStream base:16 size:8 fill:$0.
"/    tmpStream nextPut:$-.
"/
"/    d := self unsignedShortAt:1+4 bigEndian:true.
"/    d printOn:tmpStream base:16 size:4 fill:$0.
"/    tmpStream nextPut:$-.
"/
"/    d := self unsignedShortAt:1+4+2 bigEndian:true.
"/    d printOn:tmpStream base:16 size:4 fill:$0.
"/    tmpStream nextPut:$-.
"/
"/    d := self at:1+4+2+2.
"/    d printOn:tmpStream base:16 size:2 fill:$0.
"/    d := self at:1+4+2+2+1.
"/    d printOn:tmpStream base:16 size:2 fill:$0.
"/    tmpStream nextPut:$-.
"/
"/    11 to:16 do:[:idx|
"/        d := self at:idx.
"/        d printOn:tmpStream base:16 size:2 fill:$0.
"/    ].

    1 to:4 do:[:idx|
        d := self at:idx.
        d printOn:tmpStream base:16 size:2 fill:$0.
    ].
    tmpStream nextPut:$-.
    5 to:6 do:[:idx|
        d := self at:idx.
        d printOn:tmpStream base:16 size:2 fill:$0.
    ].
    tmpStream nextPut:$-.
    7 to:8 do:[:idx|
        d := self at:idx.
        d printOn:tmpStream base:16 size:2 fill:$0.
    ].
    tmpStream nextPut:$-.
    9 to:10 do:[:idx|
        d := self at:idx.
        d printOn:tmpStream base:16 size:2 fill:$0.
    ].
    tmpStream nextPut:$-.
    11 to:16 do:[:idx|
        d := self at:idx.
        d printOn:tmpStream base:16 size:2 fill:$0.
    ].

    aStream nextPutAll:(tmpStream contents asLowercase).

    "Modified: / 10-10-2007 / 23:19:03 / cg"
! !

!UUID class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/UUID.st,v 1.26 2008-06-24 13:32:55 fm Exp $'
! !

UUID initialize!