1:- module(onepointfour_dict_pp_lineify,
    2          [
    3           lineify/4 % lineify(+Entries,+SettingsDict,?LinesTip,?FinalFin)
    4          ]).    5
    6:- use_module(library('onepointfour_basics/checks.pl')).    7:- use_module(library('onepointfour_basics/stringy_concat.pl')).    8:- use_module(library('onepointfour_basics/space_stringy.pl')).    9:- use_module(library('onepointfour_basics/dict_settings.pl')).   10:- use_module(library('onepointfour_basics/stringy_justify.pl')).   11:- use_module(library('onepointfour_basics/meta_helpers.pl')).   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

Transforming a list of entries (key-value pairs) generated from a dict, "Entries", into a list of strings (nearly) ready for output and appending them to an open difference list.

The homepage for this module is at

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

*/

 lineify(+Entries, +SettingsDict, ?LinesTip, ?FinalFin)
Given the list of entries Entries, which is a list of pairs -(KeyString,Lineified), and an "open difference list" LinesTip-FinalFin as receiver, generate a string (a "line") for each entry in Entries and add it to the growing list rooted at LinesTip. The "fin2 of the open difference list will be unified with FinalFin.

All we do here is concatenate keys (strings), separators (strings) and values (either strings or lists of strings) into lines (a list of strings).

A diagram for orientation. The | are not in the result, they have been added for legibility. Note that a line from a poly/1 compound term may be longer than MaxMonoWidth as it may contain arbitrary results of prettyprinting subdicts.

           keys                              values
  |<---- MaxKeyWidth --->|<--Sep-->|<-----MaxMonoWidth---->|
  |KKKKKKKKKK            |    :    |VVVV                   |    from mono("VVVV")
  |KKKKKKKKKKKKKKKKKKKKKK|    :    |VVVVVVV                |    from mono("VVVVVVV")
  |KKKKKK                |    :    |VVVVVVVVVVV            |    from mono("VVVVVVVVVVV")
  |KKKKKKKKKK            |    :    |poly#1PPPPPPPPPP       |    from poly([str,str,str])
  |                      |         |poly#2PPPPPPPPPPPPPPPPPPPPPPPPP
  |                      |         |poly#3PPPPPPPPPPPPPPPPPPPP
  |KKKKKKKKKKKKKKK       |    :    |VVVVVVVVVVVVVVVVVVVVVVV|    from mono("VVVVVVVVVVVVVVVVVVVVVVV")
   77lineify(Entries,SettingsDict,LinesTip,FinalFin) :-
   78   max_key_width(Entries,MaxKeyWidth),
   79   max_mono_width(Entries,MaxMonoWidth),
   80   lineify_entries(
   81      Entries,
   82      _{max_key_width:MaxKeyWidth,
   83        max_mono_width:MaxMonoWidth,
   84        settings_dict:SettingsDict},  % use a parameter dict for readability
   85      LinesTip,FinalFin).
   86
   87% lineify_entries(+Entries,+MaxKeyWidth,+MaxMonoWidth,+SettingsDict,?LinesTip,?FinalFin).
   88%
   89% A loop over the list of entries Entries.
   90%
   91% Depending on whether the head entry is a pair with a mono(String) or poly(Lines)
   92% on second place, one or more than one lines may be added to the LinesTip-FinalFin
   93% open difference list.
   94
   95% Base case of the empty "Entries" list. LinesTip short-circuits to FinalFin
   96% (empty open difference list).
   97
   98lineify_entries([],_,TipIsFin,TipIsFin).
   99
  100% Case of a pair with a mono(String) on second place.
  101
  102lineify_entries([KeyString-mono(MonoString)|MoreEntries],Params,[Line|MoreLines],FinalFin) :-
  103   !,
  104   justify_key(Params.settings_dict,KeyString,Params.max_key_width,KeyStringOut),
  105   justify_mono(Params.settings_dict,MonoString,Params.max_mono_width,MonoStringOut),
  106   separator(Sep),
  107   stringy_concat([KeyStringOut,Sep,MonoStringOut],Line,string),
  108   lineify_entries(MoreEntries,Params,MoreLines,FinalFin).
  109
  110% Case where "Lineified" contains multiple lines ("poly") but the count of lines is actually 0.
  111% In that case, only the relevant key and a separator are printed.
  112
  113lineify_entries([KeyString-poly([])|MoreEntries],Params,[Line|MoreLines],FinalFin) :-
  114   !,
  115   poly_first_line(KeyString,"",Params,Line),
  116   lineify_entries(MoreEntries,Params,MoreLines,FinalFin).
  117
  118% Case where "Lineified" contains multiple lines ("poly") and the count of lines is at least 1.
  119% They are all appended to the open difference list.
  120
  121lineify_entries([KeyString-poly([Poly|MorePoly])|MoreEntries],Params,Lines,FinalFin) :-
  122   filler_string(Params.max_key_width,Filler),
  123   poly_first_line(KeyString,Poly,Params,FirstLine),
  124   Lines=[FirstLine|Fin1], % could also be put into the header
  125   maplist_onto_open_list(
  126      ({Filler}/[PolyX,Concatted]>>stringy_concat([Filler,PolyX],Concatted,string)),
  127      MorePoly,
  128      Fin1,
  129      Fin2),
  130   lineify_entries(MoreEntries,Params,Fin2,FinalFin).
  131
  132% Find the max key width in "Entries" which is a list "KeyString-Lineified"
  133
  134max_key_width(Entries,Max) :-
  135   foldl(foldl_mkw,Entries,0,Max).
  136
  137foldl_mkw(String-_,FromLeft,ToRight) :-
  138   string_length(String,Width),
  139   ToRight is max(FromLeft,Width).
  140
  141% Find the maximum width of any string appearing in a mono(String) value of an entry
  142% i.e. the entry looks like "KeyString-mono(String)"
  143
  144max_mono_width(Entries,Max) :-
  145   foldl(foldl_mmw,Entries,0,Max).
  146
  147foldl_mmw(_-mono(String),FromLeft,ToRight) :-
  148   !,
  149   string_length(String,Width),
  150   ToRight is max(FromLeft,Width).  % maxify in case of mono(_)
  151
  152foldl_mmw(_-poly(_),PassThrough,PassThrough). % disregard in case of poly(_)
  153
  154% Construct the first line for a "poly" case
  155
  156poly_first_line(KeyString,ValueSideString,Params,LineOut) :-
  157   justify_key(Params.settings_dict,KeyString,Params.max_key_width,K),
  158   separator(Sep),
  159   stringy_concat([K,Sep,ValueSideString],LineOut,string).
  160
  161% Justify a "mono" value (which is string)
  162
  163% TODO: After justification, StringOut may have trailing whitespace due to
  164% both a mix of trailing whitespace present in StringIn (ok) and whitespace
  165% of the "whitespace string" of width "Width" which is created for justification.
  166% One may not always want the latter.
  167
  168justify_mono(SettingsDict,StringIn,Width,StringOut) :-
  169   get_setting(SettingsDict,justify_value,How,left),
  170   justify_how(How,Width,StringIn,StringOut,string).
  171
  172% Justify a key (which is a string) inside a field of width Width
  173
  174justify_key(SettingsDict,StringIn,Width,StringOut) :-
  175   get_setting(SettingsDict,justify_key,How,left),
  176   justify_how(How,Width,StringIn,StringOut,string).
  177
  178% Construct a filler string for a "poly" case beyond the first line.
  179
  180filler_string(Width,StringOut) :-
  181   space_stringy(Width,Spaces,string),  
  182   empty_separator(Sep),
  183   stringy_concat([Spaces,Sep],StringOut,string).
  184
  185% The separator separating a key from a value, and the empty separator
  186% used if the value consists of several lines. Both should have the same width.
  187
  188separator(" : ").
  189empty_separator("   ")