CRCTABLE.PAS
(C) Copyright 1990 Dan Melton
All Rights Reserved
Credit for the values of the CRCTAB_32 goes to Gary S. Brown.
The text from which the tables were derived from is at the end of the
assembly language source code.
The assembly source code is appended to this TP program; the compiler
uses the "END." statement as the end of source code marker.
Nothing past "END." is processed by the Turbo Pascal compiler.
comment &
  The codes is in two parts; the compiler specific interface
  handlers and the routines that do the actual work.  By adding
  new compiler interface handlers, the internal routines can work
  with any compiler or even interpeted BASIC.
  The CRC16 and CRC32 routines get called from the high-level
  language.  Their job is to call the UPDCRC16 and UPDCRC32 with
  the proper register parameters.  The CRC16/32 routines then
  reports the results in whatever manner the compiler expects
  them.
  CRCxxBUF perform the same basic function as their CRCxx
  routines except they are designed to work on data blocks
  instead of one byte at a time.	The speed improvement comes
  from not using compiler generated loops, which are not as fast
  as they could be.
comment &
data    segment         byte public
extrn   CRCTAB_16:word
extrn   CRCTAB_32:dword
data    ends
code    segment word public
assume  cs:code,ds:data
public  CRC16
public  CRC32
public  CRC16BUF
public  CRC32BUF
;
;  function CRC16 (B : byte; CRC : word) : word;
;    begin
;      CRC16:=CRCTAB_16[((CRC shr 8) and $FF)] xor (CRC shl 8) xor B
;    end;
;
;  Uses    :   CX,DI,ES
;  Result  :   AX hold 16-bit CRC result
;
CRC     equ     bp+06   ; location of CRC16 parameter
B       equ     bp+08   ; and the B byte paramter
        crc16   proc    far
        push    bp      ; save BP
        mov     bp,sp   ; set up stack frame
        mov     ax,ds
        mov     es,ax   ; REG.ES = seg(CRCTAB_16[])
        mov     di,offset CRCTAB_16 ; REG.DI = ofs(CRCTAB_16[])
        mov     ax,[B]   ; REG.AX = word(B)
        mov     cx,[CRC] ; REG.CX = CRC
        call    updCRC16 ; update CRC-16
        mov     ax,cx   ; return result in AX
        pop     bp      ; restore stack frame
        ret     4       ; return and pop parameters
crc16   endp
;
;  TURBO PASCAL 4.x/5.x
;
;  function CRC32 (B : byte; CRC : longint) : longint;
;    begin
;      CRC32:=CRCTAB_32[byte(CRC) xor B] xor (CRC shr 8);
;    end;
;
;  Uses    :   BX,CX,DX,DI,ES
;  Result  :   DX:AX hold 32-bit CRC; DX holds MSB, AX holds LSB
;
CRC_LO  equ     bp+06   ; LSB of CRC parameter
CRC_HI  equ     bp+08   ; MSB of CRC parameter
B       equ     bp+10   ; and the B byte paramter
crc32   proc    far
        push    bp      ; save BP
        mov     bp,sp   ; set up stack frame
        mov     ax,ds
        mov     es,ax   ; REG.ES = seg(CRCTAB_32[])
        mov     di,offset CRCTAB_32 ; REG.DI = ofs(CRCTAB_32[])
        mov     ax,[B]  ; REG.BX = word(B)
        xor     ah,ah   ; clear high byte
        mov     cx,[CRC_LO] ; REG.DXCX = CRC
        mov     dx,[CRC_HI]
        call    updCRC32 ; update CRC-32
        mov     ax,cx   ; return result in DX:AX instead of DX:CX
        pop     bp      ; restore stack frame
        ret     6       ; return and pop parameters
crc32   endp
;
;  TURBO PASCAL 4.x/5.x
;
; function CRC16BUF (BSEG,BOFS,BLEN : word; CRC : word) : word;
;   begin
;     repeat
;       CRC:=CRC16(mem[BSEG:BOFS],CRC);
;       inc(BOFS);
;       dec(BLEN);
;     until BLEN=0
;     CRC16BUF:=CRC;
;   end;
;
CRC     equ     bp+6
BLEN    equ     bp+8
BOFS    equ     bp+10
BSEG    equ     bp+12
crc16buf        proc    far
        push    bp      ; save BP
        mov     bp,sp   ; set up stack frame
        mov     ax,ds
        mov     es,ax   ; REG.ES = seg(CRCTAB_16[])
        mov     di,offset CRCTAB_16 ; REG.DI = ofs(CRCTAB_16[])
        mov     ax,[BLEN] ; get buffer length
        mov     cx,[CRC]  ; get current CRC value
        mov     ds,[BSEG] ; get buffer segment
        mov     si,[BOFS] ; get buffer offset
        call    bufCRC16  ; figure CRC for a buffer
        mov     ax,es   ; restore DS
        mov     ds,ax
        mov     ax,cx   ; return CRC result in AX
        pop     bp      ; restore stack frame
        ret     8
crc16buf        endp
;
;  TURBO PASCAL 4.x/5.x
;
; function CRC32BUF (BSEG,BOFS,BLEN : word; CRC : longint) : longint;
;   begin
;     repeat
;       CRC:=CRC32(mem[BSEG:BOFS],CRC);
;       inc(BOFS);
;       dec(BLEN);
;     until BLEN=0
;     CRC32BUF:=CRC;
;   end;
;
CRC_LO  equ     bp+6
CRC_HI  equ     bp+8
BLEN    equ     bp+10
BOFS    equ     bp+12
BSEG    equ     bp+14
crc32buf        proc far
        push    bp      ; save BP
        mov     bp,sp   ; set up stack frame
        mov     ax,ds
        mov     es,ax   ; REG.ES = seg(CRCTAB_32[])
        mov     di,offset CRCTAB_32 ; REG.DI = ofs(CRCTAB_32[])
        mov     ax,[BLEN]       ; get buffer length
        mov     cx,[CRC_LO]     ; get current CRC value
        mov     dx,[CRC_HI]
        mov     ds,[BSEG]       ; get buffer segment
        mov     si,[BOFS]       ; get buffer offset
        call    bufCRC32        ; figure CRC for a buffer
        mov     ax,es   ; restore DS
        mov     ds,ax
        mov     ax,cx   ; return CRC result in DX:AX
        pop     bp      ; restore stack frame
        ret     10
crc32buf        endp
;
; BUFCRC16, BUFCRC32, UPDCRC16, and UPDCRC32 routines presented here
; should not be changed when porting the code to different compilers.
;
;
; BUFCRC16
;
;   AX    <- length of data buffer
;   CX	  <- current CRC-16 value
;   DS:SI <- pointer to start of data buffer
;   ES:DI <- pointer to start of 16-bit CRC table
;   AX	  -> last character CRC'd
;   BX	  -> destroyed
;   CX	  -> resulting CRC-16
;   DS:SI -> points to byte after buffer
;
bufCRC16        proc near
        mov     dx,ax           ; get buffer counter in DX
        cld                     ; incremental string operation
nextch16: lodsb                 ; get character from buffer
        call    updCRC16        ; update CRC-16
        dec		dx                 ; decrement buffer count
        jnz     nextch16        ; jump if DX!=0
        ret
bufCRC16 endp
;
; BUFCRC32
;
;   AX    <- length of data buffer
;   DX:CX <- current CRC-32 value
;   DS:SI <- pointer to start of data buffer
;   ES:DI <- pointer to start of 16-bit CRC table
;   AX	  -> last character CRC'd
;   BX	  -> zero
;   DX:CX -> resulting CRC-32
;   DS:SI -> points to byte after buffer
;
bufCRC32        proc near
        mov     bx,ax   ; put buffer count in BX
        cld             ; incremental string operation
nextch32: push  bx      ; put count on stack
        lodsb           ; get character from buffer
        call    updCRC32; update CRC-32
        pop     bx      ; get buffer count
        dec		bx         ; decrement buffer count
        jnz     nextch32; jump if BX!=0
        ret
bufCRC32 endp
;
; UPDCRC16
;
;   AL	  <- character to add
;   CX	  <- current CRC-16 value
;   ES:DI <- pointer to start of 16-bit CRC table
;   CX	  -> resulting CRC-16
;
updCRC16        proc near
      mov     bl,ch   ; REG.BL = (CRC shr 8)
      xor     bh,bh   ; REG.BX = (CRC shr 8) and $FF
      mov     ch,cl   ; REG.CX = (CRC shl 8)
      mov     cl,al   ; REG.CX = (CRC shl 8) xor B
      shl     bx,1    ; set REG.BX to index a table of WORD values
      xor     cx,word ptr es:[di+bx] ; REG.BX = 
                                     ; CRCTAB_16[(CRC shr 8) 
                                     ; and $FF] xor (CRC shl 8) xor B
      ret
updCRC16        endp
;
; UPDCRC32
;
;   AL	  <- character to add
;   DX:CX <- current CRC-32 value
;   ES:DI <- pointer to start of 32-bit CRC table
;   DX:CX -> resulting CRC-32
;
updCRC32        proc near
        xor     al,cl   ; REG.AL = byte(CRC) xor B
        mov     bl,al   ; REG.BL = byte(CRC) xor B
        mov     cl,ch   ; A B C-C  \  REG.DXCX = CRC shr 8
        mov     ch,dl   ; A B-B C   >
        mov     dl,dh   ; A-A B C  /  move over one byte
        xor     dh,dh   ; 0 A B C /
        mov     bh,dh   ; REG.BX = byte(CRC) xor B
        shl     bx,1    ; adjust to index dword table
                shl             bx,1
        xor     cx,es:[di+bx] ; REG.DXCX = CRCTAB_32[(byte(CRC) xor B] 
                              ; xor (CRC shr 8)
        xor     dx,es:[di+bx+2]
        ret
updCRC32 endp
code    ends
end
The following text is the file from which the tables and lookup
methods were derived from.  My copy of this files seems to be
incomplete; it mentions that code to generate the table at run-time
is shown later but is not.
/*
 ================================================================
 COPYRIGHT (C) 1986 Gary S. Brown.  You may use this program, or
 code or tables extracted from it, as desired without restriction.
 First, the polynomial itself and its table of feedback terms.  The
 polynomial is
 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+X^0
 Note that we take it "backwards" and put the highest-order term in
 the lowest-order bit.  The X^32 term is "implied"; the LSB is the
 X^31 term, etc.  The X^0 term (usually shown as "+1") results in
 the MSB being 1.
 Note that the usual hardware shift register implementation, which
 is what we're using (we're merely optimizing it by doing eight-bit
 chunks at a time) shifts bits into the lowest-order term.  In our
 implementation, that means shifting towards the right.  Why do we
 do it this way?  Because the calculated CRC must be transmitted in
 order from highest-order term to lowest-order term.  UARTs transmit
 characters in order from LSB to MSB.  By storing the CRC this way,
 we hand it to the UART in the order low-byte to high-byte; the UART
 sends each low-bit to hight-bit; and the result is transmission bit
 by bit from highest- to lowest-order term without requiring any bit
 shuffling on our part.  Reception works similarly.
 The feedback terms table consists of 256, 32-bit entries.  Notes:
     The table can be generated at runtime if desired; code to do so
     is shown later.  It might not be obvious, but the feedback
     terms simply represent the results of eight shift/xor opera-
     tions for all combinations of data and CRC register values.
     The values must be right-shifted by eight bits by the "updcrc"
     logic; the shift must be unsigned (bring in zeroes).  On some
     hardware you could probably optimize the shift in assembler by
     using byte-swap instructions.
     polynomial $edb88320
 --------------------------------------------------------------------
*/
long crc_32_tab[] = {
      0x00000000L, 0x77073096L, 0xee0e612cL, 0x990951baL, 0x076dc419L,
      0x706af48fL, 0xe963a535L, 0x9e6495a3L, 0x0edb8832L, 0x79dcb8a4L,
      0xe0d5e91eL, 0x97d2d988L, 0x09b64c2bL, 0x7eb17cbdL, 0xe7b82d07L,
      0x90bf1d91L, 0x1db71064L, 0x6ab020f2L, 0xf3b97148L, 0x84be41deL,
      0x1adad47dL, 0x6ddde4ebL, 0xf4d4b551L, 0x83d385c7L, 0x136c9856L,
      0x646ba8c0L, 0xfd62f97aL, 0x8a65c9ecL, 0x14015c4fL, 0x63066cd9L,
      0xfa0f3d63L, 0x8d080df5L, 0x3b6e20c8L, 0x4c69105eL, 0xd56041e4L,
      0xa2677172L, 0x3c03e4d1L, 0x4b04d447L, 0xd20d85fdL, 0xa50ab56bL,
      0x35b5a8faL, 0x42b2986cL, 0xdbbbc9d6L, 0xacbcf940L, 0x32d86ce3L,
      0x45df5c75L, 0xdcd60dcfL, 0xabd13d59L, 0x26d930acL, 0x51de003aL,
      0xc8d75180L, 0xbfd06116L, 0x21b4f4b5L, 0x56b3c423L, 0xcfba9599L,
      0xb8bda50fL, 0x2802b89eL, 0x5f058808L, 0xc60cd9b2L, 0xb10be924L,
      0x2f6f7c87L, 0x58684c11L, 0xc1611dabL, 0xb6662d3dL, 0x76dc4190L,
      0x01db7106L, 0x98d220bcL, 0xefd5102aL, 0x71b18589L, 0x06b6b51fL,
      0x9fbfe4a5L, 0xe8b8d433L, 0x7807c9a2L, 0x0f00f934L, 0x9609a88eL,
      0xe10e9818L, 0x7f6a0dbbL, 0x086d3d2dL, 0x91646c97L, 0xe6635c01L,
      0x6b6b51f4L, 0x1c6c6162L, 0x856530d8L, 0xf262004eL, 0x6c0695edL,
      0x1b01a57bL, 0x8208f4c1L, 0xf50fc457L, 0x65b0d9c6L, 0x12b7e950L,
      0x8bbeb8eaL, 0xfcb9887cL, 0x62dd1ddfL, 0x15da2d49L, 0x8cd37cf3L,
      0xfbd44c65L, 0x4db26158L, 0x3ab551ceL, 0xa3bc0074L, 0xd4bb30e2L,
      0x4adfa541L, 0x3dd895d7L, 0xa4d1c46dL, 0xd3d6f4fbL, 0x4369e96aL,
      0x346ed9fcL, 0xad678846L, 0xda60b8d0L, 0x44042d73L, 0x33031de5L,
      0xaa0a4c5fL, 0xdd0d7cc9L, 0x5005713cL, 0x270241aaL, 0xbe0b1010L,
      0xc90c2086L, 0x5768b525L, 0x206f85b3L, 0xb966d409L, 0xce61e49fL,
      0x5edef90eL, 0x29d9c998L, 0xb0d09822L, 0xc7d7a8b4L, 0x59b33d17L,
      0x2eb40d81L, 0xb7bd5c3bL, 0xc0ba6cadL, 0xedb88320L, 0x9abfb3b6L,
      0x03b6e20cL, 0x74b1d29aL, 0xead54739L, 0x9dd277afL, 0x04db2615L,
      0x73dc1683L, 0xe3630b12L, 0x94643b84L, 0x0d6d6a3eL, 0x7a6a5aa8L,
      0xe40ecf0bL, 0x9309ff9dL, 0x0a00ae27L, 0x7d079eb1L, 0xf00f9344L,
      0x8708a3d2L, 0x1e01f268L, 0x6906c2feL, 0xf762575dL, 0x806567cbL,
      0x196c3671L, 0x6e6b06e7L, 0xfed41b76L, 0x89d32be0L, 0x10da7a5aL,
      0x67dd4accL, 0xf9b9df6fL, 0x8ebeeff9L, 0x17b7be43L, 0x60b08ed5L,
      0xd6d6a3e8L, 0xa1d1937eL, 0x38d8c2c4L, 0x4fdff252L, 0xd1bb67f1L,
      0xa6bc5767L, 0x3fb506ddL, 0x48b2364bL, 0xd80d2bdaL, 0xaf0a1b4cL,
      0x36034af6L, 0x41047a60L, 0xdf60efc3L, 0xa867df55L, 0x316e8eefL,
      0x4669be79L, 0xcb61b38cL, 0xbc66831aL, 0x256fd2a0L, 0x5268e236L,
      0xcc0c7795L, 0xbb0b4703L, 0x220216b9L, 0x5505262fL, 0xc5ba3bbeL,
      0xb2bd0b28L, 0x2bb45a92L, 0x5cb36a04L, 0xc2d7ffa7L, 0xb5d0cf31L,
      0x2cd99e8bL, 0x5bdeae1dL, 0x9b64c2b0L, 0xec63f226L, 0x756aa39cL,
      0x026d930aL, 0x9c0906a9L, 0xeb0e363fL, 0x72076785L, 0x05005713L,
      0x95bf4a82L, 0xe2b87a14L, 0x7bb12baeL, 0x0cb61b38L, 0x92d28e9bL,
      0xe5d5be0dL, 0x7cdcefb7L, 0x0bdbdf21L, 0x86d3d2d4L, 0xf1d4e242L,
      0x68ddb3f8L, 0x1fda836eL, 0x81be16cdL, 0xf6b9265bL, 0x6fb077e1L,
      0x18b74777L, 0x88085ae6L, 0xff0f6a70L, 0x66063bcaL, 0x11010b5cL,
      0x8f659effL, 0xf862ae69L, 0x616bffd3L, 0x166ccf45L, 0xa00ae278L,
      0xd70dd2eeL, 0x4e048354L, 0x3903b3c2L, 0xa7672661L, 0xd06016f7L,
      0x4969474dL, 0x3e6e77dbL, 0xaed16a4aL, 0xd9d65adcL, 0x40df0b66L,
      0x37d83bf0L, 0xa9bcae53L, 0xdebb9ec5L, 0x47b2cf7fL, 0x30b5ffe9L,
      0xbdbdf21cL, 0xcabac28aL, 0x53b39330L, 0x24b4a3a6L, 0xbad03605L,
      0xcdd70693L, 0x54de5729L, 0x23d967bfL, 0xb3667a2eL, 0xc4614ab8L,
      0x5d681b02L, 0x2a6f2b94L, 0xb40bbe37L, 0xc30c8ea1L, 0x5a05df1bL,
      0x2d02ef8dL
   };
#define UPDCRC32(res,oct) 
   res=crc_32_tab[(byte)res^(byte)oct] ^ ((res>>8) & 0x00FFFFFFL)  
 |