CRC32Stream.st
author Claus Gittinger <cg@exept.de>
Thu, 06 Sep 2007 17:31:09 +0200
changeset 1894 8bf137acc445
parent 1192 27c5d5ea5969
child 1975 0850a3e0d484
permissions -rw-r--r--
if no unit is given in the readString, assume seconds.

"{ Package: 'exept:libcrypt' }"

HashStream subclass:#CRC32Stream
	instanceVariableNames:'crc'
	classVariableNames:'CrcTable'
	poolDictionaries:''
	category:'System-Crypt-Streams'
!

!CRC32Stream class methodsFor:'documentation'!

documentation
"
    Standard CRC method as defined by ISO 3309 [ISO-3309] or ITU-T V.42 [ITU-T-V42]. 
    The CRC polynomial employed is

        x^32+x^26+x^23+x^22+x^16+x^12+x^11+x^10+x^8+x^7+x^5+x^4+x^2+x+1

    Use CRC to protect against communication errors. Do NOT use CRC for cryptography.
    Use SHA1Stream or MD5Stream instead.


    [author:]
        Stefan Vogel (stefan@zwerg)

    [instance variables:]

    [class variables:]

    [see also:]
        SHA1Stream
        MD5Stream

"
!

examples
"

                                                                [exBegin]
    self information:(CRC32Stream hashValueOf:'Dies ist ein Test') printString
                                                                [exEnd]

                                                                [exBegin]
    self information:(CRC32Stream new nextPut:4711; hashValue) printString
                                                                [exEnd]

                                                                [exBegin]
    self information:(CRC32Stream hashValueOf:#[1 2 3 4 5 6 7]) printString
                                                                [exEnd]

                                                                [exBegin]
    self information:((CRC32Stream hashValueOf:#[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF]) digitBytes printOn:Transcript base:16)
                                                                [exEnd]
"
! !

!CRC32Stream class methodsFor:'initialization'!

initialize

    CrcTable := IntegerArray new:256.

    0 to:255 do:[:count| |i|
        i := count.
        8 timesRepeat:[
            (i bitTest:1) ifTrue:[
                i := 16rEDB88320 bitXor:(i bitShift:-1)
            ] ifFalse:[
                i := i bitShift:-1
            ]
        ].
        CrcTable at:count+1 put:i.
    ].

    "
      self initialize
    "
! !

!CRC32Stream class methodsFor:'testing'!

testVector
    "define a testvector to test the implementation"

    ^ #(
          (#[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF
             16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF]
           2362461299)

          (#[0 0 0 0 0 0 0 0 0 0 
             0 0 0 0 0 0 0 0 0 0
             0 0 0 0 0 0 0 0 0 0
             0 0 0 0 0 0 0 0 0 0]
           3924573617)

          (#[0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19
             20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39]
           228994620 )
       )

    "
     self test
    "
! !

!CRC32Stream methodsFor:'initialization'!

initialize
    "initialize the CRC"

    crc := 16rFFFFFFFF.
! !

!CRC32Stream methodsFor:'queries'!

hashValue
    "return the computed CRC"

    ^ crc bitXor:16rFFFFFFFF
! !

!CRC32Stream methodsFor:'writing'!

nextPut:arg 
    "add the hash of anObject to the computed hash so far.
     anObject can be a Character, SmallInteger, or Character-, Byte-
     Integer-Array"

    arg isCharacter ifTrue:[
        crc := (CrcTable at:((crc bitXor:arg asciiValue) bitAnd:16rFF)+1) 
               bitXor:(crc bitShift:-8).
        ^ self.
    ].

    arg isInteger ifTrue:[
        arg < 256 ifTrue:[
            crc := (CrcTable at:((crc bitXor:arg) bitAnd:16rFF)+1) 
                   bitXor:(crc bitShift:-8).
            ^ self.
        ].
        arg digitBytes do:[:byte|
            crc := (CrcTable at:((crc bitXor:byte) bitAnd:16rFF)+1) 
                   bitXor:(crc bitShift:-8).
        ].
        ^ self.
    ].
    arg isCollection ifTrue:[
        arg do:[:element|
            self nextPut:element
        ].
        ^ self.
    ].


    self error:'unsupported argument'.
! !

!CRC32Stream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/CRC32Stream.st,v 1.1 2003-05-05 12:57:01 stefan Exp $'
! !

CRC32Stream initialize!