1/*  File:    canny/crc.pl
    2    Author:  Roy Ratcliffe
    3    Created: Aug  6 2023
    4    Purpose: CRC
    5
    6Copyright (c) 2023, Roy Ratcliffe, Northumberland, United Kingdom
    7
    8Permission is hereby granted, free of charge,  to any person obtaining a
    9copy  of  this  software  and    associated   documentation  files  (the
   10"Software"), to deal in  the   Software  without  restriction, including
   11without limitation the rights to  use,   copy,  modify,  merge, publish,
   12distribute, sublicense, and/or sell  copies  of   the  Software,  and to
   13permit persons to whom the Software is   furnished  to do so, subject to
   14the following conditions:
   15
   16    The above copyright notice and this permission notice shall be
   17    included in all copies or substantial portions of the Software.
   18
   19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT  WARRANTY OF ANY KIND, EXPRESS
   20OR  IMPLIED,  INCLUDING  BUT  NOT   LIMITED    TO   THE   WARRANTIES  OF
   21MERCHANTABILITY, FITNESS FOR A PARTICULAR   PURPOSE AND NONINFRINGEMENT.
   22IN NO EVENT SHALL THE AUTHORS  OR   COPYRIGHT  HOLDERS BE LIABLE FOR ANY
   23CLAIM, DAMAGES OR OTHER LIABILITY,  WHETHER   IN  AN ACTION OF CONTRACT,
   24TORT OR OTHERWISE, ARISING FROM,  OUT  OF   OR  IN  CONNECTION  WITH THE
   25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   26
   27*/
   28
   29:- module(canny_crc,
   30          [ crc/2,                              % +Predefined,-CRC
   31            crc_property/2,                     % +CRC,?Property
   32            crc/3,                              % +CRC0,+Term,-CRC
   33            crc_16_mcrf4xx/1,                   % -Check
   34            crc_16_mcrf4xx/3                    % +Check0,+Data,-Check
   35          ]).   36:- autoload(library(apply), [foldl/4]).   37:- autoload(library(option), [option/2]).   38
   39:- use_module(bits, [rbit/3]).
 crc(+Predefined, -CRC) is semidet
Builds a predefined CRC accumulator.
Arguments:
Predefined- specifies a predefined CRC computation.
CRC- a newly-initialised CRC term with the correct polynomial, initial value and any necessary options such as bit reversal and inversion value.
   51crc(crc-8,          crc(16'107, 16'0, [])).
   52crc(crc-8-itu,      crc(16'107, 16'55, [xor(16'55)])).
   53crc(crc-16-mcrf4xx, crc(16'1_1021, 16'FFFF, [reverse])).
   54crc(crc-x25,        crc(16'1_1021, 16'0000, [reverse, xor(16'FFFF)])).
   55crc(crc-32,         crc(16'1_04C1_1DB7, 16'0000_0000, [reverse, xor(16'FFFF_FFFF)])).
   56crc(crc-32-bzip2,   crc(16'1_04C1_1DB7, 16'0000_0000, [xor(16'FFFF_FFFF)])).
   57crc(crc-64-jones,   crc(16'1_AD93_D235_94C9_35A9, 16'FFFF_FFFF_FFFF_FFFF, [reverse])).
 crc_property(+CRC, ?Property) is semidet
Extracts the CRC's checksum for comparison, or unifies with other interesting values belonging to a CRC accumulator.
   64crc_property(crc(Poly, _Check, _Options), poly(Poly)).
   65crc_property(crc(_Poly, Check, _Options), check(Check)).
 crc(+CRC0, +Term, -CRC) is semidet
Mutates CRC0 to CRC by feeding in a byte code, or a list of byte codes.
Arguments:
CRC0- the initial or thus-far accumulated CRC.
Term- a byte code or a list of byte codes.
CRC- the updated CRC.
   76crc(crc(Poly, Check0, Options), Byte, crc(Poly, Check, Options)) :-
   77    integer(Byte),
   78    !,
   79    0 =< Byte,
   80    Byte < 256,
   81    poly_deg(Poly, Deg),
   82    xor(Check0, Check1, Options),
   83    (   option(reverse, Options)
   84    ->  check_right(Deg, Poly, Check1, Byte, Check_)
   85    ;   check_left(Deg, Poly, Check1, Byte, Check_)
   86    ),
   87    Check2 is Check_ /\ ((1 << Deg) - 1),
   88    xor(Check2, Check, Options).
   89crc(Check0, List, Check) :-
   90    is_list(List),
   91    foldl(crc_, List, Check0, Check).
   92
   93crc_(Term, Check0, Check) :- crc(Check0, Term, Check).
   94
   95:- table check_left/3.   96
   97check_left(Poly, Check0, Check) :-
   98    poly_deg(Poly, Deg),
   99    Check1 is Check0 << (Deg - 8),
  100    check_left(8, Poly, Check1, Check_),
  101    Check is Check_ /\ ((1 << Deg) - 1).
  102
  103check_left(0, _Poly, Check, Check) :- !.
  104check_left(Count, Poly, Check0, Check) :-
  105    succ(Count_, Count),
  106    poly_deg(Poly, Deg),
  107    bit_left(Deg, Check0, Bit, Check1),
  108    xor(Bit, Check1, Poly, Check_),
  109    check_left(Count_, Poly, Check_, Check).
  110
  111check_left(Deg, Poly, Check0, Byte, Check) :-
  112    Shift is Deg - 8,
  113    Byte_ is Byte xor (Check0 >> Shift),
  114    check_left(Poly, Byte_, Check_),
  115    CheckMask is (1 << Shift) - 1,
  116    Check is Check_ xor ((Check0 /\ CheckMask) << 8).
  117
  118:- table check_right/3.  119
  120check_right(Poly, Check0, Check) :-
  121    poly_deg(Poly, Deg),
  122    rbit(Deg, Poly, Poly_),
  123    check_right(8, Poly_, Check0, Check_),
  124    Check is Check_ /\ ((1 << Deg) - 1).
  125
  126check_right(0, _Poly, Check, Check) :- !.
  127check_right(Count, Poly, Check0, Check) :-
  128    succ(Count_, Count),
  129    bit_right(Check0, Bit, Check1),
  130    xor(Bit, Check1, Poly, Check_),
  131    check_right(Count_, Poly, Check_, Check).
  132
  133check_right(_Deg, Poly, Check0, Byte, Check) :-
  134    Byte_ is Byte xor (Check0 /\ 16'FF),
  135    check_right(Poly, Byte_, Check_),
  136    Check is Check_ xor (Check0 >> 8).
  137
  138bit_left(Deg, Int0, Bit, Int) :-
  139    Bit is getbit(Int0, Deg - 1),
  140    Int is (Int0 << 1) /\ ((1 << Deg) - 1).
  141
  142bit_right(Int0, Bit, Int) :-
  143    Bit is getbit(Int0, 0),
  144    Int is Int0 >> 1.
  145
  146xor(0, Int, _Poly, Int).
  147xor(1, Int0, Poly, Int) :- Int is Int0 xor Poly.
  148
  149xor(Check0, Check, Options) :-
  150    (   option(xor(Check_), Options)
  151    ->  Check is Check_ xor Check0
  152    ;   Check = Check0
  153    ).
  154
  155:- table poly_deg/2.  156
  157poly_deg(Poly, Deg) :- deg(Deg), poly_deg_(Poly, Deg), !.
  158
  159deg(8).
  160deg(16).
  161deg(24).
  162deg(32).
  163deg(64).
  164
  165poly_deg_(Poly, Deg) :-
  166    Low is 1 << Deg,
  167    Low =< Poly,
  168    High is Low << 1,
  169    Poly < High.
 crc_16_mcrf4xx(-Check) is det
Initialises CRC-16/MCRF4XX checksum.
  175crc_16_mcrf4xx(16'FFFF).
 crc_16_mcrf4xx(+Check0, +Data, -Check) is det
Accumulates CRC-16/MCRF4XX checksum using optimal shifting and exclusive-OR operations.
  182crc_16_mcrf4xx(Check0, Data, Check) :-
  183    integer(Data),
  184    !,
  185    Data_ is (Check0 /\ 16'FF) xor (Data /\ 16'FF),
  186    Data__ is Data_ xor ((Data_ << 4) /\ 16'FF),
  187    Check is (Check0 >> 8) xor (Data__ << 8) xor (Data__ << 3) xor (Data__ >> 4).
  188crc_16_mcrf4xx(Check0, Data, Check) :-
  189    is_list(Data),
  190    foldl(crc_16_mcrf4xx_, Data, Check0, Check).
  191
  192crc_16_mcrf4xx_(Data, Check0, Check) :- crc_16_mcrf4xx(Check0, Data, Check)