34
35:- module(json_rpc_common,
36 [ json_rpc_send/3 37 ]). 38:- autoload(library(json), [json_write_dict/3]). 39:- autoload(library(option), [option/2]).
43json_rpc_send(Stream, Dict, Options) :-
44 option(header(true), Options),
45 !,
46 with_output_to(string(Msg),
47 json_write_dict(current_output, Dict, Options)),
48 utf8_length(Msg, Len),
49 format(Stream,
50 'Content-Length: ~d\r\n\r\n~s', [Len, Msg]),
51 flush_output(Stream).
52json_rpc_send(Stream, Dict, Options) :-
53 with_output_to(Stream,
54 json_write_dict(Stream, Dict, Options)),
55 flush_output(Stream).
56
57utf8_length(String, Len) :-
58 setup_call_cleanup(
59 open_null_stream(Null),
60 ( set_stream(Null, encoding(utf8)),
61 format(Null, '~s', [String]),
62 flush_output(Null),
63 byte_count(Null, Len)
64 ),
65 close(Null)).
66
67 70
71:- multifile
72 prolog:error_message//1,
73 prolog:message//1. 74
75prolog:error_message(json_rpc_error(Obj)) -->
76 { is_dict(Obj) },
77 json_rpc_error_message(Obj).
78prolog:error_message(json_rpc_error(Obj, Id)) -->
79 { is_dict(Obj) },
80 [ '(async ~p) '-[Id] ],
81 json_rpc_error_message(Obj).
82
83json_rpc_error_message(Obj),
84 Data = Obj.get(Data) ==>
85 json_rpc_error_message_(Obj),
86 [ nl, ' Data: ~p'-[Data] ].
87json_rpc_error_message(Obj) ==>
88 json_rpc_error_message_(Obj).
89
90json_rpc_error_message_(Obj),
91 #{code:Code, message:Message} :< Obj,
92 between(-32768, -32000, Code) ==>
93 [ 'JSON RPC error ~d: ~s'-[Code, Message] ].
94json_rpc_error_message_(Obj),
95 #{code:Code, message:Message} :< Obj ==>
96 [ 'JSON RPC application error ~d: ~s'-[Code, Message] ].
97
98prolog:message(json_rpc(Msg)) -->
99 json_rpc_message(Msg).
100
101json_rpc_message(not_implemented(Method, Params)) -->
102 [ 'No implementation for ~p using paramenters ~p'-
103 [Method, Params]
104 ]