CRCStream.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 5381 91f4a33eddd5
permissions -rw-r--r--
#FEATURE by cg class: Socket class added: #newTCPclientToHost:port:domain:domainOrder:withTimeout: changed: #newTCPclientToHost:port:domain:withTimeout:

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

"{ NameSpace: Smalltalk }"

HashStream subclass:#CRCStream
	instanceVariableNames:'crc generatorPolynom crcTable initValue xorOut'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Crypt-Hashing'
!

CRCStream class instanceVariableNames:'crcTables'

"
 No other class instance variables are inherited by this class.
"
!

!CRCStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2018 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
"
    abstract superclass of crc streams;
    refactored from original crc32 stream.
    For details, see https://en.wikipedia.org/wiki/Cyclic_redundancy_check

    Only use CRC to protect against communication errors;
    DO NOT use CRC for cryptography, authentication, security, etc.
    - use secure hashes for those instead.

    [parameters:] 
        polynomials:
            CRC_POLY_16             0xA001
            CRC_POLY_32             0xEDB88320L
            CRC_POLY_CCITT          0x1021
            CRC_POLY_DNP            0xA6BC
            CRC_POLY_KERMIT         0x8408

        start values:
            CRC_START_8             0x00
            CRC_START_16            0x0000
            CRC_START_MODBUS        0xFFFF
            CRC_START_XMODEM        0x0000
            CRC_START_CCITT_1D0F    0x1D0F
            CRC_START_CCITT_FFFF    0xFFFF
            CRC_START_KERMIT        0x0000
            CRC_START_SICK          0x0000
            CRC_START_DNP           0x0000
            CRC_START_32            0xFFFFFFFF

"
! !

!CRCStream class methodsFor:'initialization'!

crcTableFor:generatorPolynomInteger
    "construct the polynom-specific lookup table"
    
    |crcTable|

    "/ CRC8Stream flushCrcTables
    "/ CRC8Stream crcTableFor:(16r1D bitReversed8)
    
    crcTables isNil ifTrue:[
        crcTables := Dictionary new
    ].    
    crcTable := (crcTables at:generatorPolynomInteger ifAbsent:nil).
    crcTable isNil ifTrue:[
        "/ for crc16 and crc8, we waste some memory 
        "/ (could use WordArray or ByteArray);
        "/ but that would need three writeBytes implementations.
        "/ Not worth the saving.
        crcTable := IntegerArray new:256.

        "/ least-sign. bit towards most significant bit...
        0 to:255 do:[:count| |i|
            i := count.
            8 timesRepeat:[
                (i bitTest:1) ifTrue:[
                    i := generatorPolynomInteger bitXor:(i bitShift:-1)
                ] ifFalse:[
                    i := i bitShift:-1
                ]
            ].
            crcTable at:count+1 put:i.
        ].
        crcTables at:generatorPolynomInteger put:crcTable.
    ].
    ^ crcTable.

    "Created: / 16-03-2019 / 20:53:51 / Claus Gittinger"
    "Modified: / 24-03-2019 / 12:38:12 / Claus Gittinger"
!

flushCrcTables
    crcTables := nil.

    "
     CRC16Stream flushCrcTables
     CRC32Stream flushCrcTables
    "

    "Created: / 16-03-2019 / 23:41:19 / Claus Gittinger"
! !

!CRCStream class methodsFor:'instance creation'!

generatorPolynom:anLSBInteger
    "notice, in literature, the generator polynom is usually specified as an MSB number"

    ^ self basicNew 
        generatorPolynom:anLSBInteger

    "
       self assert:((self generatorPolynom:16r82F63B78)
                                nextPut:'123456789';
                                hashValue)    = 16rE3069283
    "

    "Modified (format): / 17-03-2019 / 14:03:42 / Claus Gittinger"
!

generatorPolynom:anLSBInteger initValue:initValue
    "notice, in literature, the generator polynom is usually specified as an MSB number"

    ^ self basicNew 
        generatorPolynom:anLSBInteger 
        initValue:initValue

    "
       self assert:((self generatorPolynom:16r82F63B78)
                                nextPut:'123456789';
                                hashValue)    = 16rE3069283
    "

    "Created: / 16-03-2019 / 21:15:54 / Claus Gittinger"
    "Modified (format): / 17-03-2019 / 14:03:37 / Claus Gittinger"
!

generatorPolynom:anLSBInteger initValue:initValue xorOut:xorOut
    "notice, in literature, the generator polynom is usually specified as an MSB number"

    ^ self basicNew 
        generatorPolynom:anLSBInteger 
        initValue:initValue xorOut:xorOut

    "
       self assert:((self generatorPolynom:16r82F63B78)
                                nextPut:'123456789';
                                hashValue)    = 16rE3069283
    "

    "Created: / 16-03-2019 / 21:16:05 / Claus Gittinger"
    "Modified (format): / 17-03-2019 / 14:03:30 / Claus Gittinger"
! !

!CRCStream methodsFor:'accessing'!

generatorPolynom
    "answer the generator polynom (LSB)"

    ^ generatorPolynom

    "Modified (comment): / 16-03-2019 / 20:58:10 / Claus Gittinger"
!

initValue
    "answer the init value"

    ^ initValue ? 0

    "Created: / 16-03-2019 / 21:05:04 / Claus Gittinger"
!

xorOut
    "answer the xorOut value"

    ^ xorOut ? 16rFFFFFFFF

    "Created: / 16-03-2019 / 21:16:23 / Claus Gittinger"
! !

!CRCStream methodsFor:'initialization'!

generatorPolynom:polyLSB initValue:initValueArg xorOut:xorOutArg
    "set the generator polynom for this instance.
     And set start and xorOut.
     Computes the crcTable for this polynom.
     Notice the bit order is LSB"

    generatorPolynom := polyLSB.
    crc := initValue := initValueArg.
    xorOut := xorOutArg.

    crcTable := self class crcTableFor:generatorPolynom.

    "Created: / 16-03-2019 / 21:17:12 / Claus Gittinger"
    "Modified (comment): / 17-03-2019 / 12:25:11 / Claus Gittinger"
!

reset
    "reset the current crc value"

    crc := initValue.

    "Created: / 16-03-2019 / 21:25:27 / Claus Gittinger"
! !

!CRCStream methodsFor:'queries'!

hashValue
    "return the computed CRC"

    ^ crc bitXor:xorOut.

    "Modified: / 16-03-2019 / 21:27:59 / Claus Gittinger"
! !

!CRCStream methodsFor:'writing'!

nextPutBytes:count from:anObject startingAt:start
    "add the hash of anObject to the computed hash so far."

%{
    int len, offs;

    // fetch first - check later
    len = __intVal(count);
    offs = __intVal(start) - 1;

    if (__bothSmallInteger(count, start)) {
        int objSize;
        unsigned char *extPtr;

        // the most common first
        if (__isStringLike(anObject)) {
            objSize = __stringSize(anObject);
            extPtr = (unsigned char *)__stringVal(anObject);
        } else if (__isByteArray(anObject)) {
            objSize = __byteArraySize(anObject);
            extPtr = (unsigned char *)__byteArrayVal(anObject);
        } else if (__isExternalBytesLike(anObject)) {
            OBJ sz = __externalBytesSize(anObject);

            extPtr = (unsigned char *)__externalBytesAddress(anObject);
            if (__isSmallInteger(sz)) {
                objSize = __intVal(sz);
            } else {
                objSize = 0; /* unknown */
            }
        } else {
            int nInstVars, nInstBytes;
            OBJ oClass = __Class(anObject);

            switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
                case BYTEARRAY:
                case WORDARRAY:
                case LONGARRAY:
                case SWORDARRAY:
                case SLONGARRAY:
                case FLOATARRAY:
                case DOUBLEARRAY:
                    break;
                default:
                    goto bad;
            }
            nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
            nInstBytes = __OBJS2BYTES__(nInstVars);
            // nInstBytes is the number of bytes occupied by pointer instance variables
            // subtract from size and add to byte-pointer
            objSize = __qSize(anObject) - OHDR_SIZE - nInstBytes;
            extPtr = (unsigned char *)__byteArrayVal(anObject)+nInstBytes;
        }

        if ((offs >= 0) && (len >= 0) && (objSize >= (len + offs))) {
            unsigned int _crc;
            unsigned int *_crcTable = __integerArrayVal( __INST(crcTable) );
            unsigned char *cp = extPtr+offs;
            unsigned int n = len;

            _crc = (unsigned int) (__intVal( __INST(crc) ));
#if __POINTER_SIZE__ != 8
            if (!__isSmallInteger(__INST(crc))) {
                _crc = __unsignedLongIntVal( __INST(crc) );
            }
#endif

#ifdef __LSBFIRST__
# if __POINTER_SIZE__ == 8
            if (((unsigned INT)cp & 7) == 0) {
                // longword aligned
                for ( ; n >= 8 ; n -= 8, cp += 8) {
                    unsigned INT lWord;
                    unsigned char _idx;

                    lWord = ((unsigned INT *)cp)[0];
                    _idx = (_crc ^ lWord) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (lWord>>8)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (lWord>>16)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (lWord>>24)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    
                    _idx = (_crc ^ (lWord>>32)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (lWord>>40)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (lWord>>48)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (lWord>>56)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                }
            }
# endif // __POINTER_SIZE__ == 8          
            if (((unsigned INT)cp & 3) == 0) {
                // word aligned
                for ( ; n >= 4 ; n -= 4, cp += 4) {
                    unsigned int word;
                    unsigned char _idx;

                    word = ((unsigned int *)cp)[0];
                    _idx = (_crc ^ word) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (word>>8)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (word>>16)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                    _idx = (_crc ^ (word>>24)) & 0xFF;
                    _crc = _crcTable[_idx] ^ (_crc >> 8);
                }
            }
#endif // LSBFIRST
            for ( ; n >= 4 ; n -= 4, cp += 4) {
                unsigned char _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);
            }
            while (n-- > 0) {
                unsigned char _idx = (_crc ^ *cp++) & 0xFF;
                _crc = _crcTable[_idx] ^ (_crc >> 8);
            }

#if __POINTER_SIZE__ == 8
            __INST(crc) = __MKSMALLINT(_crc);
#else
            if (_crc <= _MAX_INT) {
                __INST(crc) = __MKSMALLINT(_crc);
            } else {
                // this code fails with gcc 4.7.2:
                // __INST(crc) = __MKUINT(_crc); __STORESELF(crc);
                OBJ temp = __MKUINT(_crc); 
                __INST(crc) = temp; __STORESELF(crc);
            }
#endif
            RETURN (count);
        }
    }
bad: ;
%}.
    ArgumentError raise

    "Created: / 09-01-2012 / 16:48:35 / cg"
    "Modified: / 06-06-2019 / 23:16:48 / Claus Gittinger"
! !

!CRCStream class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !