34
35:- module(swish_render_bdd,
36 [ term_rendering//3 37 ]). 38:- use_module('../render'). 39:- use_module(graphviz, []). 40:- use_module(library(clpb)). 41:- use_module(library(varnumbers)). 42
43:- register_renderer(bdd, "Render BDDs corresponding to CLP(B) constraints").
67term_rendering(Goal, Vars, Options) -->
68 ( { Goal = clpb:'$clpb_bdd'(Ns),
69 is_list(Ns) } -> []
70 ; { Goal = sat(Sat0) } ->
71 { current_prolog_flag(clpb_residuals, OldFlag),
72 varnumbers_names(Sat0, Sat, VNames),
73 term_variables(Sat, Vs),
74 setup_call_cleanup(set_prolog_flag(clpb_residuals, bdd),
75 catch((sat(Sat),
76 copy_term(Vs, Vs, [clpb:'$clpb_bdd'(Ns)]),
77 78 maplist(del_attrs, Vs),
79 throw(nodes(Vs,Ns))),
80 81 nodes(Vs,Ns),
82 true),
83 set_prolog_flag(clpb_residuals, OldFlag)),
84 85 maplist(eq, VNames) }
86 ),
87 { nodes_dot_digraph(Ns, Dot) },
88 swish_render_graphviz:term_rendering(Dot, Vars, Options).
89
90eq(Name=Var) :- Name = Var.
91
92nodes_dot_digraph(Nodes, dot(digraph(Stmts))) :-
93 maplist(node_then_else, Nodes, Thens, Elses),
94 phrase((nodes_labels(Nodes),
95 [node(false, [fontname='Palatino-Bold']),
96 node(true, [fontname='Palatino-Bold'])],
97 [edge([style='filled'])],
98 list(Thens),
99 [edge([style='dotted'])],
100 list(Elses)), Stmts).
101
102nodes_labels([]) --> [].
103nodes_labels([node(N)-(v(Var,_) -> _ ; _)|Nodes]) -->
104 [node(N, [label=Var])],
105 nodes_labels(Nodes).
106
107node_then_else(Node-(_->Then0;Else0), (ID->Then), (ID->Else)) :-
108 maplist(node_id, [Node,Then0,Else0], [ID,Then,Else]).
109
110node_id(node(N), N).
111node_id(true, true).
112node_id(false, false).
113
114list([]) --> [].
115list([L|Ls]) --> [L], list(Ls)
Render Binary Decision Diagrams (BDDs)
This renderer draws Binary Decision Diagrams (BDDs) that express CLP(B) constraints.
Both kinds of residual goals that
library(bdd)
can emit are supported by this renderer: By default,library(clpb)
emits sat/1 residual goals. These are first translated to BDDs by reposting the goals while temporarily settingclpb_residuals
tobdd
. The translation of such BDDs to dot/1 terms is straight-forward. Alternatively, you can setclpb_residuals
tobdd
yourself. In that case, residual goals are directly emitted as BDDs and are again translated to dot/1 terms by this renderer.In both cases, the graphviz renderer is used for the final output.
*/