34
35:- module(sparql_json_result,
36 [ sparql_write_json_result/3 37 ]). 38:- use_module(library(http/http_json)). 39:- use_module(library(sgml_write)). 40:- use_module(library(apply)). 41:- use_module(library(option)). 42:- use_module(library(semweb/rdf_db)).
51sparql_json_mime_type(application/'sparql-results+json; charset=UTF-8').
59sparql_write_json_result(Out, select(VarTerm, Rows), Options) :-
60 VarTerm =.. [_|VarNames],
61 JSON = json([ head = json([vars=VarNames]),
62 results = json([bindings=Bindings])
63 ]),
64 maplist(row_to_json(VarNames), Rows, Bindings),
65 ( option(content_type(_), Options)
66 -> JSONOptions = Options
67 ; sparql_json_mime_type(Mime),
68 JSONOptions = [content_type(Mime)|Options]
69 ),
70 with_output_to(Out, reply_json(JSON, JSONOptions)).
71sparql_write_json_result(Out, ask(True), Options) :-
72 JSON = json([ head = json([]),
73 boolean = @(True)
74 ]),
75 ( option(content_type(_), Options)
76 -> JSONOptions = Options
77 ; sparql_json_mime_type(Mime),
78 JSONOptions = [content_type(Mime)|Options]
79 ),
80 with_output_to(Out, reply_json(JSON, JSONOptions)).
81
82
83row_to_json(Vars, Row, json(Bindings)) :-
84 var_col_bindings(Vars, 1, Row, Bindings).
85
86var_col_bindings([], _, _, []).
87var_col_bindings([V0|T0], I, Row, Bindings) :-
88 arg(I, Row, Value),
89 I2 is I + 1,
90 ( Value = '$null$' 91 -> var_col_bindings(T0, I2, Row, Bindings)
92 ; Bindings = [V0=json(JSON)|T],
93 rdf_term_to_json(Value, JSON),
94 var_col_bindings(T0, I2, Row, T)
95 ).
104rdf_term_to_json(literal(Lit), Object) :-
105 !,
106 Object = [type=literal, value=Txt|Rest],
107 literal_to_json(Lit, Txt, Rest).
108rdf_term_to_json(URI0, Object) :-
109 rdf_global_id(URI0, URI),
110 Object = [type=Type, value=URI],
111 object_uri_type(URI, Type).
117literal_to_json(lang(Lang, Text), Text, ['xml:lang'=Lang]) :- !.
118literal_to_json(type(Type, Text0), Text, [datatype=Type]) :-
119 !,
120 to_text(Type, Text0, Text).
121literal_to_json(Txt, Txt, []).
122
123to_text(_Type, Text, Text) :-
124 atomic(Text).
125to_text(Type, DOM, Text) :-
126 rdf_equal(Type, rdf:'XMLLiteral'),
127 !,
128 with_output_to(string(Text),
129 xml_write(DOM, [header(false)])),
130 atomic(Text).
136object_uri_type(URI, Type) :-
137 ( rdf_is_bnode(URI)
138 -> Type = bnode
139 ; Type = uri
140 ).
141
142 145
146:- multifile
147 rdf_io:write_table/4. 148
149rdf_io:write_table(json, _, Rows, Options) :-
150 memberchk(variables(Vars), Options),
151 !,
152 ( is_list(Vars)
153 -> VarTerm =.. [vars|Vars]
154 ; VarTerm = Vars
155 ),
156 sparql_write_json_result(current_output, select(VarTerm, Rows),
157 [ content_type(text/plain),
158 Options
159 ])
Write SPARQL results as JSON