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

dict prettyprinter helper predicates

This module collects a few very simple and very specialized helper predicates dealing with strings in the context of dict prettyprinting, which just add noise to the main module. So they are here, in a separate module.

The homepage for this module is at

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

*/

   49% ***************************************************
   50%  Transforming dict pairs into stringified "entries"
   51% ***************************************************
 pairs_to_entries(+Pairs, +SettingsDict, -Entries)
Iterates over the pairs Pairs obtained from the dict that shall be printed and transforms them into Entries, a list of structures described below.

Entries contains the transformed pairs in the order in which they appear in Pairs.

Each element in Entries (an "entry") is a pair KeyString-Lineified where:

   74pairs_to_entries(Pairs,SettingsDict,Entries) :-
   75   maplist(mpl_p2e(SettingsDict),Pairs,Entries).
   76
   77mpl_p2e(SettingsDict,Key-Value,KeyString-Lineified) :-
   78   stringify_key(Key,SettingsDict,KeyString),        % straightforward
   79   lineify_value(Value,SettingsDict,Lineified).      % may cause recursion if the value is a dict
   80 
   81% String generation for a dict key. No string justification occurs yet.
   82% "SettingsDict" is currently passed but not yet needed.
   83
   84stringify_key(Key,_SettingsDict,String) :-
   85   (atom(Key)
   86    -> F="~a"
   87    ;  integer(Key)
   88    -> F="~d"
   89    ;  domain_error([atom,integer],Key)), % never happens unless the implementation of dict changes
   90   format(string(String),F,[Key]).
   91
   92% String or multi-string generation for a dict value.
   93
   94% Case of: "Value" is itself a dict.
   95
   96lineify_value(Value,SettingsDict,poly(Lines)) :-    
   97   is_dict(Value),
   98   !,
   99   get_dict(depth,SettingsDict,Depth),                 % depth (the depth of the recursion) must exist
  100   DepthP is Depth+1,
  101   put_dict(depth,SettingsDict,DepthP,SettingsDict2),
  102   pp_if_shallow_enough(Value,SettingsDict2,Lines).    % **** recursive call ***** (max depth reached is examined therein)
  103
  104% Cases of: "Value" is not a dict.
  105
  106lineify_value(Value,SettingsDict,mono(String)) :-
  107   integer(Value),
  108   !,
  109   get_setting(SettingsDict,spec_int,Placeholder,d),
  110   spec_format(Placeholder,Value,String).
  111
  112lineify_value(Value,SettingsDict,mono(String)) :-
  113   float(Value),
  114   !,
  115   get_setting(SettingsDict,spec_float,Placeholder,f),
  116   spec_format(Placeholder,Value,String).
  117 
  118lineify_value(Value,_SettingsDict,mono(String)) :-
  119   string(Value),
  120   !,
  121   format(string(String),"~s",[Value]). % Won't have quotes even if there is whitespace inside
  122
  123lineify_value(Value,_SettingsDict,mono(String)) :-
  124   atom(Value),
  125   !,
  126   format(string(String),"~a",[Value]). % Won't have quotes even if there is whitespace inside
  127
  128lineify_value(Value,_SettingsDict,mono(String)) :-
  129   format(string(String),"~q",[Value]). % By default, quote
  130
  131% Print 'Value' according to 'Placeholder' (as opposed to, "according to
  132% a hardcoded format string"), yielding 'String'. We are using "safe_format/3"
  133% in case there is a problem with the format string. Then an exception message
  134% will appear in the output, but no exception will be thrown.
  135
  136spec_format(Placeholder,Value,String) :-
  137   format(string(Format),"~~~s",[Placeholder]),
  138   safe_format(Format,[Value],String).
  139
  140% **********
  141% Handling settings
  142% **********
 get_padding_settings(+SettingDict, -PadTop, -PadBottom, -PadLeft, -PadRight)
Get multiple specific values, those for paddings, in one call. This predicate also checks that the retrieved values are all integers >= 0.
  149get_padding_settings(SettingsDict,PadTop,PadBottom,PadLeft,PadRight) :-
  150   get_setting(SettingsDict,pad_top,    PadTop    ,0),
  151   get_setting(SettingsDict,pad_bottom, PadBottom ,0),
  152   get_setting(SettingsDict,pad_left,   PadLeft   ,0),
  153   get_setting(SettingsDict,pad_right,  PadRight  ,0),
  154   check_that(PadTop,hard(pos0int)),
  155   check_that(PadBottom,hard(pos0int)),
  156   check_that(PadLeft,hard(pos0int)),
  157   check_that(PadRight,hard(pos0int)).
 get_padding_settings_clamped(+DecisionForPadding, +SettingsDict, -PadTop, -PadBottom, -PadLeft, -PadRight)
Get the settings for the padding, but clamp them all to 0 if DecisionForPadding is false.
  163get_padding_settings_clamped(false,_,0,0,0,0) :- !.
  164
  165get_padding_settings_clamped(true,SettingsDict,PadTop,PadBottom,PadLeft,PadRight) :-
  166   get_padding_settings(SettingsDict,PadTop,PadBottom,PadLeft,PadRight)