1/*  File:    canny/shifter.pl
    2    Author:  Roy Ratcliffe
    3    Created: Sep 16 2023
    4    Purpose: Bit Shifter
    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_shifter,
   30          [ bit_shift/3                         % +Shifter,?Left,?Right
   31          ]).
 bit_shift(+Shifter, ?Left, ?Right) is semidet
Shifts bits left or right depending on the argument mode. Mode (+, -, +) shifts left whereas mode (+, +, -) shifts right. The first argument specifies the position of the bit or bits in Left, the second argument, while the third argument specifies the aligned Right bits. The shift moves in the direction of the variable argument, towards the (-) mode argument.

The Shifter argument provides three different ways to specify a bit shift and bit width: either by an exclusive range using + and - terms; or an inclusive range using : terms; or finally just a single bit shift which implies a width of one bit. Colons operate inclusively whereas plus and minus apply exclusive upper ranges.

It first finds the amount of Shift required and the bit Width. After computing the lefthand and righthand bit masks, it finally performs a shift-mask or mask-shift for left and right shifts respectively.

Arguments:
Shifter- is a Shift+Width, Shift-Width, High:Low, Low:High or just a single integer Shift for single bits.
Left- is the left-shifted integer.
Right- is the right-shifted integer.
   59bit_shift(Shifter, Left, Right) :-
   60    shifter(Shifter, Shift, Width),
   61    RightMask is (1 << Width) - 1,
   62    LeftMask is RightMask << Shift,
   63    shift(Left, Right, Shift, LeftMask).
   64
   65shifter(Shift+Width, Shift, Width) :- !.
   66shifter(Shift0-Width, Shift, Width) :- !, Shift is Shift0 - Width.
   67shifter(Low:High, Low, Width) :- Low =< High, !, Width is High - Low + 1.
   68shifter(High:Low, Low, Width) :- !, Width is High - Low + 1.
   69shifter(Shift, Shift, 1).
   70
   71shift(Left, Right, Shift, LeftMask), var(Left) =>
   72    Left is (Right << Shift) /\ LeftMask.
   73shift(Left, Right, Shift, LeftMask) =>
   74    Right is (Left /\ LeftMask) >> Shift