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

"{ Encoding: utf8 }"

"
 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' }"

"{ NameSpace: Smalltalk }"

CRCStream subclass:#CRC16Stream
	instanceVariableNames:'byteSwapped'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Crypt-Hashing'
!

!CRC16Stream 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
"
     Only use CRC to protect against communication errors;
     DO NOT use CRC for cryptography, authentication, security, etc.
     - use secure hashes for those instead.

    ATTENTION: CRC16Stream is currently BROKEN (in development)

    crc16 is a full zoo of different implementations;
    they differ in the polynom, the initial value and the final xor value.
    Also, some return an MSB, others an LSB first value (i.e. byteswapped).
    Make sure to use the correct one:
    
    newCRC_CCITT:
      Standard CRC method as defined by CCITT with FFFF as start value 
      (ITU-T-T30, ITU-T V42, ITU-T X25, RFC1331, RFC1662, ISO/IEC FCD14443-3).
      This is used in data link protocols such as HDLC, SS7, and ISDN.
    
      The polynomial is
        x^16 + x^12 + x^5 + 1

    newCRC_DNP:
      Standard CRC method as defined by DNP.
      This is used in data link protocols such as HDLC, SS7, and ISDN.
      DNP 3.0, or distributed network protocol is a communication protocol 
      designed for use between substation computers, RTUs remote terminal units, 
      IEDs intelligent electronic devices 
      and master stations for the electric utility industry. 
      It is now also used in familiar industries like waste water treatment, 
      transportation and the oil and gas industry.
      The polynomial is 0x3d65

    newKERMIT:
      CRC as used in kermit protocol

    newMODBUS:
      CRC as used in the modbus protocol
      
    [author:]
        Claus Gittinger

    [instance variables:]

    [class variables:]

    [see also:]
        SHA1Stream
        MD5Stream

"
!

examples
"
  expect xxx:
                                                                [exBegin]
    self information:(CRC16Stream hashValueOf:'resume') hexPrintString
                                                                [exEnd]

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

  expect xxx:
                                                                [exBegin]
    self information:(CRC16Stream hashValueOf:#[1 2 3 4 5 6 7]) hexPrintString
                                                                [exEnd]

  expect xxx:
                                                                [exBegin]
    self information:((CRC16Stream 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]) hexPrintString)
                                                                [exEnd]

  expect xxx:
  timing throughput:
                                                                [exBegin]
    |hashStream n t|

    hashStream := CRC16Stream new.
    n := 1000000.
    t := Time millisecondsToRun:[
            n timesRepeat:[
                hashStream nextPutAll:'12345678901234567890123456789012345678901234567890'.
            ].
         ].
    t := (t / 1000) asFloat.
    Transcript show:'crc16:'; showCR: hashStream hashValue hexPrintString.
    Transcript show:t; show:' seconds for '; show:(50*n/1024) asFloat; showCR:' Kb'.
    Transcript show:(n*50/1024 / t); showCR:' Kb/s'
                                                                [exEnd]

"
! !

!CRC16Stream class methodsFor:'instance creation'!

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

    ^ self generatorPolynom:(anInteger bitReversed16)

    "Created: / 16-03-2019 / 20:58:49 / Claus Gittinger"
!

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

    ^ self generatorPolynom:(anInteger bitReversed16) initValue:initValue

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

generatorPolynomMSB:anInteger initValue:initValueArg xorOut:xorOut
    "notice, in literature, the generator polynom is usually specified as an MSB number"

    ^ self generatorPolynom:(anInteger bitReversed16) initValue:initValueArg xorOut:xorOut

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

new
    "return an instance of the CCITT CRC-16"

    ^ self newCCITT

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

newCCITT
    "return an instance of the CCITT CRC-16 with FFFF as initial value
        x16 + x12 + x5 + 1 "

    "/ 16r1021 bitReversed16 => 16r8408
    self error:'currently broken'.
    ^ self generatorPolynomMSB:16r1021 initValue:16rFFFF xorOut:0

    "Created: / 16-03-2019 / 21:13:11 / Claus Gittinger"
    "Modified: / 25-03-2019 / 14:32:39 / Claus Gittinger"
!

newCCITT_1D0F
    "return an instance of the CCITT CRC-16 with 1D0F as initial value
        x16 + x12 + x5 + 1 "

    "/ 16r1021 bitReversed16 => 16r8408
    self error:'currently broken'.
    ^ self generatorPolynomMSB:16r1021 initValue:16r1D0F xorOut:0

    "Created: / 24-03-2019 / 20:57:32 / Claus Gittinger"
    "Modified: / 25-03-2019 / 14:33:05 / Claus Gittinger"
!

newCRC_16
    "return an instance of the CRC-16
        x16 + x15 + x2 + 1 "

    "/ 16r8005 bitReversed16 => 16rA001
    self error:'currently broken'.
    ^ self generatorPolynomMSB:16rA001 initValue:0 xorOut:16rFFFF

    "Created: / 17-03-2019 / 13:59:52 / Claus Gittinger"
    "Modified: / 25-03-2019 / 14:32:06 / Claus Gittinger"
!

newDNP
    "return an instance of the DNP CRC-16
        x16 + x13 + x12 + x11 + x10 + x8 + x6 + x5 + x2 + 1

     DNP 3.0, or distributed network protocol is a communication protocol 
     designed for use between substation computers, RTUs remote terminal units, 
     IEDs intelligent electronic devices 
     and master stations for the electric utility industry. 
     It is now also used in familiar industries like waste water treatment, 
     transportation and the oil and gas industry."

    "/ 16r3d65 bitReversed16 hexPrintString -> 'A6BC'
    ^ (self generatorPolynom:16rA6BC initValue:0 xorOut:16rFFFF) byteSwapped:true

    "Created: / 16-03-2019 / 20:50:03 / Claus Gittinger"
    "Modified: / 24-03-2019 / 21:17:58 / Claus Gittinger"
!

newKERMIT
    "return an instance of the CRC-16 used by kermit
        2r11110101100101
        x16 + x13 + x12 + x11 + x10 + x8 + x6 + x5 + x2 + 1 "

    "/ 16r1021 bitReversed16 => 16r8408
    ^ (self generatorPolynomMSB:16r1021 initValue:0 xorOut:0) byteSwapped:true

    "Created: / 17-03-2019 / 13:51:20 / Claus Gittinger"
    "Modified: / 24-03-2019 / 20:10:31 / Claus Gittinger"
!

newMODBUS
    "return an instance of the MODBUS CRC-16
        x16 + x15 + x2 + 1 "

    "/ 16r8005 bitReversed16 => 16rA001
    ^ self generatorPolynom:16rA001 initValue:16rFFFF xorOut:0

    "Created: / 17-03-2019 / 14:22:41 / Claus Gittinger"
    "Modified: / 24-03-2019 / 20:08:41 / Claus Gittinger"
!

newXMODEM
    "return an instance of the XMODEM protocol
        x16 + x12 + x5 + 1
        1 2r0001000000100001 "
        
    self error:'currently broken'.
    ^ self generatorPolynom:16r1021 initValue:0 xorOut:0
    "/ ^ self generatorPolynomMSB:16r1021 initValue:0 xorOut:0

    "Created: / 24-03-2019 / 20:16:08 / Claus Gittinger"
    "Modified: / 25-03-2019 / 14:31:41 / Claus Gittinger"
! !

!CRC16Stream class methodsFor:'queries'!

hashSize
    "return the size of the hashvalue returned by instances of this class (in bytes)"

    ^ 2

    "Created: / 24-03-2019 / 12:53:05 / Claus Gittinger"
! !

!CRC16Stream methodsFor:'initialization'!

byteSwapped
    ^ byteSwapped ? false

    "Created: / 24-03-2019 / 20:10:12 / Claus Gittinger"
!

byteSwapped:aBoolean
    byteSwapped := aBoolean

    "Created: / 24-03-2019 / 20:10:01 / Claus Gittinger"
!

generatorPolynom:anLSBInteger
    "set the generator polynom for this instance,
     set start and xorOut to 16rFFFF.
     Note: you have to set the bit-reversed value, so the LSB must be first"

    self generatorPolynom:anLSBInteger 
         initValue:16rFFFF xorOut:16rFFFF.

    "Modified: / 16-03-2019 / 21:24:35 / Claus Gittinger"
    "Modified (format): / 17-03-2019 / 14:02:47 / Claus Gittinger"
!

generatorPolynom:anLSBInteger initValue:initValueArg
    "set the generator polynom for this instance.
     set start to initValueArg and xorOut to 16rFFFF.
     Note: you have to set the bit-reversed value, so the LSB must be first"

    self generatorPolynom:anLSBInteger 
         initValue:initValueArg xorOut:16rFFFF

    "Created: / 16-03-2019 / 21:24:03 / Claus Gittinger"
    "Modified (format): / 17-03-2019 / 14:02:57 / Claus Gittinger"
! !

!CRC16Stream methodsFor:'queries'!

hashValue
    "return the computed CRC.
     For unknown reasons, the standard crc16 needs byte swapping"

    |hv|

    hv := super hashValue.
    (byteSwapped == true) ifTrue:[
        ^ hv byteSwapped16
    ].    
    ^ hv.

    "Created: / 17-03-2019 / 13:45:29 / Claus Gittinger"
    "Modified: / 24-03-2019 / 20:11:49 / Claus Gittinger"
! !

!CRC16Stream class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !