34
35:- module(swish_csv, []). 36:- use_module(library(pengines), []). 37:- use_module(library(pairs)). 38:- use_module(library(csv), [csv_write_stream/3]). 39:- use_module(library(apply)). 40:- use_module(library(pprint)). 41:- use_module(library(option)). 42:- use_module(library(http/http_cors)). 43:- use_module(library(debug)). 44:- use_module(library(lists)).
56:- multifile
57 pengines:write_result/3,
58 write_answers/2, 59 write_answers/3.
66pengines:write_result(csv, Event, OptionDict) :-
67 ( Disposition = OptionDict.get(disposition)
68 -> Options = [disposition(Disposition)]
69 ; Options = []
70 ),
71 csv(Event, Options).
72
73csv(create(_Id, Features), Options) :- !,
74 memberchk(answer(Answer), Features),
75 csv(Answer, Options).
76csv(destroy(_Id, Wrapped), Options) :- !,
77 csv(Wrapped, Options).
78csv(success(_Id, Answers, Projection, _Time, More), Options) :- !,
79 VarTerm =.. [row|Projection],
80 success(Answers, VarTerm, [more(More)|Options]).
81csv(error(_Id, Error), _Options) :- !,
82 message_to_string(Error, Msg),
83 format('Status: 400 Bad request~n'),
84 format('Content-type: text/plain~n~n'),
85 format('ERROR: ~w~n', [Msg]).
86csv(output(_Id, message(_Term, _Class, HTML, _Where)), _Opts) :- !,
87 format('Status: 400 Bad request~n'),
88 format('Content-type: text/html~n~n'),
89 format('<html>~n~s~n</html>~n', [HTML]).
90csv(page(Page, Event), Options) :-
91 csv(Event, [page(Page)|Options]).
92csv(failure(_Id, _Time), Options) :- !,
93 success([], -, [more(false)|Options]).
94csv(Event, _) :-
95 print_term(Event, [output(user_error)]).
96
97success(Answers, VarTerm, Options) :-
98 write_answers(Answers, VarTerm, Options), !.
99success(Answers, VarTerm, Options) :-
100 write_answers(Answers, VarTerm), !,
101 assertion(\+option(page(_), Options)).
102success(Answers, _VarTerm, Options) :-
103 option(page(Page), Options),
104 Page > 1, !,
105 maplist(csv_answer, Answers, Rows),
106 forall(paginate(100, OutPage, Rows),
107 csv_write_stream(current_output, OutPage, [])).
108success(Answers, VarTerm, Options) :-
109 option(disposition(Disposition), Options, 'swish-result.csv'),
110 maplist(csv_answer, Answers, Rows),
111 cors_enable,
112 format('Content-encoding: chunked~n'),
113 format('Content-disposition: attachment; filename="~w"~n', [Disposition]),
114 format('Content-type: text/csv~n~n'),
115 projection_row(VarTerm),
116 forall(paginate(100, Page, Rows),
117 csv_write_stream(current_output, Page, [])).
118
119projection_row(-) :- !.
120projection_row(row) :- !.
121projection_row(VarTerm) :-
122 csv_write_stream(current_output, [VarTerm], []).
123
124paginate(Len, Page, List) :-
125 length(Page0, Len),
126 ( append(Page0, Rest, List)
127 -> ( Page = Page0
128 ; paginate(Len, Page, Rest)
129 )
130 ; Page = List
131 ).
132
133
134csv_answer(JSON, Row) :-
135 is_dict(JSON), !,
136 dict_pairs(JSON, _, Pairs),
137 pairs_values(Pairs, Values),
138 maplist(csv_value, Values, CVSValues),
139 Row =.. [row|CVSValues].
140csv_answer(RowIn, Row) :-
141 compound(RowIn), !,
142 RowIn =.. [_|Values],
143 maplist(csv_value, Values, CVSValues),
144 Row =.. [row|CVSValues].
145
146csv_value(Var, '') :-
147 var(Var), !.
148csv_value(Number, Number) :-
149 number(Number), !.
150csv_value(Atom, Atom) :-
151 atom(Atom), !.
152csv_value(String, String) :-
153 string(String), !.
154csv_value(Term, Value) :-
155 term_string(Term, Value)
Support CSV output from a Pengines server
This module defines the result-format
csv
for Pengines. It allows SWISH users to post a query against the core Prolog system or a saved SWISH program and obtain the results using a simple web client such ascurl
. An example shell script is provided inclient/swish-ask.sh
.