CRC32Stream.st
changeset 4845 36770d6f14bf
parent 4238 ab8390ef187a
child 4847 c76689ab85bf
--- a/CRC32Stream.st	Sat Mar 16 21:41:56 2019 +0100
+++ b/CRC32Stream.st	Sat Mar 16 21:42:14 2019 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2003 by eXept Software AG
 	      All Rights Reserved
@@ -13,9 +15,9 @@
 
 "{ NameSpace: Smalltalk }"
 
-HashStream subclass:#CRC32Stream
-	instanceVariableNames:'crc generatorPolynom crcTable'
-	classVariableNames:'CrcTables'
+CRCStream subclass:#CRC32Stream
+	instanceVariableNames:''
+	classVariableNames:''
 	poolDictionaries:''
 	category:'System-Crypt-Hashing'
 !
@@ -44,12 +46,13 @@
         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 16r04C11DB7)
 
-    You can also create an instace performing the Castagnioli CRC-32C
-    (used in iSCSI & SCTP, G.hn payload, SSE4.2):
+    You can also create an instace performing the Castagnioli CRC-32C 
+    (used in iSCSI & SCTP [RFC3720], G.hn payload, SSE4.2):
 
         self newCrc32c
 
-        x32 + x28 + x27 + x26 + x25 + x23 + x22 + x20 + x19 + x18 + x14 + x13 + x11 + x10 + x9 + x8 + x6 + 1
+        poly: 16r1edc6f41
+        = x32 + x28 + x27 + x26 + x25 + x23 + x22 + x20 + x19 + x18 + x14 + x13 + x11 + x10 + x9 + x8 + x6 + 1
 
     Only use CRC to protect against communication errors;
     do NOT use CRC for cryptography - use SHA1Stream or MD5Stream instead.
@@ -109,7 +112,6 @@
              16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF]) hexPrintString)
                                                                 [exEnd]
 
-  expect 16r86D7D79A:
   timing throughput:
                                                                 [exBegin]
     |hashStream n t|
@@ -127,112 +129,120 @@
     Transcript show:(n*50/1024 / t); showCR:' Kb/s'
                                                                 [exEnd]
 
-"
-! !
-
-!CRC32Stream class methodsFor:'initialization'!
-
-crcTableFor:generatorPolynomInteger
-    |crcTable|
-
-    crcTable := (CrcTables at:generatorPolynomInteger ifAbsent:nil).
-    crcTable isNil ifTrue:[
-	crcTable := IntegerArray new:256.
+  test vectors from https://tools.ietf.org/html/rfc3720#page-217:
+  
+  expect 0
+                                                                [exBegin]
+    self information:(CRC32Stream newCrc32c hashValueOf:'') hexPrintString
+                                                                [exEnd]
+  expect C1D04330
+                                                                [exBegin]
+    self information:(CRC32Stream newCrc32c hashValueOf:'a') hexPrintString
+                                                                [exEnd]
+  expect E3069283
+                                                                [exBegin]
+    self information:(CRC32Stream newCrc32c hashValueOf:'123456789') hexPrintString
+                                                                [exEnd]
+  expect 8A9136AA
+                                                                [exBegin]
+    self information:(CRC32Stream newCrc32c hashValueOf:(ByteArray new:32 withAll:0)) hexPrintString
+                                                                [exEnd]
+  expect 62a8ab43
+                                                                [exBegin]
+    self information:(CRC32Stream newCrc32c hashValueOf:(ByteArray new:32 withAll:16rFF)) hexPrintString
+                                                                [exEnd]
+  expect 46dd794e
+                                                                [exBegin]
+    self information:(CRC32Stream newCrc32c hashValueOf:(0 to:31) asByteArray) hexPrintString
+                                                                [exEnd]
 
-	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.
-!
-
-initialize
-    CrcTables := Dictionary new.
+"
 ! !
 
 !CRC32Stream class methodsFor:'instance creation'!
 
-generatorPolynom:anInteger
-    ^ self basicNew generatorPolynom:anInteger
+generatorPolynomMSB:anInteger
+    "notice, in literature, the generator polynom is usually specified as an MSB number"
+    
+    ^ self generatorPolynom:(anInteger bitReversed32)
 
     "
        self assert:((self generatorPolynom:16r82F63B78)
-				nextPut:'123456789';
-				hashValue)    = 16rE3069283
+                                nextPut:'123456789';
+                                hashValue)    = 16rE3069283
     "
+
+    "Created: / 16-03-2019 / 20:55:46 / Claus Gittinger"
+!
+
+generatorPolynomMSB:anInteger initValue:initValueArg
+    "notice, in literature, the generator polynom is usually specified as an MSB number"
+    
+    ^ self generatorPolynom:(anInteger bitReversed32) initValue:initValueArg
+
+    "Created: / 16-03-2019 / 21:11:31 / Claus Gittinger"
+!
+
+generatorPolynomMSB:anInteger initValue:initValueArg xorOut:xorOut
+    "notice, in literature, the generator polynom is usually specified as an MSB number"
+    
+    ^ self generatorPolynom:(anInteger bitReversed32) initValue:initValueArg xorOut:xorOut
+
+    "Created: / 16-03-2019 / 21:21:27 / Claus Gittinger"
+!
+
+new
+    "return an instance of the ITU-T CRC-32
+        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"
+
+    "/ 16r4C11DB7 bitReversed32 -> 16rEDB88320
+    ^ self generatorPolynom:16rEDB88320 initValue:16rFFFFFFFF xorOut:16rFFFFFFFF
+
+    "Created: / 16-03-2019 / 21:09:19 / Claus Gittinger"
 !
 
 newCrc32c
     "return an instance of the Castagnoli CRC-32
-	x32 + x28 + x27 + x26 + x25 + x23 + x22 + x20 + x19 + x18 + x14 + x13 + x11 + x10 + x9 + x8 + x6 + 1
+        x32 + x28 + x27 + x26 + x25 + x23 + x22 + x20 + x19 + x18 + x14 + x13 + x11 + x10 + x9 + x8 + x6 + 1
      (used in iSCSI & SCTP, G.hn payload, SSE4.2)"
 
-    ^ self basicNew generatorPolynom:16r82F63B78
+    "/ 16r1edc6f41 bitReversed32 -> 16r82F63B78
+    ^ self generatorPolynom:16r82F63B78 initValue:16rFFFFFFFF xorOut:16rFFFFFFFF
 
     "
      Castagnoli crc:
        self assert:((self newCrc32c)
-				nextPut:'123456789';
-				hashValue) = 3808858755. '16rE3069283'
+                                nextPut:'123456789';
+                                hashValue) = 3808858755. '16rE3069283'
 
      default crc:
        self assert:((self new)
-				nextPut:'123456789';
-				hashValue) = 3421780262. '16rCBF43926'
+                                nextPut:'123456789';
+                                hashValue) = 3421780262. '16rCBF43926'
     "
 
     "Modified (comment): / 17-05-2012 / 12:48:53 / cg"
+    "Modified: / 16-03-2019 / 21:21:07 / Claus Gittinger"
 ! !
 
-!CRC32Stream methodsFor:'accessing'!
-
-generatorPolynom
-    "answer the generator polynom"
-
-    ^ generatorPolynom
-!
+!CRC32Stream 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"
 
-    generatorPolynom := anInteger.
-    crc := 16rFFFFFFFF.
-    crcTable := self class crcTableFor:generatorPolynom.
+    self generatorPolynom:anInteger initValue:16rFFFFFFFF xorOut:16rFFFFFFFF.
+
+    "Modified: / 16-03-2019 / 21:23:25 / Claus Gittinger"
 !
 
-reset
-    "reset the current crc value"
-
-    crc := 16rFFFFFFFF.
-
-    "Created: / 12-01-2012 / 12:23:03 / cg"
-! !
-
-!CRC32Stream methodsFor:'initialization'!
+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"
 
-initialize
-    "initialize the CRC to CRC-32 ITU-T:
-	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"
-
-    self generatorPolynom:16rEDB88320
-! !
+    self generatorPolynom:anInteger initValue:initValueArg xorOut:16rFFFFFFFF
 
-!CRC32Stream methodsFor:'queries'!
-
-hashValue
-    "return the computed CRC"
-
-    ^ crc bitXor:16rFFFFFFFF.
+    "Created: / 16-03-2019 / 21:06:16 / Claus Gittinger"
 ! !
 
 !CRC32Stream methodsFor:'writing'!
@@ -295,6 +305,34 @@
             }
 
 #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            
             if (((unsigned INT)cp & 3) == 0) {
                 // word aligned
                 for ( ; n >= 4 ; n -= 4, cp += 4) {
@@ -348,6 +386,7 @@
     self error:'invalid argument'
 
     "Created: / 09-01-2012 / 16:48:35 / cg"
+    "Modified: / 16-03-2019 / 21:40:02 / Claus Gittinger"
 ! !
 
 !CRC32Stream class methodsFor:'documentation'!
@@ -360,5 +399,3 @@
     ^ '$Header$'
 ! !
 
-
-CRC32Stream initialize!