UUID.st
author Stefan Vogel <sv@exept.de>
Fri, 13 Aug 2004 15:31:06 +0200
changeset 1467 a394ade68816
parent 1447 210f3ac37991
child 1491 512b21b45a9e
permissions -rw-r--r--
Protect against a nil SequenceNumber

"
 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'
	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 define by OpenGroup/DCE
    http://www.opengroup.org/onlinepubs/9629399/apdxa.htm.

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

    [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.
    ]
!

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'!

fromBytes:aByteArray
    ^ self fromBytes:aByteArray msb:(UninterpretedBytes isBigEndian)
!

fromBytes:aByteArray msb:msb
    |uuid d1 d2 d3|

    uuid := self new.
    uuid replaceFrom:1 to:16 with:aByteArray.

    msb ifTrue:[
        d1 := aByteArray unsignedLongAt:1 bigEndian:msb.
        uuid unsignedLongAt:1 put:d1 bigEndian:false.

        d2 := aByteArray unsignedShortAt:1+4 bigEndian:msb.
        uuid unsignedShortAt:1+4 put:d2 bigEndian:false.

        d3 := aByteArray unsignedShortAt:1+4+2 bigEndian:msb.
        uuid unsignedShortAt:1+4+2 put:d3 bigEndian:false.
    ].

    ^ 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.    
    "
!

genUUID
    "generate a new UUID"

    ^ self new genUUID
"
    self genUUID
"
!

new
    ^ super new:16
!

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|

    s := aStringOrStream readStream.
    uuid := self new.
    offs := 1.

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

    t := s next:8.
    d := Integer readFrom:t radix:16 onError:errorBlock.
    uuid unsignedLongAt:1 put:d bigEndian:false.
    offs := offs + 4.

    s next.

    1 to:3 do:[:i |
        t := s next:4.
        d := Integer readFrom:t radix:16 onError:errorBlock.
        uuid unsignedShortAt:offs put:d bigEndian:false.
        offs := offs + 2.
        s next.
    ].

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

    "
     UUID readFrom:'5ab2e9b4-3d48-11d2-9ea4-80c5140aaa77' 
     UUID fromString:'5ab2e9b4-3d48-11d2-9ea4-80c5140aaa77' 
    "
! !

!UUID class methodsFor:'defaults'!

uuidVersion

    ^ 1
! !

!UUID class methodsFor:'helpers'!

getDtssUtcTime
    "return the DTSS based time in 100 nsec intervals
     DTSS UTC base time is October 15, 1582.
     Unix base time is January 1, 1970.
     The difference between both is: 16r01B21DD213814000"

    ^ Timestamp now getMilliseconds * 10000 + 16r01B21DD213814000.
!

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

    CachedMACAddress isNil ifTrue:[
        |dictOfIf|

        dictOfIf := OperatingSystem getNetworkMACAddresses.

        dictOfIf do:[:macAddress |
            (macAddress contains:[:byte | byte ~~ 0]) ifTrue:[
                ^ CachedMACAddress := macAddress
            ].
        ].
        self error:'no mac address' mayProceed:true.
        ^ #[16r55 16r55 16r55 16r55 16r55 16r55].
    ].

    ^ CachedMACAddress

    "
       CachedMACAddress := nil.
       self getValidMACAddress
    "
! !

!UUID methodsFor:'accessing'!

clockSeqAndReserved

    ^ self unsignedShortAt:9 bigEndian:false
!

node

    ^ self copyFrom:10 to:16
!

timeHighAndVersion

    ^ self unsignedShortAt:7 bigEndian:false
!

timeLow

    ^ self unsignedLongAt:1 bigEndian:false
!

timeMid

    ^ self unsignedShortAt:5 bigEndian:false
! !

!UUID methodsFor:'converting'!

asBytes
    ^ self asBytesMSB:(UninterpretedBytes isBigEndian)
!

asBytesMSB:msb
    |bytes d1 d2 d3|

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

    msb ifTrue:[
        d1 := self unsignedLongAt:1 bigEndian:false.
        d2 := self unsignedShortAt:1+4 bigEndian:false.
        d3 := self unsignedShortAt:1+4+2 bigEndian:false.

        bytes unsignedLongAt:1 put:d1 bigEndian:true.
        bytes unsignedShortAt:1+4 put:d2 bigEndian:true.
        bytes unsignedShortAt:1+4+2 put:d3 bigEndian:true.
    ].
    ^ bytes
! !

!UUID methodsFor:'generating uuids'!

genUUID
    |macBytes utcTime|

    macBytes := self class getValidMACAddress.

    "use 60 bit counter of 100ns ticks since 00:00:00 15.oct 1582 (sigh)"
    Lock critical:[
        SequenceNumber isNil ifTrue:[
            SequenceNumber := Random nextIntegerBetween:0 and:16383.
        ].
        utcTime := self class getDtssUtcTime.
        LastTime < utcTime 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.
    ].

    "first 60 bits of timestamp"
    self replaceFrom:1 to:8 with:utcTime digitBytes.
    "multiplex the 4 bit version number in high bits of byte 8"
    self at:8 put:((self at:8) bitOr:(self class uuidVersion bitShift:4)).

    "2 sequence bytes + reserved bits"
    self at:9  put:(SequenceNumber digitAt:1).
    self at:10 put:((SequenceNumber digitAt:2) bitOr:2r10000000).

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

    "
      self genUUID
    "

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

!UUID methodsFor:'printing'!

displayString
    ^ self printString
!

printOn:aStream
    |offs d tmpStream|

    tmpStream := '' writeStream.

    d := self unsignedLongAt:1 bigEndian:false.
    d printOn:tmpStream base:16 size:8 fill:$0.

    tmpStream nextPut:$-.

    offs := 5.
    3 timesRepeat:[
        d := self unsignedShortAt:offs bigEndian:false.
        offs := offs + 2.
        d printOn:tmpStream base:16 size:4 fill:$0.
        tmpStream nextPut:$-.
    ].

    6 timesRepeat:[
        d := self at:offs.
        offs := offs + 1.
        d printOn:tmpStream base:16 size:2 fill:$0.
    ].

    aStream nextPutAll:(tmpStream contents asLowercase).
! !

!UUID class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/UUID.st,v 1.10 2004-08-13 13:31:06 stefan Exp $'
! !

UUID initialize!