Calculating 32-bit CRCs (CRC-32) |
MDFS::Info.Comp.Comms.CRC32/htm | Search |
The ZIP CRC is CRC-32 with a start value of &FFFFFFFF, the end value is XORed with &FFFFFFFF, and uses a polynomic of &EDB88320. These three values can be changed to create code to generate other varients of CRC-32. CRC32 is BBC BASIC test code with BASIC, 6502, Z80, 80x86 and ARM code.
/* Calculating ZIP CRC-32 in 'C' ============================= Reference model for the translated code */ #define poly 0xEDB88320 /* Some compilers need #define poly 0xEDB88320uL */ /* On entry, addr=>start of data num = length of data crc = incoming CRC */ int crc32(char *addr, int num, int crc) { int i; for (; num>0; num--) /* Step through bytes in memory */ { crc = crc ^ *addr++; /* Fetch byte from memory, XOR into CRC */ for (i=0; i<8; i++) /* Prepare to rotate 8 bits */ { if (crc & 1) /* b0 is set... */ crc = (crc >> 1) ^ poly; /* rotate and XOR with ZIP polynomic */ else /* b0 is clear... */ crc >>= 1; /* just rotate */ /* Some compilers need: crc &= 0xFFFFFFFF; */ } /* Loop for 8 bits */ } /* Loop until num=0 */ return(crc); /* Return updated CRC */ }
REM crc% = incoming CRC REM start%=>start of data REM num% = number of bytes : FOR addr%=start% TO start%+num%-1 crc%=crc% EOR ?addr% :REM EOR with current byte FOR bit%=1 TO 8 :REM Loop through 8 bits old%=crc% crc%=(((crc%+(crc%<0))DIV2)AND&7FFFFFFF) :REM Move crc% down one bit REM The above is the same as crc%=crc% >>> 1 in BASIC V. IF old% AND 1:crc%=crc% EOR &EDB88320 :REM EOR with ZIP polynomic NEXT bit% NEXT addr% : REM crc% = outgoing CRCThe following is a highly crunched and speeded up version:
FORA%=mem%TOmem%+num%-1:S%=S%EOR?A%:FORB%=1TO8:O%=S%:S%=(((S%+(S%<0))DIV2)AND&7FFFFFFF):IFO%AND1:S%=S%EOR&EDB88320 NEXT:NEXT
\ Calculating ZIP CRC-32 in 6502 \ ============================== \ Calculate a ZIP 32-bit CRC from data in memory. This code is as \ tight and as fast as it can be, moving as much code out of inner \ loops as possible. \ \ On entry, crc..crc+3 = incoming CRC \ addr..addr+1 => start of data \ num..num+1 = number of bytes \ On exit, crc..crc+3 = updated CRC \ addr..addr+1 => end of data+1 \ num..num+1 = 0 \ \ Multiple passes over data in memory can be made to update the CRC. \ For ZIP, initial CRC must be &FFFFFFFF, and the final CRC must \ be EORed with &FFFFFFFF before being stored in the ZIP file. \ \ Extra CRC optimisation by Mike Cook, extra loop optimisation by JGH. \ Total 63 bytes. \ .crc32 .bytelp LDX #8 :\ Prepare to rotate CRC 8 bits LDA (addr-8 AND &FF,X) :\ Fetch byte from memory : \ The following code updates the CRC with the byte in A ---------+ \ If used in isolation, requires LDX #8 here | EOR crc+0 :\ EOR byte into CRC bottom byte | .rotlp :\ | LSR crc+3:ROR crc+2 :\ Rotate CRC clearing bit 31 | ROR crc+1:ROR A :\ | BCC clear :\ b0 was zero | TAY :\ Hold CRC low byte in Y for a bit | LDA crc+3:EOR #&ED:STA crc+3 :\ CRC=CRC EOR &EDB88320, ZIP polynomic LDA crc+2:EOR #&B8:STA crc+2 :\ | LDA crc+1:EOR #&83:STA crc+1 :\ | TYA:EOR #&20 :\ Get CRC low byte back into A | .clear :\ | DEX:BNE rotlp :\ Loop for 8 bits | \ If used in isolation, requires STA crc+0 here | \ ---------------------------------------------------------------+ : INC addr:BNE next:INC addr+1 :\ Step to next byte .next STA crc+0 :\ Store CRC low byte :\ Now do a 16-bit decrement LDA num+0:BNE skip :\ num.lo<>0, not wrapping from 00 to FF DEC num+1 :\ Wrapping from 00 to FF, dec. high byte .skip DEC num+0:BNE bytelp :\ Dec. low byte, loop until num.lo=0 LDA num+1:BNE bytelp :\ Loop until num=0 RTSThere is a examination of optimising the CRC code on the BeebWiki.
\ Calculating ZIP CRC-32 in Z80 \ ============================= \ Calculate a ZIP 32-bit CRC from data in memory. This code is as \ tight and as fast as it can be, moving as much code out of inner \ loops as possible. Can be made shorter, but slower, by replacing \ JP with JR. \ \ On entry, crc..crc+3 = incoming CRC \ addr..addr+1 => start of data \ num..num+1 = number of bytes \ On exit, crc..crc+3 = updated CRC \ addr..addr+1 => undefined \ num..num+1 = undefined \ \ Multiple passes over data in memory can be made to update the CRC. \ For ZIP, initial CRC must be &FFFFFFFF, and the final CRC must \ be EORed with &FFFFFFFF before being stored in the ZIP file. \ Total 70 bytes. \ .crc32 LD IX,(addr):LD BC,(num) :\ Address, Count LD DE,(crc):LD HL,(crc+2) :\ Incoming CRC \ \ Enter here with IX=addr, BC=num, HLDE=crc \ .bytelp PUSH BC :\ Save count LD A,(IX) :\ Fetch byte from memory : \ The following code updates the CRC with the byte in A ---------+ XOR E :\ XOR byte into CRC bottom byte | LD B,8 :\ Prepare to rotate 8 bits | .rotlp :\ | SRL H:RR L:RR D:RRA :\ Rotate CRC | JP NC,clear :\ b0 was zero | LD E,A :\ Put CRC low byte back into E | LD A,H:XOR &ED:LD H,A :\ CRC=CRC XOR &EDB88320, ZIP polynomic| LD A,L:XOR &B8:LD L,A :\ | LD A,D:XOR &83:LD D,A :\ | LD A,E:XOR &20 :\ And get CRC low byte back into A | .clear :\ | DEC B:JP NZ,rotlp :\ Loop for 8 bits | LD E,A :\ Put CRC low byte back into E | \ ---------------------------------------------------------------+ : INC IX :\ Step to next byte POP BC:DEC BC :\ num=num-1 LD A,B:OR C:JP NZ,bytelp :\ Loop until num=0 LD (crc),DE:LD (crc+2),HL :\ Store outgoing CRC RET
\ Calculating ZIP CRC-32 in 6809 \ ============================== \ Calcluate a ZIP 32-bit CRC from data in memory. This code is as \ tight and nearly as fast as it can be, moving as much code out of inner \ loops as possible. Further optimisation may be possible, moving the \ whole CRC in registers but the gain on average data is only slight \ (estimated 2% but at losing clarity of implemention; \ worst case gain is 18%, best case worsens at 29%) \ \ On entry, crc..crc+3 = incoming CRC \ addr..addr+1 => start of data \ num..num+1 = number of bytes \ On exit, crc..crc+3 = updated CRC \ addr..addr+1 => unchanged \ num..num+1 = unchanged \ \ Value order in memory is H,L (big endian) \ \ Multiple passes over data in memory can be made to update the CRC. \ For ZIP, initial CRC must be &FFFFFFFF, and the final CRC must \ be EORed with &FFFFFFFF before being stored in the ZIP file. \ Total 47 bytes (if above parameters are located in direct page). \ \ Author: \ \ ZIP polynomic &04C11DB7, bit reversed POLYHH EQU &ED POLYHL EQU &B8 POLYLH EQU &83 POLYLL EQU &20 .crc32 ldu addr :\ Start address (direct page or extended) ldx num :\ Count (DP or extended) ldd crc+2 :\ Incoming CRC, low part : .bl \ The following code updates the CRC with the byte in the operand of the eorb statement --+ eorb ,u+ :\ Fetch byte and XOR into CRC lowest byte | ldy #8 :\ Rotate loop counter | .rl | lsr crc :\ Shift CRC right, beginning | ror crc+1 :\ from the highest byte | rora | rorb | bcc cl :\ Justify or ... | eora #POLYLH :\ CRC=CRC XOR polynomic low word | eorb #POLYLL | std crc+2 | ldd crc :\ CRC=CRC XOR polynomic high word | eora #POLYHH | eorb #POLYHL | std crc | ldd crc+2 :\ CRC low | .cl | leay -1,y :\ Shift loop (8 bits) | bne rl | \ ----------------------------------------------------------------------------------------+ : leax -1,x :\ Byte loop bne bl : std crc+2 :\ Store final CRC low back rts
; Calculating ZIP CRC-32 in PDP-11 ; ================================ ; Calculate a ZIP 32-bit CRC from data in memory. This code is as ; tight and as fast as it can be, moving as much code out of inner ; loops as possible. ; ; On entry, crc..crc+3 = incoming CRC ; addr..addr+1 => start of data ; num..num+1 = number of bytes ; On exit, crc..crc+1 = updated CRC ; addr..addr+1 => undefined ; num..num+1 = undefined ; ; Multiple passes over data in memory can be made to update the CRC. ; For ZIP, initial CRC must be &FFFFFFFF, and the final CRC must ; be EORed with &FFFFFFFF before being stored in the ZIP file. ; Total 70 bytes. ; .crc32 mov (addr),r1 ; Address mov (num),r2 ; Count mov (crc+0),r4 ; CRC low byte mov (crc+2),r3 ; CRC high byte ; ; Enter here with r1=>addr, r2=count, r3/r4=CRC ; .bytelp movb (r1)+,r0 ; Fetch byte from memory ; The following code updates the CRC with the byte in R0 -----+ bic #&FF00,r0 ; Ensure b8-b15 clear | xor r0,r4 ; XOR into CRC low byte | mov #8,r0 ; Prepare to rotate 8 bits | .rotlp ; | clc ; | ror r3 ; Rotate CRC | ror r4 ; | bcc clear ; b0 was zero | mov #&EDB8,r5 ; CRC=CRC xor &EDB88320, ZIP polynomic | xor r5,r3 ; | mov #&8320,r5 ; | xor r5,r4 ; | .clear ; | sub #1,r0 ; | bne rotlp ; Loop for 8 bits | ; ------------------------------------------------------------+ ; sub #1,r2 ; num=num-1 bne bytelp ; Loop until num=0 mov r4,(crc+0) ; Store outgoing CRC mov r3,(crc+2) rts pc
; Calculating ZIP CRC-32 in 32-bit 80x86 ; ====================================== ; Calculate a ZIP 32-bit CRC from data in memory. This code is as ; tight and as fast as it can be, moving as much code out of inner ; loops as possible. ; ; On entry, crc..crc+3 = incoming CRC ; addr..addr+3 => start of data ; num..num+3 = number of bytes ; On exit, crc..crc+3 = updated CRC ; addr..addr+3 = undefined ; num..num+3 = undefined ; ; Multiple passes over data in memory can be made to update the CRC. ; For ZIP, initial CRC must be &FFFFFFFF, and the final CRC must ; be EORed with &FFFFFFFF before being stored in the ZIP file. ; total 62 bytes. ; .crc32 MOV ESI,[addr] ; ESI=>start of data MOV EBX,[num] ; EBX= length of data MOV ECX,[crc] ; ECX= incoming CRC ; .bytelp MOV AL,[ESI] ; Fetch byte from memory ; ; The following code updates the CRC with the byte in AL -----+ XOR CL,AL ; XOR byte into bottom of CRC | MOV AL,8 ; Prepare to rotate 8 bits | .rotlp ; | SHR ECX,1 ; Rotate CRC | JNC clear ; b0 was zero | XOR ECX,&EDB88320 ; If b0 was set, XOR with ZIP polymonic | .clear ; | DEC AL:JNZ rotlp ; Loop for 8 bits | ; ------------------------------------------------------------+ ; INC SI ; Point to next byte DEC EBX:JNE bytelp ; num=num-1, loop until num=0 MOV [crc],ECX ; Store outgoing CRC RETF .addr:DD 0 .num:DD 0 .crc:DD 0
\ Calculating ZIP CRC-32 in ARM \ ============================= \ Calculate a ZIP 32-bit CRC from data in memory. This code is as \ tight and as fast as it can be, moving as much code out of inner \ loops as possible. \ \ On entry, crc..crc+3 = incoming CRC \ addr..addr+3 => start of data \ num..num+3 = number of bytes \ On exit, crc..crc+3 = updated CRC \ addr..addr+3 => undefined \ num..num+3 = undefined \ \ Multiple passes over data in memory can be made to update the CRC. \ For ZIP, initial CRC must be &FFFFFFFF, and the final CRC must \ be EORed with &FFFFFFFF before being stored in the ZIP file. \ Total 76 bytes. \ .crc32 LDR R0,addr:LDR R1,num :\ Address, Count LDR R2,crc :\ Incoming CRC \ \ Enter here with R0=addr, R1=num, R2=crc \ .crc32reg LDR R3,xor :\ ZIP polynomic .bytelp LDRB R4,[R0],#1 :\ Get byte, inc address : \ The following code updates the CRC with the byte in R4 --------+ \ If used in isolation, requires LDR R3,xor here | EOR R2,R2,R4 :\ EOR byte into CRC bottom byte | MOV R4,#8 :\ Prepare to rotate 8 bits | .rotlp :\ | MOVS R2,R2,LSR #1 :\ Rotate CRC | EORCS R2,R2,R3 :\ If b0 was set, EOR with ZIP polynomic SUBS R4,R4,#1:BNE rotlp :\ Loop for 8 bits | \ ---------------------------------------------------------------+ : SUBS R1,R1,#1:BNE bytelp :\ Loop until num=0 STR R2,crc:MOV R15,R14 :\ Store outgoing CRC and return .xor :EQUD &EDB88320 :\ ZIP polynomic .addr:EQUD 0 .num :EQUD 0 .crc :EQUD 0
REM mem%=buffer REM max%=size of buffer S%=-1 :REM CRC starts as &FFFFFFFF REPEAT num%=EXT#in%-PTR#in% :REM Number of bytes to transfer IF num%>max% THEN num%=max% :REM If more than size of buffer max%, use max% PROCgbpb(rd%,in%,mem%,num%,0) :REM Read block of data PROCcrc :REM Update CRC PROCgbpb(wr%,out%,mem%,num%,0) :REM Write block of data UNTIL PTR#in%=EXT#in% :REM Loop until all done crc%=NOT S% :REM Final CRC is invertedThe CRC is calculated with one of the following subroutines:
REM BASIC: DEFPROCcrc:FORA%=mem%TOmem%+num%-1:S%=S%EOR?A%:FORB%=1TO8:O%=S%:S%=(((S%+(S%<0))DIV2)AND&7FFFFFFF):IFO%AND1:S%=S%EOR&EDB88320 NEXT:NEXT:ENDPROC REM Assembler: DEFPROCcrc:!addr=mem%:!num=num%:!crc=S%:CALL Calc:S%=!crc:ENDPROC : REM With CRC-32 code previously assembled with: : REM Crunched assembler routines REM --------------------------- DEFPROCcrc65:DIM Calc 63:addr=&70:num=&72:crc=&74:FORP=0TO1 P%=Calc:[OPT P*2:.bl:LDX #8:LDA (addr-8 AND &FF,X):EOR crc .rl:LSR crc+3:ROR crc+2:ROR crc+1:ROR A:BCC cl TAY:LDA crc+3:EOR #&ED:STA crc+3:LDA crc+2:EOR #&B8:STA crc+2 LDA crc+1:EOR #&83:STA crc+1:TYA:EOR #&20:.cl DEX:BNE rl:INC addr:BNE nx:INC addr+1:.nx:STA crc LDA num:BNE sk:DEC num+1:.sk:DEC num:BNE bl LDA num+1:BNE bl:RTS:]:NEXT:ENDPROC : DEFPROCcrc80:DIM Calc 79:addr=&70:num=&72:crc=&74:FORP=0TO1 P%=Calc:[OPT P*2:LD IX,(addr):LD BC,(num) LD DE,(crc):LD HL,(crc+2) .bl:PUSH BC:LD A,(IX):XOR E:LD B,8 .rl:SRL H:RR L:RR D:RRA:JP NC,cl:LD E,A LD A,H:XOR &ED:LD H,A:LD A,L:XOR &B8:LD L,A LD A,D:XOR &83:LD D,A:LD A,E:XOR &20 .cl:DEC B:JP NZ,rl:LD E,A:INC IX:POP BC:DEC BC LD A,B:OR C:JP NZ,bl:LD (crc),DE LD (crc+2),HL:RET:]:NEXT:ENDPROC : DEFPROCcrc86:DIM Calc 63:FORP=0TO1 P%=Calc:[OPT P*2:MOV ESI,[addr]:MOV EBX,[num] MOV ECX,[crc]:.bl:MOV AL,[ESI]:XOR CL,AL:MOV AL,8 .rl:SHR ECX,1:JNC cl:XOR ECX,&EDB88320:.cl DEC AL:JNZ rl:INC SI:DEC EBX:JNE bl:MOV [crc],ECX RETF:.addr:DD 0:.num:DD 0:.crc:DD 0:]:NEXT:ENDPROC : DEFPROCcrcARM:DIM Calc 79:FORP=0TO1 P%=Calc:[OPT P*2:LDR R0,addr:LDR R1,num LDR R2,crc:LDR R3,xor .bl:LDRB R4,[R0],#1:EOR R2,R2,R4:MOV R4,#8 .rl:MOVS R2,R2,LSR #1:EORCS R2,R2,R3 SUBS R4,R4,#1:BNE rl:SUBS R1,R1,#1:BNE bl STR R2,crc:MOV R15,R14:.xor:EQUD &EDB88320 .addr:EQUD 0:.num:EQUD 0:.crc:EQUD 0:]:NEXT:ENDPROC :07-Jan-2013: Managed to squeeze another one byte out of the Z80 code.