1:- module(djson, [ json//1
    2                 , json_term/2
    3                 , is_like_json/1
    4                 ]
    5         ).    6
    7:- use_module(library(apply), [maplist/3]).    8:- use_module(library(http/json)).    9:- use_module(library(list_util)).
 json_term(+Json:atom, -Term) is multi
json_term(-Json:atom, +Term) is det
True if Json is a serialization of Term in JSON notation. For single use, Term can be a Prolog term with JSON-like notation. For example,
Term = {
    name: Name,
    occupation: Job
}

json_term/2 considers it acceptable for Json to have extraneous fields that are not present in Term. This allows one to pattern match against a Json document without having to specify every imagineable key.

When dealing repeatedly with the same terms and JSON structures, it's most convenient to declare additional clauses for json//1.

   31json_term(Json, Term) :-
   32    ( ground(Json) ->
   33        atom_json_term(Json, JsonTerm, []),
   34        json(Term, JsonTerm, _)
   35    ; true -> % assume Term is ready to convert
   36        json(Term, JsonTerm, _),
   37        finalize(JsonTerm),
   38        is_json_term(JsonTerm, []),
   39        !,
   40        atom_json_term(Json, JsonTerm, [as(atom)])
   41    ).
   42
   43
   44% convert difference lists into proper lists, recursively inside a
   45% library(http/json) term.
   46finalize(X) :-
   47    var(X),
   48    !,
   49    X=[].
   50finalize(json(J)) :-
   51    !,
   52    finalize(J).
   53finalize([_Key=Value|T]) :-
   54    !,
   55    finalize(Value),
   56    finalize(T).
   57finalize([H|T]) :-
   58    !,
   59    finalize(H),
   60    finalize(T).
   61finalize(_).
 json(?Term)//
Multifile hook for declaring a JSON-Prolog relation. When adding clauses to this predicate, one typically calls json//1 recursively with a JSON-like argument to describe the desired structure.

For example,

:- multifile djson:json//1.
djson:json(person(Name,Age)) -->
    json({ name: Name, age: Age }).
   75:- multifile json//1.   76json(X, X, _) :-
   77    member(TypeCheck, [atom, integer, float]),
   78    call(TypeCheck, X),
   79    !.
   80json({}, json([]), _).
   81json({Pairs}, json(J0), json(J)) :-
   82    ( var(Pairs) ->
   83        maplist(eq_colon,J0,Pairs0),
   84        xfy_list(',', Pairs, Pairs0),
   85        J = []
   86    ; Pairs=(Key:Value0) ->
   87        once(select(Key=Value, J0, J)),
   88        json(Value0, Value, _)
   89    ; Pairs=(Key:Value0,Rest) ->
   90        once(select(Key=Value,J0,J1)),
   91        json(Value0, Value, _),
   92        json({Rest}, json(J1), json(J))
   93    ).
   94json([], [], _).
   95json([H|T], [JH|JT], _) :-
   96    json(H, JH, _),
   97    json(T, JT, _).
   98json(json(J),json(J),_).
   99
  100
  101eq_colon(K=V0,K:V) :-
  102    json(V, V0, _),
  103    is_like_json(V).
 is_like_json(+Term) is semidet
True if Term is JSON-like. A JSON-like term is one that looks the same as JSON notation. For example,
?- is_like_json({ hi: world }).
true.
?- is_like_json([ a, b, 73 ]).
true.
?- is_like_json(foo(_,_)).
false.
  117is_like_json(Atom) :-
  118    atom(Atom),
  119    !.
  120is_like_json(Number) :-
  121    number(Number),
  122    !.
  123is_like_json([]).
  124is_like_json({}).
  125is_like_json([H|T]) :-
  126    is_like_json(H),
  127    is_like_json(T).
  128is_like_json({_:V}) :-
  129    !,
  130    is_like_json(V).
  131is_like_json({_:V, Rest}) :-
  132    is_like_json(V),
  133    is_like_json({Rest}).
  134is_like_json(json(_)) :-
  135    !,
  136    fail