CRC32Stream.st
author Stefan Vogel <sv@exept.de>
Tue, 10 May 2011 16:27:15 +0200
changeset 2564 0c8cd34c7176
parent 2416 df3f9f02c8d8
child 2569 abfbf6f1682b
permissions -rw-r--r--
changed: #documentation

"
 COPYRIGHT (c) 2003 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' }"

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

!CRC32Stream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2003 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
"
    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
        (or 16r82608EDB)

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

    Notice that this CRC is also used with PNG images - therefore, its performance 
    directly affects png image processing.

    throughput:
        150000 Kb/s on 2Ghz Duo

    [author:]
        Stefan Vogel (stefan@zwerg)

    [instance variables:]

    [class variables:]

    [see also:]
        SHA1Stream
        MD5Stream

"
!

examples
"

  expect 60C1D0A0
                                                                [exBegin]
    self information:(CRC32Stream hashValueOf:'resume') hexPrintString
                                                                [exEnd]

  expect 16r60C1D0A0
                                                                [exBegin]
    self information:(CRC32Stream new
                            nextPut:$r;
                            nextPut:$e;
                            nextPut:$s;
                            nextPut:$u;
                            nextPut:$m;
                            nextPut:$e;
                            hashValue) hexPrintString
                                                                [exEnd]

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

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

  expect 16r8CD04C73:
                                                                [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 hexPrintString)
                                                                [exEnd]

  expect 16r86D7D79A:
  timing throughput:
                                                                [exBegin]
    |hashStream n t|

    hashStream := CRC32Stream new.
    n := 100000.
    t := Time millisecondsToRun:[
            n timesRepeat:[
                hashStream nextPutAll:'12345678901234567890123456789012345678901234567890'.
            ].
         ].
    t := (t / 1000) asFloat.
    Transcript show:'crc32:'; showCR: hashStream hashValue.
    Transcript show:t; show:' seconds for '; show:(50*n/1024) asFloat; showCR:' Kb'.
    Transcript show:(n*50/1024 / t); showCR:' Kb/s'
                                                                [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"

    | argSize "{ Class:SmallInteger }"
      byte    "{ Class:SmallInteger }" |

%{
#if 1
    unsigned char *cp;
    int n;
    unsigned char c;

    if (__isStringLike(arg)) {
        cp = __stringVal(arg);
        n = __stringSize(arg);
        goto doBytes;
    }

    if (__isByteArrayLike(arg)) {
        cp = __byteArrayVal(arg);
        n = __byteArraySize(arg);
    doBytes:
        {
            unsigned int _crc;
            unsigned int *_crcTable;

            if (__isSmallInteger(__INST(crc)) ) {
                _crc = (unsigned) (__intVal( __INST(crc) ));
            } else {
                _crc = __unsignedLongIntVal( __INST(crc) );
            }

            _crcTable = __integerArrayVal( @global(CrcTable) );

            while (n > 3) {
                unsigned _idx;

                _idx = (_crc ^ cp[0]) & 0xFF;
                _crc = _crcTable[_idx] ^ (_crc >> 8);
                _idx = (_crc ^ cp[1]) & 0xFF;
                _crc = _crcTable[_idx] ^ (_crc >> 8);
                _idx = (_crc ^ cp[2]) & 0xFF;
                _crc = _crcTable[_idx] ^ (_crc >> 8);
                _idx = (_crc ^ cp[3]) & 0xFF;
                _crc = _crcTable[_idx] ^ (_crc >> 8);
                cp += 4;
                n -= 4;
            }
            while (n > 0) {
                unsigned _byte = *cp++;
                unsigned _idx;

                _idx = (_crc ^ _byte) & 0xFF;
                _crc = _crcTable[_idx] ^ (_crc >> 8);
                n--;
            }
            __INST(crc) = __MKUINT(_crc);
        }
        RETURN (self );
    }
    if (__isCharacter(arg)) {
        unsigned int value;

        value = __intVal(_characterVal(arg));
        if ((unsigned)value <= 0xFF) {
            c = value;
            cp = &c;
            n = 1;
            goto doBytes;
        }
    }
#endif
%}.
    arg isByteCollection ifTrue:[
        argSize := arg size.
        1 to:argSize do:[:n|
            byte := arg byteAt:n.
            crc := (CrcTable at:((crc bitXor:byte) bitAnd:16rFF)+1) 
                   bitXor:(crc bitShift:-8).
        ].
        ^ self.
    ].

    arg isCharacter ifTrue:[
        byte := arg codePoint.
        byte < 256 ifTrue:[
            crc := (CrcTable at:((crc bitXor:byte) bitAnd:16rFF)+1) 
                   bitXor:(crc bitShift:-8).
            ^ self.
        ].
        byte digitBytes do:[:eachByte|
            crc := (CrcTable at:((crc bitXor:eachByte) 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:[:eachByte|
            crc := (CrcTable at:((crc bitXor:eachByte) bitAnd:16rFF)+1) 
                   bitXor:(crc bitShift:-8).
        ].
        ^ self.
    ].

    arg isCollection ifTrue:[
        arg do:[:eachElement|
            self nextPut:eachElement
        ].
        ^ self.
    ].

    self error:'unsupported argument'.
! !

!CRC32Stream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/CRC32Stream.st,v 1.13 2011-05-10 14:27:15 stefan Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic2/CRC32Stream.st,v 1.13 2011-05-10 14:27:15 stefan Exp $'
! !

CRC32Stream initialize!