1:- module(onepointfour_basics_stringy_justify,
    2          [
    3           justify_left/4   % justify_left(FieldWidth,Text,Result,ResultType)
    4          ,justify_left/5   % justify_left(FieldWidth,Text,Result,ResultType,SettingsDict)
    5          ,justify_right/4  % justify_right(FieldWidth,Text,Result,ResultType)
    6          ,justify_right/5  % justify_right(FieldWidth,Text,Result,ResultType,SettingsDict)
    7          ,justify_center/4 % justify_center(FieldWidth,Text,Result,ResultType)
    8          ,justify_center/5 % justify_center(FieldWidth,Text,Result,ResultType,SettingsDict)
    9          ,justify_how/5    % justify_how(How,FieldWidth,Text,Result,ResultType) 
   10          ,justify_how/6    % justify_how(How,FieldWidth,Text,Result,ResultType,SettingsDict) 
   11          ]).   12
   13:- use_module(library('onepointfour_basics/stringy_overwrite.pl')).   14:- use_module(library('onepointfour_basics/dict_settings.pl')).   15:- use_module(library('onepointfour_basics/checks.pl')).   16:- use_module(library('onepointfour_basics/stringy_length.pl')).   17:- use_module(library('onepointfour_basics/space_stringy.pl')).   18
   19/*  MIT License Follows (https://opensource.org/licenses/MIT)
   20
   21    Copyright 2021 David Tonhofer <ronerycoder@gluino.name>
   22
   23    Permission is hereby granted, free of charge, to any person obtaining
   24    a copy of this software and associated documentation files
   25    (the "Software"), to deal in the Software without restriction,
   26    including without limitation the rights to use, copy, modify, merge,
   27    publish, distribute, sublicense, and/or sell copies of the Software,
   28    and to permit persons to whom the Software is furnished to do so,
   29    subject to the following conditions:
   30
   31    The above copyright notice and this permission notice shall be
   32    included in all copies or substantial portions of the Software.
   33
   34    THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
   35    EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
   36    MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
   37    IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
   38    CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
   39    TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
   40    SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   41*/
   42
   43/* pldoc ==================================================================== */

Justify a text left,right or center inside a field of fixed width

Homepage for this code

https://github.com/dtonhofer/prolog_code/blob/main/unpacked/onepointfour_basics/doc/README_stringy_justify.md

*/

Default behaviour in all cases.
   57justify_how(How,FieldWidth,Text,Result,ResultType) :-
   58   justify_how(How,FieldWidth,Text,Result,ResultType,_{}).
SettingsDict can contain:

cut_left - a boolean, cut the result at left field limit (default true) cut_right - a boolean, cut the result at right field limit (default true) offset - an integer, used for "offset on the left" when justifying left

   68justify_how(How,FieldWidth,Text,Result,ResultType,SettingsDict) :-
   69   assertion(check_that(How,[hard(member(left,right,center))])),
   70   (
   71     (How==left) 
   72     -> 
   73     justify_left(FieldWidth,Text,Result,ResultType,SettingsDict)
   74     ;
   75     (How==right) 
   76     -> 
   77     justify_right(FieldWidth,Text,Result,ResultType,SettingsDict)
   78     ;
   79     (How==center)
   80     ->
   81     justify_center(FieldWidth,Text,Result,ResultType,SettingsDict)
   82   ).
   83
   84% -----------------------------------------------------------------------------------
   85
   86/* Justify left
   87
   88   case of positive offset
   89
   90   |************************FieldWidth****************************|
   91   |**Offset**|******TextWidth*********|---------PadWidth---------|
   92   |~~~~~~~~~ReducedFieldWidth~~~~~~~~~|
   93
   94   case of positive offset with negative PadWidth
   95
   96   |************************FieldWidth****************************|
   97   |**Offset**|***********************TextWidth*********************************|
   98   |~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ReducedFieldWidth~~~~~~~~~~~~~~~~~~~~~~~~~~~~~|
   99                                                                  |--PadWidth---|
  100
  101   case of negative offset with positive PadWdith
  102
  103              |************************FieldWidth****************************|
  104   |**Offset**|******TextWidth*********|-----------------PadWidth------------|
  105   |~~~~~~~~~ReducedFieldWidth~~~~~~~~~|
  106
  107*/
 justify_left(FieldWidth, Text, Result, ResultType, SettingsDict)
Standard "left justify", everything is default.
  113justify_left(FieldWidth,Text,Result,ResultType) :-
  114   justify_left(FieldWidth,Text,Result,ResultType,_{}).
 justify_left(FieldWidth, Text, Result, ResultType, SettingsDict)
Justify Text left inside a field of width FieldWidth, yielding the Result of the type given by ResultType (one of string, atom). ResultType can also be deduced if Result is instantiated on call, or else from the given Text.

SettingsDict can contain:

cut_left - a boolean, cut the result at left field limit (default true) cut_right - a boolean, cut the result at right field limit (default true) offset - an integer, used for "offset on the left" when justifying left

  129justify_left(FieldWidth,Text,Result,ResultType,SettingsDict) :-
  130   decaps_cut_flags(SettingsDict,CutLeft,CutRight),
  131   decaps_offset(SettingsDict,Offset),
  132   common_entry_checks(FieldWidth,Text,Result,ResultType),
  133   complete_result_type(Text,Result,ResultType),
  134   space_stringy(FieldWidth,BgText,string),
  135   stringy_overwrite(BgText,Text,Offset,CutLeft,CutRight,Result,ResultType).
  136
  137% -----------------------------------------------------------------------------------
  138
  139/* Justify right
  140
  141   case of positive offset
  142
  143   |************************FieldWidth****************************|
  144   |-------PadWidth-----------|*********TextWidth******|**Offset**|
  145
  146   case of negative offset
  147
  148   |************************FieldWidth****************************|
  149   |---------------------PadWidth----------------------|*********TextWidth******|
  150                                                                  |***Offset****|
  151*/
 justify_right(FieldWidth, Text, Result, ResultType)
Standard "right justify", everything is default.
  157justify_right(FieldWidth,Text,Result,ResultType) :-
  158   justify_right(FieldWidth,Text,Result,ResultType,_{}).
 justify_right(FieldWidth, Text, Result, ResultType, SettingsDict)
Justify Text right inside a field of width FieldWidth, yielding the Result of the type given by ResultType (one of string, atom). ResultType can also be deduced if Result is instantiated on call, or else from the given Text.

SettingsDict can contain:

cut_left cut_right offset

  173justify_right(FieldWidth,Text,Result,ResultType,SettingsDict) :-
  174   decaps_cut_flags(SettingsDict,CutLeft,CutRight),
  175   decaps_offset(SettingsDict,Offset),
  176   common_entry_checks(FieldWidth,Text,Result,ResultType),
  177   complete_result_type(Text,Result,ResultType),
  178   stringy_length(Text,TextWidth),
  179   PadWidth is FieldWidth-TextWidth-Offset,
  180   space_stringy(FieldWidth,BgText,string),
  181   stringy_overwrite(BgText,Text,PadWidth,CutLeft,CutRight,Result,ResultType).
  182
  183% -----------------------------------------------------------------------------------
  184
  185/* Justify center
  186
  187   case of positive offset
  188
  189   |********************************************FieldWidth***********************************************|
  190   |**OffsetLeft**|---PadLeftWidth---|**********TextWidth*********|----PadRightWidth-----|**OffsetRight**|
  191                  |~~~~~~~~~~~~~~~~~~~~~~~~ReducedFieldWidth~~~~~~~~~~~~~~~~~~~~~~~~~~~~~|
  192
  193*/
 justify_center(FieldWidth, Text, Result, ResultType)
Standard "center justify", everything is default.
  199justify_center(FieldWidth,Text,Result,ResultType) :-
  200   justify_center(FieldWidth,Text,Result,ResultType,_{}).
 justify_center(FieldWidth, Text, Result, ResultType, SettingsDict)
Justify Text centrally inside a field of width FieldWidth, yielding the Result of the type given by ResultType (one of string, atom). ResultType can also be deduced if Result is instantiated on call, or else from the given Text.

SettingsDict can contain:

cut_left cut_right offset_left offset_right prefer - leftly,rightly : where to prefer shifting the foreground left or right if full central alignment is impossible
  218justify_center(FieldWidth,Text,Result,ResultType,SettingsDict) :-
  219   decaps_offset_left_right(SettingsDict,OffsetLeft,OffsetRight),
  220   decaps_cut_flags(SettingsDict,CutLeft,CutRight),
  221   decaps_prefer(SettingsDict,Prefer),
  222   common_entry_checks(FieldWidth,Text,Result,ResultType),
  223   complete_result_type(Text,Result,ResultType),
  224   stringy_length(Text,TextWidth),
  225   ReducedFieldWidth is FieldWidth-OffsetLeft-OffsetRight, % could already be negative
  226   ((ReducedFieldWidth < 0)
  227    ->
  228    deal_with_negative_reduced_field_width(ReducedFieldWidth,FieldWidth,OffsetLeft,OffsetRight,Text,Result,ResultType,CutLeft,CutRight,Prefer)
  229    ;
  230    deal_with_pos0_reduced_field_width(ReducedFieldWidth,FieldWidth,OffsetLeft,Text,TextWidth,Result,ResultType,CutLeft,CutRight,Prefer)).
  231
  232deal_with_negative_reduced_field_width(ReducedFieldWidth,FieldWidth,OffsetLeft,OffsetRight,Text,Result,ResultType,CutLeft,CutRight,Prefer) :-
  233   Half           is (-ReducedFieldWidth)//2, % round towards 0 (in principle)
  234   OtherHalf      is (-ReducedFieldWidth) - Half,
  235   NewOffsetLeft  is OffsetLeft  - Half,
  236   NewOffsetRight is OffsetRight - OtherHalf,
  237   assertion(FieldWidth =:= NewOffsetLeft+NewOffsetRight),
  238   % calls itself now
  239   justify_center(FieldWidth,Text,Result,ResultType,
  240      _{offset_left  : NewOffsetLeft,
  241        offset_right : NewOffsetRight,
  242        cut_left     : CutLeft,
  243        cut_right    : CutRight,
  244        prefer       : Prefer}).
  245
  246deal_with_pos0_reduced_field_width(ReducedFieldWidth,FieldWidth,OffsetLeft,Text,TextWidth,Result,ResultType,CutLeft,CutRight,Prefer) :-
  247   odd_even(ReducedFieldWidth,TaggedReducedFieldWidth),
  248   odd_even(TextWidth,TaggedTextWidth),
  249   once(start_pos(TaggedReducedFieldWidth,TaggedTextWidth,Prefer,StartPos)),
  250   AbsoluteStartPos is OffsetLeft + StartPos,
  251   space_stringy(FieldWidth,BgText,string),
  252   stringy_overwrite(BgText,Text,AbsoluteStartPos,CutLeft,CutRight,Result,ResultType).
  253
  254% -----------------------------------------------------------------------------------
  255
  256odd_even(X,odd(X))  :- (X mod 2) =:= 1, !.
  257odd_even(X,even(X)).
  258
  259% In two cases the StartPosition is computed as ReducedFieldWidth//2 - TextWidth//2
  260%
  261%   oooooooooXiiiiiiiii       ReducedFieldWidth is odd (and has a central character)
  262%         aaaXbbb             TextWidth is odd (and has a central character)
  263%
  264%                             or
  265%
  266%   ooooooooooiiiiiiiiii      ReducedFieldWidth is even
  267%          aaabbb             TextWidth is even
  268%
  269% An arbitrary decision is needed if one of the width is even and one is odd_
  270%
  271%   ooooooooooiiiiiiiiii      ReducedFieldWidth is even
  272%          aaaXbbb            rightly behaviour
  273%         aaaXbbb             leftly  behaviour
  274%
  275%   oooooooooXiiiiiiiii       ReducedFieldWidth is odd (and has a central character)
  276%          aaabbb             rightly behaviour
  277%         aaabbb              leftly  behaviour
  278
  279start_pos(odd(RFW)  ,odd(TW)  ,_       ,StartPos) :- StartPos is RFW//2 - TW//2.
  280start_pos(even(RFW) ,even(TW) ,_       ,StartPos) :- StartPos is RFW//2 - TW//2.
  281start_pos(odd(RFW)  ,even(TW) ,leftly  ,StartPos) :- StartPos is RFW//2 - TW//2.
  282start_pos(odd(RFW)  ,even(TW) ,rightly ,StartPos) :- StartPos is RFW//2 - TW//2 + 1.
  283start_pos(even(RFW) ,odd(TW)  ,leftly  ,StartPos) :- StartPos is RFW//2 - TW//2 - 1.
  284start_pos(even(RFW) ,odd(TW)  ,rightly ,StartPos) :- StartPos is RFW//2 - TW//2.
  285
  286% In case the ResultType (here called PassedResultType) has been left uninstantiated
  287% by the caller, clamp it to 'atom' or 'string', possibly by guessing.
  288% Note that we demand to have a positive conclusion as to what type to deliver or
  289% we complain, unlike in stringy_concat for example, where lack of a positive
  290% conclusion leads to non-determinacy, with two solutions delivered.
  291
  292complete_result_type(Text,Result,PassedResultType) :-
  293   has_type(Text,TextType),
  294   has_type(Result,ResultType),
  295   has_type(PassedResultType,PassedResultTypeType),
  296   assertion(member(TextType,[atom,string])),           % has already been check_that-ed
  297   assertion(member(ResultType,[var,string,atom])),     % has already been check_that-ed
  298   assertion(member(PassedResultTypeType,[var,atom])),  % has already been check_that-ed (also, if atom, it is one of 'atom', 'string')
  299   complete_result_type_2(TextType,ResultType,PassedResultTypeType,PassedResultType), % this throws, or fails or succeeds, with PassedResultType instantiated
  300   !,                                                   % complete_result_type_2 generates choicepoint we don't want!
  301   assertion(check_that(PassedResultType,hard(stringy_typeid))).   % PassedResultType must be instantiated now!
  302
  303%                            ResultType
  304%                    TextType    |  PassedResultTypeType
  305%                       |        |        |        +-------PassedResultType (may be var on call, as indicated by the preceding arg)
  306%                       |        |        |        |
  307complete_result_type_2(atom   , var    , var   , atom   ).         % Guess: We want PassedResultType (unbound on call) to be the atom 'atom' because the input texts are both atom
  308complete_result_type_2(string , var    , var   , string ).         % Guess: We want PassedResultType (unbound on call) to be the atom 'string' because the input texts are both string
  309complete_result_type_2( _     , string , var   , string ).         % Set: We definitely want PassedResultType (unbound on call) to be the atom 'string' because the provided Result is a string
  310complete_result_type_2( _     , atom   , var   , atom   ).         % Set: We definitely want PassedResultType (unbound on call) to be the atom 'atom' because the provided Result is an atom
  311complete_result_type_2( _     , var    , atom  , _      ).         % OK: the result type is specified (atom on 4th arg) but the Result is var, so anything is ok
  312complete_result_type_2( _     , string , atom  , atom   ) :- fail. % FAIL: the result is specified and 'string' but the ResultType is provided and is 'atom'
  313complete_result_type_2( _     , atom   , atom  , string ) :- fail. % FAIL: the result is specified and 'atom'   but the ResultType is provided and is 'string'
  314complete_result_type_2( _     , string , atom  , string ).         % OK: the result is specified and 'string' and the ResultType is provided and is 'string'
  315complete_result_type_2( _     , atom   , atom  , atom   ).         % OK: the result is specified and 'atom'   and the ResultType is provided and is 'atom'
  316
  317has_type(X,var)    :- var(X),!.
  318has_type(X,atom)   :- atom(X),!.
  319has_type(X,string) :- string(X).
  320
  321common_entry_checks(FieldWidth,Text,Result,ResultType) :-
  322   assertion(check_that(FieldWidth, hard(integer), hard(pos0int),     _{name:"FieldWidth"})),
  323   assertion(check_that(Text,       hard(stringy),                    _{name:"Text"})),
  324   assertion(check_that(Result,     break(var), hard(stringy),        _{name:"Result"})),
  325   assertion(check_that(ResultType, break(var), hard(stringy_typeid), _{name:"ResultType"})).
  326
  327% Get OffsetLeft and OffsetRight out of the SettingsDict (if missing, they are assumed 0)
  328
  329decaps_offset_left_right(SettingsDict,OffsetLeft,OffsetRight) :-
  330   get_setting(SettingsDict,offset_left,OffsetLeft,0),
  331   get_setting(SettingsDict,offset_right,OffsetRight,0),
  332   assertion(check_that(OffsetLeft,  hard(integer), _{name:"OffsetLeft"})),
  333   assertion(check_that(OffsetRight, hard(integer), _{name:"OffsetRight"})).
  334
  335% Get CutLeft and CutRight out of the SettingsDict (if missing, they are assumed true)
  336
  337decaps_cut_flags(SettingsDict,CutLeft,CutRight) :-
  338   get_setting(SettingsDict,cut_left,CutLeft,true),
  339   get_setting(SettingsDict,cut_right,CutRight,true),
  340   assertion(check_that(CutLeft,  hard(boolean), _{name:"CutLeft"})),
  341   assertion(check_that(CutRight, hard(boolean), _{name:"CutRight"})).
  342
  343% Get Offset out of the SettingsDict (if missing, it is assumed 0)
  344
  345decaps_offset(SettingsDict,Offset) :-
  346   get_setting(SettingsDict,offset,Offset,0),
  347   assertion(check_that(Offset, hard(integer), _{name:"Offset"})).
  348
  349% Get Prefer out of the SettingsDict (if missing, it is assumed leftly)
  350
  351decaps_prefer(SettingsDict,Prefer) :-
  352   get_setting(SettingsDict,prefer,Prefer,leftly),
  353   assertion(check_that(Prefer, hard(member(leftly,rightly)), _{name:"Prefer"}))