34
35:- module(broker, []). 36
37:- use_module(library(lists)). 38:- use_module(library(neck)). 39:- use_module(library(codegen)). 40:- use_module(library(change_alias)). 41:- reexport(library(compound_expand)). 42:- reexport(library(interface)). 43:- init_expansors.
59alias_file(RelTo, Alias, File) :-
60 absolute_file_name(Alias, File, [file_type(prolog), relative_to(RelTo)]).
61
62generate_server(File, Alias, Module, AliasTo) -->
63 { prolog_load_context(source, RelTo),
64 atom_concat(Module, '_intf', Interface),
65 atom_concat(Module, '_remt', ImplRemote),
66 atom_concat(Module, '_locl', ImplLocal),
67 generate_intf(File, RelTo, Module, Interface, AliasTo, AliasIntf),
68 generate_locl(File, RelTo, Alias, ImplLocal, AliasTo, AliasIntf),
69 generate_remt('_remt', File, RelTo, Module, ImplRemote, AliasTo, AliasIntf),
70 generate_serv(File, RelTo, Module, AliasTo, AliasServ)
71 },
72 [(:- use_module(AliasServ, []))].
73
74generate_proxy(ImplProxy, File, Module, AliasIntf, AliasTo) -->
75 { prolog_load_context(source, RelTo),
76 generate_remt('', File, RelTo, Module, ImplProxy, AliasTo, AliasIntf),
77 generate_prxy(File, RelTo, Module, ImplProxy, AliasTo, AliasSuff)
78 },
79 [(:- use_module(AliasSuff, []))].
80
81generate_intf(File, RelTo, Module, Interface, AliasTo, AliasIntf) :-
82 generate_file('_intf', File, RelTo, AliasTo, AliasIntf, dump_interface(Module, Interface)).
83
84generate_locl(File, RelTo, Alias, ImplLocal, AliasTo, AliasIntf) :-
85 generate_file('_locl', File, RelTo, AliasTo, _, dump_local(Alias, ImplLocal, AliasIntf)).
86
87generate_remt(Suff, File, RelTo, Module, ImplRemote, AliasTo, AliasIntf) :-
88 generate_file(Suff, File, RelTo, AliasTo, _, dump_remote(Module, ImplRemote, AliasIntf)).
89
90generate_prxy(File, RelTo, Module, ImplRemote, AliasTo, AliasSuff) :-
91 atom_concat(ImplRemote, '_serv', ModuleServ),
92 generate_file('_serv', File, RelTo, AliasTo, AliasSuff, dump_server(Module, ModuleServ)).
93
94generate_serv(File, RelTo, Module, AliasTo, AliasSuff) :-
95 atom_concat(Module, '_serv', ModuleServ),
96 generate_file('_serv', File, RelTo, AliasTo, AliasSuff, dump_server(Module, ModuleServ)).
97
98:- meta_predicate
99 generate_file(+,+,+,+,+,2). 100
101generate_file(Suffix, File, RelTo, AliasIntf, AliasSuff, Dump) :-
102 change_alias(add_suffix(Suffix), AliasIntf, AliasSuff),
103 alias_file(RelTo, AliasSuff, FileSuff),
104 ( is_newer(FileSuff, File)
105 ->true
106 ; term_to_file(FileSuff, Dump)
107 ).
108
109dump_interface(Module, Interface) -->
110 {module_property(Module, exports(PIL))},
111 [ (:- module(Interface, PIL)),
112 (:- use_module(library(interface))),
113 (:- init_expansors),
114 (:- interface)
115 ].
116
117dump_local(Alias, ImplLocal, AliasIntf) -->
118 [ (:- module(ImplLocal, [])),
119 (:- use_module(library(interface))),
120 (:- reexport(Alias)),
121 (:- init_expansors),
122 (:- implements(AliasIntf))
123 ].
124
125dump_remote(Module, ImplRemote, AliasIntf) -->
126 [ (:- module(ImplRemote, [])),
127 (:- use_module(library(interface))),
128 (:- use_module(library(broker_rt))),
129 (:- init_expansors),
130 (:- implements(AliasIntf))
131 ],
132 findall((H :- remote_call(H, Module)),
133 ( module_property(Module, exports(PIL)),
134 member(F/A, PIL),
135 functor(H, F, A)
136 )).
137
138dump_server(Module, ImplService) -->
139 [ (:- module(ImplService, [])),
140 (:- use_module(library(http/http_dispatch))),
141 (:- use_module(library(http/websocket))),
142 (:- use_module(library(broker_ws))),
143 (:- init_expansors),
144 (:- http_handler(root(broker/Module),
145 http_upgrade_to_websocket(broker_ws(Module), []),
146 [spawn([])]))
147 ].
148
149term_expansion_proxy(ImplRemote, AliasIntf, AliasImpl, AliasPrxy) -->
150 { prolog_load_context(source, RelTo),
151 absolute_file_name(AliasImpl, File, [file_type(prolog), access(read), relative_to(RelTo)]),
152 use_module(AliasImpl, []), 153 module_property(Module, file(File))
154 },
155 generate_proxy(ImplRemote, File, Module, AliasIntf, AliasPrxy).
156
157term_expansion_server(Alias, AliasIntf) -->
158 { prolog_load_context(source, RelTo),
159 absolute_file_name(Alias, File, [file_type(prolog), access(read), relative_to(RelTo)]),
160 use_module(Alias, []), 161 module_property(Module, file(File))
162 },
163 generate_server(File, Alias, Module, AliasIntf).
164
165term_expansion((:- broker_server(Alias, AliasIntf)), Clauses) :-
166 phrase(term_expansion_server(Alias, AliasIntf), Clauses).
167term_expansion((:- broker_proxy(ImplRemote, AliasIntf, AliasImpl, AliasPrxy)), Clauses) :-
168 phrase(term_expansion_proxy(ImplRemote, AliasIntf, AliasImpl, AliasPrxy), Clauses)
WebSocket broker
WebSocket broker that allows to execute predicates remotely.
balancing roundrobin leastconec
*/