1/*  File:    dcg/endian.pl
    2    Author:  Roy Ratcliffe
    3    Created: Aug 28 2023
    4    Purpose: Big- and Little-Endian Grammars
    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(dcg_endian,
   30          [ endian//3,
   31            big_endian//2,
   32            little_endian//2
   33          ]).   34:- autoload(library(dcg/basics), [remainder/3]).
 endian(?BigOrLittle, ?Width, ?Value)// is semidet
Applies big or little-endian ordering grammar to an integer Value of any Width.

Divides the problem in two: firstly the 'endianness' span which unifies an input or output phrase with the bit width of a value, and secondly the shifted bitwise-OR phase that translates between coded eight-bit octets and un-encoded integers of unlimited bit width by accumulation.

Arguments:
BigOrLittle- is the atom big or little specifying the endianness of the coded Value.
Width- is the multiple-of-eight bit width of the endian-ordered octet phrase.
Value- is the un-encoded integer value of unlimited bit width.
   55endian(big, Width, Value) --> big_endian(Width, Value).
   56endian(little, Width, Value) --> little_endian(Width, Value).
 big_endian(?Width, ?Value)// is semidet
Implements the grammar for endian(big, Width, Value) super-grammar.

In (-, +) mode the accumulator recurses first and then the residual Value_ merges with the accumulated Value because the first octet code is the most-significant byte of the value for big-endian integer representations, rather than the least-significant. The 0 =< H, H =< 255 guard conditions ensure failure for non-octet code items in the list.

   69big_endian(Width, Value) -->
   70    { var(Value), !
   71    },
   72    endianness(Width, Octets),
   73    { big_endian(Octets, 0, Value)
   74    }.
   75big_endian(Width, Value) -->
   76    endianness(Width, Octets),
   77    { big_endian_(Octets, Value, _)
   78    }.
   79
   80big_endian([], Value, Value).
   81big_endian([H|T], Value0, Value) :-
   82    acc(H, Value0, Value_),
   83    big_endian(T, Value_, Value).
   84
   85big_endian_([], Value, Value).
   86big_endian_([H|T], Value0, Value) :-
   87    big_endian_(T, Value0, Value_),
   88    acc_(H, Value_, Value).
   89
   90acc(H, Value0, Value_) :-
   91    0 =< H,
   92    H =< 255,
   93    Value_ is H \/ (Value0 << 8).
   94
   95acc_(H, Value_, Value) :-
   96    H is Value_ /\ 16'ff,
   97    Value is Value_ >> 8.
 little_endian(?Width, ?Value)// is semidet
Implements endian(little, Width, Value) grammar.

Little-endian accumulators perform the same logical unification as for big-endian only in reverse. The only difference between big and little: recurse first or recurse last. Apart from that subtle but essential difference, the inner computation behaves identically.

  108little_endian(Width, Value) -->
  109    { var(Value), !
  110    },
  111    endianness(Width, Octets),
  112    { little_endian(Octets, 0, Value)
  113    }.
  114little_endian(Width, Value) -->
  115    endianness(Width, Octets),
  116    { little_endian_(Octets, Value, _)
  117    }.
  118
  119little_endian([], Value, Value).
  120little_endian([H|T], Value0, Value) :-
  121    little_endian(T, Value0, Value_),
  122    %
  123    %   0 =< H,
  124    %   H =< 255,
  125    %   Value is H \/ (Value_ << 8),
  126    %
  127    acc(H, Value_, Value).
  128
  129little_endian_([], Value, Value).
  130little_endian_([H|T], Value0, Value) :-
  131    %
  132    %   H is Value0 /\ 16'ff,
  133    %   Value_ is Value0 >> 8,
  134    %
  135    acc_(H, Value0, Value_),
  136    little_endian_(T, Value_, Value).
 endianness(?Width, ?Octets)// is semidet
Grammar for finding Octets by Width. Unites difference lists of octet codes with zero or more items by a width.

The Width term can be either a variable or an integer. For unknown widths, the clauses span the remainder of the difference lists. The length of the outstanding list of codes determines the final width multiplied by eight.

The Octets may also have variable items. The grammar does not examine the codes themselves; it only concerns the length and its relationship to width. The grammar fails if the width is not a multiple of eight.

  153endianness(Width, Octets) -->
  154    { var(Width), !
  155    },
  156    remainder(Octets),
  157    { length(Octets, Len),
  158      Width is Len << 3
  159    }.
  160endianness(Width, Octets) -->
  161    { Width_ is Width /\ 2'111,
  162      Width_ == 0,
  163      Len is Width >> 3,
  164      length(Octets, Len)
  165    },
  166    Octets