CRC16Stream.st
author Claus Gittinger <cg@exept.de>
Sat, 16 Mar 2019 23:30:18 +0100
changeset 4858 8ba5358392d2
parent 4848 320b11a3048f
child 4861 7a69e6afd632
permissions -rw-r--r--
#DOCUMENTATION by cg class: CRC16Stream removed: #nextPutBytes:from:startingAt: class: CRC16Stream class comment/format in: #newCCITT

"{ 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:''
	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
"
    newCRC_CCITT:
      Standard CRC method as defined by CCITT 
      (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 default 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.

      The default polynomial is 0x3d65


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

    [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
        2r11110101100101
        x16 + x13 + x12 + x11 + x10 + x8 + x6 + x5 + x2 + 1 "

    "/ 16r1021 bitReversed16 => 16r8408
    ^ self generatorPolynomMSB:16r1021 initValue:16rFFFF xorOut:16rFFFF

    "Created: / 16-03-2019 / 21:13:11 / Claus Gittinger"
    "Modified (format): / 16-03-2019 / 23:08:57 / Claus Gittinger"
!

newDNP
    "return an instance of the DNP CRC-16
        2r11110101100101
          3210 8 65  2 0
        x16 + x13 + x12 + x11 + x10 + x8 + x6 + x5 + x2 + 1 "

    ^ self generatorPolynomMSB:16r3d65 initValue:0 xorOut:16rFFFF

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

newModbus
    "return an instance of the Modbus CRC-16
        2r11110101100101
          3210 8 65  2 0
        x16 + x13 + x12 + x11 + x10 + x8 + x6 + x5 + x2 + 1 "

    ^ self generatorPolynomMSB:16r8005 initValue:16rFFFF xorOut:0

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

!CRC16Stream methodsFor:'initialization'!

generatorPolynom:anInteger
    "set the generator polynom for this instance.
     Note: you have to set the bit-reversed value, so the LSB must be first"

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

    "Modified: / 16-03-2019 / 21:24:35 / Claus Gittinger"
!

generatorPolynom:anInteger initValue:initValueArg
    "set the generator polynom for this instance.
     Note: you have to set the bit-reversed value, so the LSB must be first"

    self generatorPolynom:anInteger initValue:initValueArg xorOut:16rFFFF

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

!CRC16Stream class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !