json_convert.pl -- Convert between JSON terms and Prolog application terms
The idea behind this module is to provide a flexible high-level mapping
between Prolog terms as you would like to see them in your application
and the standard representation of a JSON object as a Prolog term. For
example, an X-Y point may be represented in JSON as {"x":25,
"y":50}
. Represented in Prolog this becomes json([x=25,y=50])
, but
this is a pretty non-natural representation from the Prolog point of
view.
This module allows for defining records (just like library(record)) that provide transparent two-way transformation between the two representations.
:- json_object point(x:integer, y:integer).
This declaration causes prolog_to_json/2 to translate the native Prolog representation into a JSON Term:
?- prolog_to_json(point(25,50), X). X = json([x=25, y=50])
A json_object/1 declaration can define multiple objects separated by a
comma (,), similar to the dynamic/1 directive. Optionally, a declaration
can be qualified using a module. The conversion predicates
prolog_to_json/2 and json_to_prolog/2 first try a conversion associated
with the calling module. If not successful, they try conversions
associated with the module user
.
JSON objects have no type. This can be solved by adding an extra field
to the JSON object, e.g. {"type":"point", "x":25, "y":50}
. As Prolog
records are typed by their functor we need some notation to handle this
gracefully. This is achieved by adding +Fields to the declaration. I.e.
:- json_object point(x:integer, y:integer) + [type=point].
Using this declaration, the conversion becomes:
?- prolog_to_json(point(25,50), X). X = json([x=25, y=50, type=point])
The predicate json_to_prolog/2 is often used after http_read_json/2 and prolog_to_json/2 before reply_json/1. For now we consider them separate predicates because the transformation may be too general, too slow or not needed for dedicated applications. Using a separate step also simplifies debugging this rather complicated process.
- current_json_object(Term, Module, Fields)[multifile]
- Multifile predicate computed from the json_object/1
declarations. Term is the most general Prolog term representing
the object. Module is the module in which the object is defined
and Fields is a list of
f(Name, Type, Default, Var)
, ordered by Name. Var is the corresponding variable in Term. - json_object(+Declaration)
- Declare a JSON object. The declaration takes the same format as
using in record/1 from library(record). E.g.
?- json_object point(x:int, y:int, z:int=0).
The type arguments are either types as know to library(error) or functor names of other JSON objects. The constant
any
indicates an untyped argument. If this is a JSON term, it becomes subject to json_to_prolog/2. I.e., using the typelist(any)
causes the conversion to be executed on each element of the list.If a field has a default, the default is used if the field is not specified in the JSON object. Extending the record type definition, types can be of the form (Type1|Type2). The type
null
means that the field may not be present.Conversion of JSON to Prolog applies if all non-defaulted arguments can be found in the JSON object. If multiple rules match, the term with the highest arity gets preference.
- compile_json_objects(+Spec, -Clauses) is det[private]
- Compiles a :- json_object directive into Clauses. Clauses are of
the form:
json_object_to_pairs(Term, Module, Pairs) :- <type-checks on Term>, <make Pairs from Term>.
- record_to_json_clause(+Constructor, +Module, +Type, +Names)[private]
- Create a clause translating the record definition into a pairs representation.
- type_checks(+Types, -VarsIn, -VarsOut, -Goal, +Module) is det[private]
- Goal is a body-term that validates Vars satisfy Types. In
addition to the types accepted by must_be/2, it accepts
any
and Name/Arity. The latter demands a json_object term of the given Name and Arity. - prolog_bool_to_json(+Prolog, -JSON) is semidet[private]
- JSON is the JSON boolean for Prolog. It is a flexible the Prolog
notation for thruth-value, accepting one of
true
,on
or1
for @true and one offalse
,fail
,off
or0
for @false. - type_goal(+Type, +Var, -BodyTerm) is det[private]
- Inline type checking calls.
- clean_body(+BodyIn, -BodyOut) is det[private]
- Cleanup a body goal. Eliminate redundant
true
statements and perform partial evaluation on some commonly constructs that are generated from the has_type/2 clauses in library(error). - current_clause(+Constructor, +Module, +Types, +Defs, +Names, +Extra)[private]
- Create the clause current_json_object/3.
- defaults(+ArgsSpecs, -Defaults, -Args)[private]
- Strip the default specification from the argument specification.
- types(+ArgsSpecs, -Defaults, -Args)[private]
- Strip the default specification from the argument specification.
- prolog_to_json(:Term, -JSONObject) is det
- Translate a Prolog application Term into a JSON object term.
This transformation is based on :- json_object/1 declarations.
If a json_object/1 declaration declares a field of type
boolean
, commonly used thruth-values in Prolog are converted to JSON booleans. Boolean translation accepts one oftrue
,on
,1
, @true,false
,fail
,off
or0
, @false. - json_to_prolog(+JSON, -Term) is det
- Translate a JSON term into an application term. This
transformation is based on :- json_object/1 declarations. An
efficient transformation is non-trivial, but we rely on the
assumption that, although the order of fields in JSON terms is
irrelevant and can therefore vary a lot, practical applications
will normally generate the JSON objects in a consistent order.
If a field in a json_object is declared of type
boolean
, @true and @false are translated totrue
orfalse
, the most commonly used Prolog representation for truth-values. - pairs_to_term(+Pairs, ?Term, +Module) is semidet[private]
- Convert a Name=Value set into a Prolog application term based on json_object/1 declarations. If multiple rules can be created, make the one with the highest arity the preferred one.
- create_rule(+PairArgs, +Module, -ObjectM, -Term, -Body, -Quality) is det[private]
- Create a new rule for dealing with Pairs, a Name=Value list of a
particular order. Here is an example rule:
json_to_prolog_rule([x=X, y=Y], point(X,Y)) :- integer(X), integer(Y).