CRC8Stream.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 4919 1594f0a70c62
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) 2019 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:#CRC8Stream
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'System-Crypt-Hashing'
!

!CRC8Stream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2019 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
"
    ATTENTION: CRC8Stream is currently BROKEN (in development)

    newSAE_J1850:
      Standard CRC method as defined by SAE J1850 (used in AUTOSAR)
      The polynomial is 0x1D; initial value 0xFF; xorOut is 0xFF
      
    [author:]
        Claus Gittinger

    [instance variables:]

    [class variables:]

    [see also:]
        SHA1Stream
        MD5Stream

"
!

examples
"
  expect xxx:
                                                                [exBegin]
    self information:(CRC8Stream new 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]

"
! !

!CRC8Stream class methodsFor:'instance creation'!

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

    ^ self generatorPolynom:(anInteger bitReversed8)

    "Created: / 16-03-2019 / 20:58:49 / Claus Gittinger"
    "Modified: / 24-03-2019 / 12:15:05 / Claus Gittinger"
!

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

    ^ self generatorPolynom:(anInteger bitReversed8) initValue:initValue

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

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

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

    "Created: / 16-03-2019 / 21:29:04 / Claus Gittinger"
    "Modified: / 24-03-2019 / 12:15:13 / Claus Gittinger"
!

newSAE_J1850
    "return an instance of the SAE_J1850 CRC8 (used in AUTOSAR)"
    
    self error:'currently broken'.    
    ^ self generatorPolynomMSB:16r1D initValue:16rFF xorOut:16rFF

    "Created: / 24-03-2019 / 11:34:16 / Claus Gittinger"
    "Modified: / 25-03-2019 / 14:27:48 / Claus Gittinger"
!

new_2F
    "return an instance of the CRC8-2F (used in AUTOSAR).
     Currently broken."

    self error:'currently broken'.    
    ^ self generatorPolynom:16r2F initValue:16rFF xorOut:16rFF

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

!CRC8Stream class methodsFor:'queries'!

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

    ^ 1

    "Created: / 24-03-2019 / 12:52:58 / Claus Gittinger"
! !

!CRC8Stream methodsFor:'initialization'!

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

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

    "Modified: / 24-03-2019 / 11:30:56 / Claus Gittinger"
!

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

    self generatorPolynom:anLSBInteger 
         initValue:initValueArg xorOut:16rFF

    "Created: / 16-03-2019 / 21:24:03 / Claus Gittinger"
    "Modified: / 24-03-2019 / 11:31:06 / Claus Gittinger"
! !

!CRC8Stream methodsFor:'queries'!

hashValue
    "return the computed CRC"

    ^ super hashValue bitAnd:16rFF

    "Created: / 24-03-2019 / 12:08:33 / Claus Gittinger"
! !

!CRC8Stream class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !