CRC-16

From BeebWiki
Revision as of 12:26, 25 August 2021 by Jgharston (talk | contribs) (Tidied 6809 comments.)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to: navigation, search

XMODEM and Acorn CFS/RFS files have a 16-bit CRC (Cyclic Redundancy Check). The following code calculates these CRCs. I have put all my work together here so other people can use it.

The XMODEM CRC is CRC-16 with a start value of &0000 and uses a polynomic of &1021. These three values can be changed to create code to generate other variants of CRC-16. The same CRC is used by Acorn CFS/RFS, but the published code is different, and the CRC is stored high-byte,low-byte.

'C' code

/* Calculating XMODEM CRC-16 in 'C'
   ================================
   Reference model for the translated code */

#define poly 0x1021

/* On entry, addr=>start of data
             num = length of data
             crc = incoming CRC     */
int crc16(char *addr, int num, int crc)
{
int i;

for (; num>0; num--)               /* Step through bytes in memory */
  {
  crc = crc ^ (*addr++ << 8);      /* Fetch byte from memory, XOR into CRC top byte*/
  for (i=0; i<8; i++)              /* Prepare to rotate 8 bits */
    {
    crc = crc << 1;                /* rotate */
    if (crc & 0x10000)             /* bit 15 was set (now bit 16)... */
      crc = (crc ^ poly) & 0xFFFF; /* XOR with XMODEM polynomic */
                                   /* and ensure CRC remains 16-bit value */
    }                              /* Loop for 8 bits */
  }                                /* Loop until num=0 */
  return(crc);                     /* Return updated CRC */
}

An optimisation is to define poly as 0x11021 then the loop can use crc ^= poly as the overflowed bit 16 is cleared by the additional 1. Obviously, this depends on the compiler using 32-bit integers. If using 16-bit integers, bit 15 must be tested before it overflows:

   {
   if (crc & 0x8000)              /* b15 is set... */
     crc = (crc << 1) ^ poly;     /* rotate and XOR with XMODEM polynomic */
   else                           /* b15 is clear... */
     crc = crc << 1;              /* just rotate */
   }                              /* Loop for 8 bits */

BBC BASIC

REM crc%  = incoming CRC
REM start%=>start address
REM num%  = number of bytes
:
FOR addr%=start% TO start%+num%-1
  crc%=crc% EOR 256*?addr%                   :REM EOR with current byte
  FOR bit%=1 TO 8                            :REM Loop through 8 bits
    crc%=crc%+crc%                           :REM Move crc% up one bit
    IF crc% AND &10000:crc%=crc% EOR &11021  :REM EOR with XMODEM polynomic
  NEXT bit%                                  :REM Ensuring CRC remains a 16-bit value
NEXT addr%
:
REM crc% = outgoing CRC

The following is a highly crunched and speeded up version:

FORA%=mem%TOmem%+num%-1:S%=S%EOR256*?A%:FORB%=1TO8:S%=S%*2:IFS%AND&10000:S%=S%EOR&11021
NEXT:NEXT

6502

\ Calculating XMODEM CRC-16 in 6502
\ =================================

\ Calculate an XMODEM 16-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+1   =  incoming CRC
\           addr..addr+1 => start address of data
\           num..num+1   =  number of bytes
\ On exit,  crc..crc+1   =  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 XMODEM, initial CRC must be &0000. For Acorn CFS/RFS the CRC
\ is stored in the header high-byte/low-byte.
\ Opimisation based on Greg Cook's 6502 CRC-32 optimisation.
\ Total 47 bytes
\
.crc16
.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+1                      :\ EOR byte into CRC top byte     |
.rotlp                         :\                                |
ASL crc+0:ROL A                :\ Rotate CRC clearing bit 0      |
BCC clear                      :\ b15 was clear, skip past       |
TAY                            :\ Hold CRC high byte in Y        |
LDA crc+0:EOR #&21:STA crc+0   :\ CRC=CRC EOR &1021, XMODEM polynomic
TYA:EOR #&10                   :\ Get CRC high byte back from Y  |
.clear                         :\ b15 was zero                   |
DEX:BNE rotlp                  :\ Loop for 8 bits                |
STA crc+1                      :\ Store CRC high byte            |
\ ---------------------------------------------------------------+
:
INC addr+0:BNE next:INC addr+1 :\ Step to next byte
.next
:
\ 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
RTS

Z80

\ Calculating XMODEM CRC-16 in Z80
\ ================================

\ Calculate an XMODEM 16-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+1   =  incoming CRC
\           addr..addr+1 => start address 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 XMODEM, initial CRC must be &0000. For Acorn CFS/RFS the CRC
\ is stored in the header high-byte/low-byte.
\ Total 47 bytes.
\
.crc16
LD HL,(addr):LD BC,(num)  :\ Address, Count
LD DE,(crc)               :\ Incoming CRC
:
\ Enter here with HL=>data, BC=count, DE=incoming CRC
.bytelp
PUSH BC                   :\ Save count
LD A,(HL)                 :\ Fetch byte from memory
:
\ The following code updates the CRC with the byte in A ---------+
XOR D                     :\ XOR byte into CRC top byte          |
LD B,8                    :\ Prepare to rotate 8 bits            |
.rotlp                    :\                                     |
SLA E:ADC A,A             :\ Rotate CRC                          |
JP NC,clear               :\ b15 was zero                        |
LD D,A                    :\ Put CRC high byte back into D       |
LD A,E:XOR &21:LD E,A     :\ CRC=CRC XOR &1021, XMODEM polynomic |
LD A,D:XOR &10            :\ And get CRC top byte back into A    |
.clear                    :\                                     |
DEC B:JP NZ,rotlp         :\ Loop for 8 bits                     |
LD D,A                    :\ Put CRC top byte back into D        |
\ ---------------------------------------------------------------+
:
INC HL                    :\ 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               :\ Store outgoing CRC
RET

6809

\ Calculating XMODEM CRC-16 in 6809
\ =================================

\ Calculate an XMODEM 16-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+1   =  incoming CRC
\           addr..addr+1 => start address of data
\           num..num+1   =  number of bytes
\ On exit,  crc..crc+1   =  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 XMODEM, initial CRC must be &0000. For Acorn CFS/RFS the CRC
\ is stored in the header high-byte/low-byte.
\ Total 35 bytes (if above parameters are not in the direct page, otherwise 31).
\
\ XMODEM polynomic
POLYH    EQU &10
POLYL    EQU &21

.crc16
ldu addr        :\ Start address (direct page or extended)
ldx num         :\ Count (DP or extended)
ldd crc         :\ Incoming CRC
:
.bl 
\ The following code updates the CRC with the byte fetched by the
\ eora ,u+ instruction ------------------------------------------+
eora ,u+        :\ Fetch byte and XOR into CRC high byte         |
ldy #8          :\ Rotate loop counter                           |
.rl                                                              |
aslb            :\ Shift CRC left, first low                     |
rola            :\ and than high byte                            |
bcc cl          :\ Justify or ...                                |
eora #POLYH     :\ CRC=CRC XOR polynomic, high                   |
eorb #POLYL     :\ and low byte                                  |
.cl                                                              |
leay -1,y       :\ Shift loop (8 bits)                           |
bne rl                                                           |
\ ---------------------------------------------------------------+
:
leax -1,x       :\ Byte loop
bne bl
:
std crc         :\ Store final CRC back
rts

PDP-11

; Calculating XMODEM CRC-16 in PDP-11
; ===================================

; Calculate an XMODEM 16-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+1   =  incoming CRC
;           addr..addr+1 => start address 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 XMODEM, initial CRC must be &0000. For Acorn CFS/RFS the CRC
; is stored in the header high-byte/low-byte.
; Total 56 bytes.
;
.crc16
mov  (addr),r1     ; Address
mov  (num),r2      ; Count
mov  (crc),r3      ; CRC
;
; Enter here with r1=>addr, r2=count, r3=CRC
;
mov #&1021,r4      ; XMODEM polynomic
.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                      |
swab r0            ; Move byte into b8-b15                    |
xor r0,r3          ; XOR into CRC high byte                   |
mov #8,r0          ; Prepare to rotate 8 bits                 |
.rotlp             ;                                          |
clc                ;                                          |
rol r3             ; Rotate CRC, clearing b0                  |
bcc clear          ; b15 was zero                             |
xor r4,r3          ; CRC=CRC xor &1021, XMODEM polynomic      |
.clear             ;                                          |
sub #1,r0          ;                                          |
bne rotlp          ; Loop for 8 bits                          |
; ------------------------------------------------------------+
;
sub #1,r2          ; num=num-1
bne bytelp         ; Loop until num=0
mov r3,(crc)       ; Store outgoing CRC
rts pc

32-bit 80x86

; Calculating XMODEM CRC-16 in 32-bit 80x86
; =========================================

; Calculate a XMODEM 16-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 address 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 XMODEM, initial CRC must be &0000. For Acorn CFS/RFS the CRC
; is stored in the header high-byte/low-byte.
; Opimisation based on Mike Cook's CRC32 optimisation.
; Total 71 bytes
;
.crc16
MOV ESI,[addr]      ; ESI=>start of data
MOV EBX,[num]       ; EBX= length of data
MOV ECX,[crc]       ; ECX= incoming CRC
SHL ECX,16          ; Move CRC into b16-b31
;
.bytelp
MOV AL,[ESI]        ; Fetch byte from memory
;
; The following code updates the CRC with the byte in AL -----+
SHL EAX,24          ; Move byte to b8-b15                     |
XOR ECX,EAX         ; XOR byte into top of CRC                |
MOV AL,8            ; Prepare to rotate 8 bits                |
.rotlp              ;                                         |
SHL ECX,1           ; Rotate CRC                              |
JNC clear           ; b15 was zero                            |
XOR ECX,&10210000   ; If b15 was set, XOR with XMODEM 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
SHR ECX,16          ; Move CRC back into b0-b15
MOV [crc],ECX       ; Store outgoing CRC
RETF
.addr:DD 0
.num:DD 0
.crc:DD 0

32016

ARM

\ Calculating XMODEM CRC-16 in ARM
\ ================================

\ Calculate an XMODEM 16-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 address 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 XMODEM, initial CRC must be &0000. For Acorn CFS/RFS the CRC
\ is stored in the header high-byte/low-byte.
\ Total 84 bytes.
\
.crc16
LDR R0,addr:LDR R1,num       :\ Address, Count
LDR R2,crc                   :\ Incoming CRC
\
\ Enter here with R0=addr, R1=num, R2=crc
\
.crc16reg
MOV R2,R2,LSL #16            :\ Move CRC to top of register
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,LSL #24         :\ EOR byte into CRC top byte          |
MOV R4,#8                    :\ Prepare to rotate 8 bits            |
.rotlp                       :\                                     |
MOVS R2,R2,LSL #1            :\ Rotate CRC                          |
EORCS R2,R2,R3               :\ If b15 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
MOV R2,R2,LSR #16:STR R2,crc :\ Store outgoing CRC
MOV R15,R14
.xor:EQUD &10210000          :\ ZIP polynomic
.addr:EQUD 0:.num:EQUD 0
.crc:EQUD 0

Sample calling code

Multiple passes over data can be made, for instance, as an input file is copied to an output file. The following code demonstrates how to do this, copying from an open file on in% to an open file on out%, calculating an XMODEM CRC-16 as it goes.

S%=0                             :REM CRC starts as &0000
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</pre>

The CRC is calculated with one of the following subroutines:

REM BASIC:
DEFPROCcrc:FORA%=mem%TOmem%+num%-1:S%=S%EOR256*?A%:FORB%=1TO8:S%=S%*2:IFS%AND&10000:S%=S%EOR&11021
NEXT:NEXT:ENDPROC

REM Assembler:
DEFPROCcrc:!addr=mem%:!num=num%:!crc=S%:CALL Calc:S%=!crc:ENDPROC
:
REM With CRC-16 code previously assembled with:
:
REM Crunched assembler routines
REM ---------------------------
DEFPROCcrc65:DIM Calc 49:addr=&70:num=&72:crc=&74:FORP=0TO1
P%=Calc:[OPT P*2:.bl:LDX #8:LDA (addr-8 AND &FF,X)
EOR crc+1:.rl:ASL crc:ROL A:BCC cl:TAY
LDA crc:EOR #&21:STA crc:TYA:EOR #&10:.cl:DEX
BNE rl:STA crc+1:INC addr:BNE nx:INC addr+1:.nx
LDA num:BNE sk:DEC num+1:.sk:DEC num:BNE bl
LDA num+1:BNE bl:RTS:]:NEXT:ENDPROC
:
DEFPROCcrc80:DIM Calc 49:addr=&70:num=&72:crc=&74:FORP=0TO1
P%=Calc:[OPT P*2:LD HL,(addr):LD BC,(num):LD DE,(crc)
.bl:PUSH BC:LD A,(HL):XOR D:LD B,8
.rl:SLA E:ADC A,A:JP NC,cl:LD D,A:LD A,E:XOR &21
LD E,A:LD A,D:XOR &10:.cl:DEC B:LD D,A:JP NZ,rl
INC HL:POP BC:DEC BC:LD A,B:OR C:JP NZ,bl
LD (crc),DE:RET:]:NEXT:ENDPROC
:
DEFPROCcrc86:DIM Calc 71:FORP=0TO1
P%=Calc:[OPT P*2:MOV ESI,[addr]:MOV EBX,[num]
MOV ECX,[crc]:SHL ECX,16:.bl:MOV AL,[ESI]:SHL EAX,24
XOR ECX,EAX:MOV AL,8:.rl:SHL ECX,1:JNC cl:XOR ECX,&10210000
.cl:DEC AL:JNZ rl:INC SI:DEC EBX:JNE blp:SHR ECX,16:MOV [crc],ECX
RETF:.addr:DD 0:.num:DD 0:.crc:DD 0:]:NEXT:ENDPROC
:
DEFPROCcrcARM:DIM Calc 83:FORP=0TO1
P%=Calc:[OPT P*2:LDR R0,addr:LDR R1,num
LDR R2,crc:MOV R2,R2,LSL #16:LDR R3,xor
.bl:LDRB R4,[R0],#1:EOR R2,R2,R4,LSL #24:MOV R4,#8
.rl:MOVS R2,R2,LSL #1:EORCS R2,R2,R3
SUBS R4,R4,#1:BNE rl:SUBS R1,R1,#1:BNE bl
MOV R2,R2,LSR #16:STR R2,crc:MOV R15,R14
.xor:EQUD &10210000:.addr:EQUD 0:.num:EQUD 0
.crc:EQUD 0:]:NEXT:ENDPROC
:

External links