1:- module(onepointfour_basics_dict_pp, 2 [ 3 dict_pp/1 % dict_pp(+Dict) 4 ,dict_pp/2 % dict_pp(+Dict,+SettingsDict) 5 ,dict_pp/3 % dict_pp(+Dict,+SettingsDict,-Lines) 6 ]). 7 8:- use_module(library('onepointfour_basics/checks.pl')). 9:- use_module(library('onepointfour_basics/dict_pp/topmost.pl')). 10 11:- use_module(library(apply)). % meta-call predicates (slow) 12:- use_module(library(apply_macros)). % rewrite to avoid meta-calling (transforms the above into fast code)
current_output
. An empty Dict does not lead to failure but to no output.
Wrap this goal with with_output_to/2 to redirect the output to a stream of your choice.
Behaves as dict_pp/3 called with default settings, followed by immediate printing of the resulting Lines.
206dict_pp(Dict) :-
207 dict_pp(Dict,_{}).
current_output
. An empty Dict does not lead to failure but to no output.
Instructions on how to format the output can be given by SettingsDict. The tag of that dict is arbitrary. Default settings are requested by giving an empty dict here.
Wrap this goal with with_output_to/2 to redirect the output to a stream of your choice.
Behaves as dict_pp/3, followed by immediate printing of the resulting lines.
225dict_pp(Dict,SettingsDict) :- 226 dict_pp(Dict,SettingsDict,LinesOut), 227 maplist([Line]>>format("~s~n",[Line]),LinesOut). % All the lines are strings.
Instructions on how to format the output can be given by SettingsDict. The tag of that dict is arbitrary. Default settings are requested by giving an empty dict here.
The following settings are understood. Anything not recognized is disregarded, if a setting is missing when it is needed, the default value is assumed.
key | value | default | explainer |
border | true , false | false | Decorate outermost dict with an ASCII border. |
sub_border | true , false , inherit | inherit | Whether to decorate subdicts with an ASCII border, too. |
tag | true , false | true | Print the tag of the outermost dict. If the tag is an unbound variable, it is never printed. |
sub_tag | true , false , inherit | inherit | Whether to display the tags of subdicts, too. |
justify_key | left , right , center | left | How to justify the keys inside the key column. |
justify_value | left , right , center | left | How to justify the values inside the values column. |
justify_tag | left , right , center | center | How to justify the tag inside the tag line. f stands for "full". |
justify_tag_full | true , false | true | Left and right padding is considered as being part of the tag field. |
spec_float | see format/2 | f | A format/2 specifier used for floats. Passed to format/3 "as is". |
spec_int | see format/2 | d | A format/2 specifier used for integers. Passed to format/3 "as is". |
depth_limit | int >= 0 | 10 | "subdict depth" at which prettyprinting switches to a "one-liner". 0 means even the root dict is printed as a oneliner. |
pad | true , false | false | Switch on padding according to pad_left etc. Note that if pad is true (and border is false ), and none of the pad_X values has been given, then the output is a rectangle filled to rectangle-ness with whitespace. |
sub_pad | true , false , inherit | inherit | Whether to pad subdicts with whitespace, too. |
pad_left | int >= 0 | 0 | Pad with whitespace on the left depending on pad and sub_pad (inside the ASCII border if any). |
pad_right | int >= 0 | 0 | As above, on the right. |
pad_top | int >= 0 | 0 | As above, on top (underneath the tag, if any). |
pad_bottom | int >= 0 | 0 | As above, on the bottom. |
269dict_pp(Dict,SettingsDict,LinesOut) :-
270 assertion(check_that(LinesOut,break(var),hard(list))), % Maybe Lines is a given; that would be extraordinary
271 assertion(check_that(Dict,hard(dict))),
272 assertion(check_that(SettingsDict,hard(dict))),
273 put_dict(depth,SettingsDict,0,SettingsDict2), % Start tracking depth of recursion via 'depth' entry in SettingsDict
274 pp_if_shallow_enough(Dict,SettingsDict2,LinesOut),
275 assertion(check_that(LinesOut,hard(proper_list),hard(passall(string))))
Prettyprinting of SWI-Prolog "dicts"
Predicates
dict_pp(+Dict)
current_output
, assuming default settings.dict_pp(+Dict,+SettingsDict)
current_output
, take settings in SettingsDict.dict_pp(+Dict,+SettingsDict,-Lines)
Examples
Prettyprint Dict to a list of strings with default settings (SettingsDict set to
_{}
). Note that here, Dict has no valid tag.Direct output of result, with some settings.
Direct ouput of result, with different settings. Here, Dict has a valid tag.
Wrap the result in a border.
No border, but with padding around the result.
With both border and padding.
Prettyprint a dict with subdicts.
Prettyprint a dict with subdicts, but suppress the tags.
Prettyprint a dict with subdicts, show the tags, don't show a border.
History
*/