1:- module(json_answer, [query/1, query/2, term_to_dict/2, term_to_dict_list/2]).    2:- use_module(library(http/json)).

Parse prolog compound terms into json

This is a convenience module to convert a prolog query into a JSON answer for IPC /

 lowercase_atom(+Atom, -Atom)
Lowers only the first character, so that a var name can be camel-cased
   11lowercase_atom(Atom, Atom2) :-
   12    atom_string(Atom, String),
   13    string_to_list(String, [C|Ls]),
   14    to_upper(C2, C),
   15    string_to_list(String2, [C2|Ls]),
   16    atom_string(Atom2, String2).
 lower_var(+VarEq, -VarEqLower) is semidet
Lowers the variable name of a ['X'=_A, 'Y'=_B] -esque value
See also
- lowercase_atom/2
   23lower_var(VarEq, VarEqLower) :-
   24    VarEq =.. [=, Key, Val],
   25    lowercase_atom(Key, Key2),
   26    VarEqLower =.. [=, Key2, Val].
 query(+Term, +Stream) is semidet
Writes the JSON to the given stream
deprecated
- term_to_dict_list/2
   33query(Qs, OutputStream) :-
   34    open_string(Qs, S),
   35    read_term(S, T, [variable_names(Vars)]),
   36    maplist(lower_var, Vars, Vars2),
   37    dict_create(Dict, _, Vars2),
   38    bagof(Dict, T, Res),
   39    atom_json_dict(Json, Res, []),
   40    write(OutputStream, Json).
 query(+Term) is semidet
Outputs JSON to current_output
deprecated
- term_to_dict_list/2
   47query(Qs) :-
   48    query(Qs, current_output).
 term_to_dict(+Term, -Dict) is semidet
Converts a compound term to a dict
   53term_to_dict(Term, Dict) :-
   54    (Term =.. [:,_,UnscopedTerm] ->
   55     term_to_dict(UnscopedTerm, Dict) ;
   56     (compound(Term), not(is_list(Term)) ->
   57          Term =.. [Key, Value | Values],
   58          (member(_, Values) ->
   59               maplist(term_to_dict, [Value|Values], DictValue) ;
   60           term_to_dict(Value, DictValue)
   61          ),
   62          dict_create(Dict, _, [Key-DictValue]) ;
   63      (is_list(Term) ->
   64           maplist(term_to_dict, Term, Dict) ;
   65       Dict = Term)
   66     )
   67    ).
 term_to_dict_list(+Term, -DictList) is semidet
Converts a compound term to a list of dicts
?- assert(friend(alex, luke)),
   assert(friend(donna, eric)),
   assert(friend(donna, mary)).
true
?- term_to_dict_list(friend(donna, _), DictList),
   json:json_write_dict(current_output, DictList).
[ {"friend": ["donna", "eric" ]},  {"friend": ["donna", "mary" ]} ]
DictList = [_{friend:[donna, eric]}, _{friend:[donna, mary]}].
   83term_to_dict_list(Term, DictList) :-
   84    callable(Term),
   85    findall(Dict, (call(Term), term_to_dict(Term, Dict)), DictList)