37
38:- module('$history',
39 [ read_term_with_history/2 40 ]). 41
42:- multifile
43 prolog:history/2. 44
49
50read_term_with_history(Term, Options) :-
51 '$option'(prompt(Prompt), Options, '~! ?-'),
52 '$option'(input(Input), Options, user_input),
53 repeat,
54 prompt_history(Prompt),
55 '$toplevel':read_query_line(Input, Raw),
56 read_history_(Raw, Term, Options),
57 !.
58
59read_history_(Raw, _Term, Options) :-
60 '$option'(show(Raw), Options, history),
61 list_history,
62 !,
63 fail.
64read_history_(Raw, _Term, Options) :-
65 '$option'(help(Raw), Options, '!help'),
66 '$option'(show(Show), Options, '!history'),
67 print_message(help, history(help(Show, Raw))),
68 !,
69 fail.
70read_history_(Raw, Term, Options) :-
71 expand_history(Raw, Expanded, Changed),
72 add_to_history(Expanded, Options),
73 '$option'(module(Module), Options, Var),
74 ( Module == Var
75 -> '$current_typein_module'(Module)
76 ; true
77 ),
78 '$option'(variable_names(Bindings), Options, Bindings0),
79 catch(read_term_from_atom(Expanded, Term0,
80 [ module(Module),
81 variable_names(Bindings0)
82 ]),
83 E,
84 ( print_message(error, E),
85 fail
86 )),
87 ( var(Term0)
88 -> Term = Term0,
89 Bindings = Bindings0
90 ; ( Changed == true
91 -> print_message(query, history(expanded(Expanded)))
92 ; true
93 ),
94 Term = Term0,
95 Bindings = Bindings0
96 ).
97
101
102list_history :-
103 prolog:history(current_input, events(Events0)),
104 !,
105 '$reverse'(Events0, Events),
106 print_message(query, history(history(Events))).
107list_history :-
108 print_message(query, history(no_history)).
109
114
115prompt_history('') :-
116 !,
117 ttyflush.
118prompt_history(Prompt) :-
119 ( prolog:history(current_input, curr(Curr, _))
120 -> This is Curr + 1
121 ; This = 1
122 ),
123 atom_codes(Prompt, SP),
124 atom_codes(This, ST),
125 ( atom_codes('~!', Repl),
126 substitute(Repl, ST, SP, String)
127 -> prompt1(String)
128 ; prompt1(Prompt)
129 ),
130 ttyflush.
131
135
136substitute(Old, New, String, Substituted) :-
137 '$append'(Head, OldAndTail, String),
138 '$append'(Old, Tail, OldAndTail),
139 !,
140 '$append'(Head, New, HeadAndNew),
141 '$append'(HeadAndNew, Tail, Substituted).
142
147
148add_to_history(end_of_file, _) :- !.
149add_to_history(Line, Options) :-
150 '$option'(no_save(NoSave), Options),
151 catch(term_string(Query, Line), error(_,_), fail),
152 nonvar(Query),
153 memberchk(Query, NoSave),
154 !.
155add_to_history(Line, _Options) :-
156 format(string(CompleteLine), '~W~W',
157 [ Line, [partial(true)],
158 '.', [partial(true)]
159 ]),
160 catch(prolog:history(user_input, add(CompleteLine)), _, fail),
161 !.
162add_to_history(_, _).
163
174
175expand_history(Raw, Expanded, Changed) :-
176 atom_chars(Raw, RawString),
177 expand_history2(RawString, ExpandedString, Changed),
178 atom_chars(Expanded, ExpandedString),
179 !.
180
181expand_history2([!], [!], false) :- !.
182expand_history2([!, C|Rest], [!|Expanded], Changed) :-
183 not_event_char(C),
184 !,
185 expand_history2([C|Rest], Expanded, Changed).
186expand_history2([!|Rest], Expanded, true) :-
187 !,
188 match_event(Rest, Event, NewRest),
189 '$append'(Event, RestExpanded, Expanded),
190 !,
191 expand_history2(NewRest, RestExpanded, _).
192expand_history2(['\''|In], ['\''|Out], Changed) :-
193 !,
194 skip_quoted(In, '\'', Out, Tin, Tout),
195 expand_history2(Tin, Tout, Changed).
196expand_history2(['"'|In], ['"'|Out], Changed) :-
197 !,
198 skip_quoted(In, '"', Out, Tin, Tout),
199 expand_history2(Tin, Tout, Changed).
200expand_history2([H|T], [H|R], Changed) :-
201 !,
202 expand_history2(T, R, Changed).
203expand_history2([], [], false).
204
205skip_quoted([Q|T],Q,[Q|R], T, R) :- !.
206skip_quoted([\,Q|T0],Q,[\,Q|T], In, Out) :-
207 !,
208 skip_quoted(T0, Q, T, In, Out).
209skip_quoted([Q,Q|T0],Q,[Q,Q|T], In, Out) :-
210 !,
211 skip_quoted(T0, Q, T, In, Out).
212skip_quoted([C|T0],Q,[C|T], In, Out) :-
213 !,
214 skip_quoted(T0, Q, T, In, Out).
215skip_quoted([], _, [], [], []).
216
221
222get_last_event(Event) :-
223 prolog:history(current_input, first(_Num, String)),
224 string_chars(String, Event0),
225 remove_full_stop(Event0, Event),
226 !.
227get_last_event(_) :-
228 print_message(query, history(no_event)),
229 fail.
230
231remove_full_stop(In, Out) :-
232 phrase(remove_full_stop(Out), In).
233
234remove_full_stop([]) -->
235 spaces, ['.'], spaces, eos,
236 !.
237remove_full_stop([H|T]) -->
238 [H], !,
239 remove_full_stop(T).
240remove_full_stop([]) -->
241 [].
242
243spaces --> space, !, spaces.
244spaces --> [].
245
246space -->
247 [C],
248 { char_type(C, space) }.
249
250eos([], []).
251
255
256match_event(Spec, Event, Rest) :-
257 find_event(Spec, Event, Rest),
258 !.
259match_event(_, _, _) :-
260 print_message(query, history(no_event)),
261 fail.
262
263not_event_char(C) :- code_type(C, csym), !, fail.
264not_event_char(!) :- !, fail.
265not_event_char(_).
266
267find_event([!|Left], Event, Left) :-
268 !,
269 get_last_event(Event).
270find_event([N|Rest], Event, Left) :-
271 code_type(N, digit),
272 !,
273 take_number([N|Rest], NumCodes, Left),
274 number_codes(Number, NumCodes),
275 prolog:history(current_input, event(Number, String)),
276 string_chars(String, Event0),
277 remove_full_stop(Event0, Event).
278find_event(Spec, Event, Left) :-
279 take_string(Spec, String, Left),
280 matching_event(String, Event).
281
282take_string([C|Rest], [C|String], Left) :-
283 code_type(C, csym),
284 !,
285 take_string(Rest, String, Left).
286take_string([C|Rest], [], [C|Rest]) :- !.
287take_string([], [], []).
288
289take_number([C|Rest], [C|String], Left) :-
290 code_type(C, digit),
291 !,
292 take_string(Rest, String, Left).
293take_number([C|Rest], [], [C|Rest]) :- !.
294take_number([], [], []).
295
300
301matching_event(String, Chars) :-
302 prolog:history(current_input, prev_str(String, _Num, String)),
303 string_chars(String, Chars0),
304 remove_full_stop(Chars0, Chars)