36
37:- module(editline,
38 [ el_wrap/0, 39 el_wrap/4, 40 el_wrapped/1, 41 el_unwrap/1, 42
43 el_source/2, 44 el_bind/2, 45 el_addfn/4, 46 el_cursor/2, 47 el_line/2, 48 el_insertstr/2, 49 el_deletestr/2, 50
51 el_history/2, 52 el_history_events/2, 53 el_add_history/2, 54 el_write_history/2, 55 el_read_history/2 56 ]). 57:- autoload(library(apply),[maplist/2,maplist/3]). 58:- autoload(library(lists),[reverse/2,max_list/2,append/3,member/2]). 59:- autoload(library(solution_sequences),[call_nth/2]). 60
61:- use_foreign_library(foreign(libedit4pl)). 62
63:- initialization el_wrap_if_ok. 64
65:- meta_predicate
66 el_addfn(+,+,+,3). 67
68:- multifile
69 el_setup/1, 70 prolog:complete_input/4. 71
72
80
81el_wrap_if_ok :-
82 \+ current_prolog_flag(console_menu_version, qt),
83 \+ current_prolog_flag(readline, readline),
84 stream_property(user_input, tty(true)),
85 !,
86 el_wrap.
87el_wrap_if_ok.
88
99
100el_wrap :-
101 el_wrapped(user_input),
102 !.
103el_wrap :-
104 stream_property(user_input, tty(true)), !,
105 el_wrap(swipl, user_input, user_output, user_error),
106 add_prolog_commands(user_input),
107 forall(el_setup(user_input), true).
108el_wrap.
109
110add_prolog_commands(Input) :-
111 el_addfn(Input, complete, 'Complete atoms and files', complete),
112 el_addfn(Input, show_completions, 'List completions', show_completions),
113 el_addfn(Input, electric, 'Indicate matching bracket', electric),
114 el_addfn(Input, isearch_history, 'Incremental search in history',
115 isearch_history),
116 el_bind(Input, ["^I", complete]),
117 el_bind(Input, ["^[?", show_completions]),
118 el_bind(Input, ["^R", isearch_history]),
119 bind_electric(Input),
120 add_paste_quoted(Input),
121 el_source(Input, _).
122
130
137
141
149
154
155
172
202
208
213
217
221
234
240
244
250
257
258
259:- multifile
260 prolog:history/2. 261
262prolog:history(Input, add(Line)) :-
263 el_add_history(Input, Line).
264prolog:history(Input, load(File)) :-
265 el_read_history(Input, File).
266prolog:history(Input, save(File)) :-
267 el_write_history(Input, File).
268prolog:history(Input, load) :-
269 el_history_events(Input, Events),
270 load_history_events(Events).
271
275
276load_history_events(Events) :-
277 '$reverse'(Events, RevEvents),
278 forall('$member'(Ev, RevEvents),
279 add_event(Ev)).
280
281add_event(Num-String) :-
282 remove_dot(String, String1),
283 '$save_history_event'(Num-String1).
284
285remove_dot(String0, String) :-
286 string_concat(String, ".", String0),
287 !.
288remove_dot(String, String).
289
290
291 294
298
299bind_electric(Input) :-
300 forall(bracket(_Open, Close), bind_code(Input, Close, electric)),
301 forall(quote(Close), bind_code(Input, Close, electric)).
302
303bind_code(Input, Code, Command) :-
304 string_codes(Key, [Code]),
305 el_bind(Input, [Key, Command]).
306
307
309
310electric(Input, Char, Continue) :-
311 string_codes(Str, [Char]),
312 el_insertstr(Input, Str),
313 el_line(Input, line(Before, _)),
314 ( string_codes(Before, Codes),
315 nesting(Codes, 0, Nesting),
316 reverse(Nesting, [Close|RevNesting])
317 -> ( Close = open(_,_) 318 -> Continue = refresh
319 ; matching_open(RevNesting, Close, _, Index)
320 -> string_length(Before, Len), 321 Move is Index-Len,
322 Continue = electric(Move, 500, refresh)
323 ; Continue = refresh_beep 324 )
325 ; Continue = refresh_beep
326 ).
327
328matching_open_index(String, Index) :-
329 string_codes(String, Codes),
330 nesting(Codes, 0, Nesting),
331 reverse(Nesting, [Close|RevNesting]),
332 matching_open(RevNesting, Close, _, Index).
333
334matching_open([Open|Rest], Close, Rest, Index) :-
335 Open = open(Index,_),
336 match(Open, Close),
337 !.
338matching_open([Close1|Rest1], Close, Rest, Index) :-
339 Close1 = close(_,_),
340 matching_open(Rest1, Close1, Rest2, _),
341 matching_open(Rest2, Close, Rest, Index).
342
343match(open(_,Open),close(_,Close)) :-
344 ( bracket(Open, Close)
345 -> true
346 ; Open == Close,
347 quote(Open)
348 ).
349
350bracket(0'(, 0')).
351bracket(0'[, 0']).
352bracket(0'{, 0'}).
353
354quote(0'\').
355quote(0'\").
356quote(0'\`).
357
358nesting([], _, []).
359nesting([H|T], I, Nesting) :-
360 ( bracket(H, _Close)
361 -> Nesting = [open(I,H)|Nest]
362 ; bracket(_Open, H)
363 -> Nesting = [close(I,H)|Nest]
364 ),
365 !,
366 I2 is I+1,
367 nesting(T, I2, Nest).
368nesting([0'0, 0'\'|T], I, Nesting) :-
369 !,
370 phrase(skip_code, T, T1),
371 difflist_length(T, T1, Len),
372 I2 is I+Len+2,
373 nesting(T1, I2, Nesting).
374nesting([H|T], I, Nesting) :-
375 quote(H),
376 !,
377 ( phrase(skip_quoted(H), T, T1)
378 -> difflist_length(T, T1, Len),
379 I2 is I+Len+1,
380 Nesting = [open(I,H),close(I2,H)|Nest],
381 nesting(T1, I2, Nest)
382 ; Nesting = [open(I,H)] 383 ).
384nesting([_|T], I, Nesting) :-
385 I2 is I+1,
386 nesting(T, I2, Nesting).
387
388difflist_length(List, Tail, Len) :-
389 difflist_length(List, Tail, 0, Len).
390
391difflist_length(List, Tail, Len0, Len) :-
392 List == Tail,
393 !,
394 Len = Len0.
395difflist_length([_|List], Tail, Len0, Len) :-
396 Len1 is Len0+1,
397 difflist_length(List, Tail, Len1, Len).
398
399skip_quoted(H) -->
400 [H],
401 !.
402skip_quoted(H) -->
403 "\\", [H],
404 !,
405 skip_quoted(H).
406skip_quoted(H) -->
407 [_],
408 skip_quoted(H).
409
410skip_code -->
411 "\\", [_],
412 !.
413skip_code -->
414 [_].
415
416
417 420
428
429
430:- dynamic
431 last_complete/2. 432
433complete(Input, _Char, Continue) :-
434 el_line(Input, line(Before, After)),
435 ensure_input_completion,
436 prolog:complete_input(Before, After, Delete, Completions),
437 ( Completions = [One]
438 -> string_length(Delete, Len),
439 el_deletestr(Input, Len),
440 complete_text(One, Text),
441 el_insertstr(Input, Text),
442 Continue = refresh
443 ; Completions == []
444 -> Continue = refresh_beep
445 ; get_time(Now),
446 retract(last_complete(TLast, Before)),
447 Now - TLast < 2
448 -> nl(user_error),
449 list_alternatives(Completions),
450 Continue = redisplay
451 ; retractall(last_complete(_,_)),
452 get_time(Now),
453 asserta(last_complete(Now, Before)),
454 common_competion(Completions, Extend),
455 ( Delete == Extend
456 -> Continue = refresh_beep
457 ; string_length(Delete, Len),
458 el_deletestr(Input, Len),
459 el_insertstr(Input, Extend),
460 Continue = refresh
461 )
462 ).
463
464:- dynamic
465 input_completion_loaded/0. 466
467ensure_input_completion :-
468 input_completion_loaded,
469 !.
470ensure_input_completion :-
471 predicate_property(prolog:complete_input(_,_,_,_),
472 number_of_clauses(N)),
473 N > 0,
474 !.
475ensure_input_completion :-
476 exists_source(library(console_input)),
477 !,
478 use_module(library(console_input), []),
479 asserta(input_completion_loaded).
480ensure_input_completion.
481
482
486
487show_completions(Input, _Char, Continue) :-
488 el_line(Input, line(Before, After)),
489 prolog:complete_input(Before, After, _Delete, Completions),
490 nl(user_error),
491 list_alternatives(Completions),
492 Continue = redisplay.
493
494complete_text(Text-_Comment, Text) :- !.
495complete_text(Text, Text).
496
500
501common_competion(Alternatives, Common) :-
502 maplist(atomic, Alternatives),
503 !,
504 common_prefix(Alternatives, Common).
505common_competion(Alternatives, Common) :-
506 maplist(complete_text, Alternatives, AltText),
507 !,
508 common_prefix(AltText, Common).
509
513
514common_prefix([A1|T], Common) :-
515 common_prefix_(T, A1, Common).
516
517common_prefix_([], Common, Common).
518common_prefix_([H|T], Common0, Common) :-
519 common_prefix(H, Common0, Common1),
520 common_prefix_(T, Common1, Common).
521
525
526common_prefix(A1, A2, Prefix) :-
527 sub_atom(A1, 0, _, _, A2),
528 !,
529 Prefix = A2.
530common_prefix(A1, A2, Prefix) :-
531 sub_atom(A2, 0, _, _, A1),
532 !,
533 Prefix = A1.
534common_prefix(A1, A2, Prefix) :-
535 atom_codes(A1, C1),
536 atom_codes(A2, C2),
537 list_common_prefix(C1, C2, C),
538 string_codes(Prefix, C).
539
540list_common_prefix([H|T0], [H|T1], [H|T]) :-
541 !,
542 list_common_prefix(T0, T1, T).
543list_common_prefix(_, _, []).
544
545
546
552
553list_alternatives(Alternatives) :-
554 maplist(atomic, Alternatives),
555 !,
556 length(Alternatives, Count),
557 maplist(atom_length, Alternatives, Lengths),
558 max_list(Lengths, Max),
559 tty_size(_, Cols),
560 ColW is Max+2,
561 Columns is max(1, Cols // ColW),
562 RowCount is (Count+Columns-1)//Columns,
563 length(Rows, RowCount),
564 to_matrix(Alternatives, Rows, Rows),
565 ( RowCount > 11
566 -> length(First, 10),
567 Skipped is RowCount - 10,
568 append(First, _, Rows),
569 maplist(write_row(ColW), First),
570 format(user_error, '... skipped ~D rows~n', [Skipped])
571 ; maplist(write_row(ColW), Rows)
572 ).
573list_alternatives(Alternatives) :-
574 maplist(complete_text, Alternatives, AltText),
575 list_alternatives(AltText).
576
577to_matrix([], _, Rows) :-
578 !,
579 maplist(close_list, Rows).
580to_matrix([H|T], [RH|RT], Rows) :-
581 !,
582 add_list(RH, H),
583 to_matrix(T, RT, Rows).
584to_matrix(List, [], Rows) :-
585 to_matrix(List, Rows, Rows).
586
587add_list(Var, Elem) :-
588 var(Var), !,
589 Var = [Elem|_].
590add_list([_|T], Elem) :-
591 add_list(T, Elem).
592
593close_list(List) :-
594 append(List, [], _),
595 !.
596
597write_row(ColW, Row) :-
598 length(Row, Columns),
599 make_format(Columns, ColW, Format),
600 format(user_error, Format, Row).
601
602make_format(N, ColW, Format) :-
603 format(string(PerCol), '~~w~~t~~~d+', [ColW]),
604 Front is N - 1,
605 length(LF, Front),
606 maplist(=(PerCol), LF),
607 append(LF, ['~w~n'], Parts),
608 atomics_to_string(Parts, Format).
609
610
611 614
619
620isearch_history(Input, _Char, Continue) :-
621 el_line(Input, line(Before, After)),
622 string_concat(Before, After, Current),
623 string_length(Current, Len),
624 search_print('', "", Current),
625 search(Input, "", Current, 1, Line),
626 el_deletestr(Input, Len),
627 el_insertstr(Input, Line),
628 Continue = redisplay.
629
630search(Input, For, Current, Nth, Line) :-
631 el_getc(Input, Next),
632 Next \== -1,
633 !,
634 search(Next, Input, For, Current, Nth, Line).
635search(_Input, _For, _Current, _Nth, "").
636
637search(7, _Input, _, Current, _, Current) :- 638 !,
639 clear_line.
640search(18, Input, For, Current, Nth, Line) :- 641 !,
642 N2 is Nth+1,
643 search_(Input, For, Current, N2, Line).
644search(19, Input, For, Current, Nth, Line) :- 645 !,
646 N2 is max(1,Nth-1),
647 search_(Input, For, Current, N2, Line).
648search(127, Input, For, Current, _Nth, Line) :- 649 sub_string(For, 0, _, 1, For1),
650 !,
651 search_(Input, For1, Current, 1, Line).
652search(Char, Input, For, Current, Nth, Line) :-
653 code_type(Char, cntrl),
654 !,
655 search_end(Input, For, Current, Nth, Line),
656 el_push(Input, Char).
657search(Char, Input, For, Current, _Nth, Line) :-
658 format(string(For1), '~w~c', [For,Char]),
659 search_(Input, For1, Current, 1, Line).
660
661search_(Input, For1, Current, Nth, Line) :-
662 ( find_in_history(Input, For1, Current, Nth, Candidate)
663 -> search_print('', For1, Candidate)
664 ; search_print('failed ', For1, Current)
665 ),
666 search(Input, For1, Current, Nth, Line).
667
668search_end(Input, For, Current, Nth, Line) :-
669 ( find_in_history(Input, For, Current, Nth, Line)
670 -> true
671 ; Line = Current
672 ),
673 clear_line.
674
675find_in_history(_, "", Current, _, Current) :-
676 !.
677find_in_history(Input, For, _, Nth, Line) :-
678 el_history_events(Input, History),
679 call_nth(( member(_N-Line, History),
680 sub_string(Line, _, _, _, For)
681 ),
682 Nth),
683 !.
684
685search_print(State, Search, Current) :-
686 format(user_error, '\r(~wreverse-i-search)`~w\': ~w\e[0K',
687 [State, Search, Current]).
688
689clear_line :-
690 format(user_error, '\r\e[0K', []).
691
692
693 696
697:- meta_predicate
698 with_quote_flags(+,+,0). 699
700add_paste_quoted(Input) :-
701 current_prolog_flag(gui, true),
702 !,
703 el_addfn(Input, paste_quoted, 'Paste as quoted atom', paste_quoted),
704 el_bind(Input, ["^Y", paste_quoted]).
705add_paste_quoted(_).
706
712
713paste_quoted(Input, _Char, Continue) :-
714 clipboard_content(String),
715 quote_text(Input, String, Quoted),
716 el_insertstr(Input, Quoted),
717 Continue = refresh.
718
719quote_text(Input, String, Value) :-
720 el_line(Input, line(Before, _After)),
721 ( sub_string(Before, _, 1, 0, Quote)
722 -> true
723 ; Quote = "'"
724 ),
725 quote_text(Input, Quote, String, Value).
726
727quote_text(Input, "'", Text, Quoted) =>
728 format(string(Quoted), '~q', [Text]),
729 el_deletestr(Input, 1).
730quote_text(Input, "\"", Text, Quoted) =>
731 atom_string(Text, String),
732 with_quote_flags(
733 string, codes,
734 format(string(Quoted), '~q', [String])),
735 el_deletestr(Input, 1).
736quote_text(Input, "`", Text, Quoted) =>
737 atom_string(Text, String),
738 with_quote_flags(
739 codes, string,
740 format(string(Quoted), '~q', [String])),
741 el_deletestr(Input, 1).
742quote_text(_, _, Text, Quoted) =>
743 format(string(Quoted), '~q', [Text]).
744
745with_quote_flags(Double, Back, Goal) :-
746 current_prolog_flag(double_quotes, ODouble),
747 current_prolog_flag(back_quotes, OBack),
748 setup_call_cleanup(
749 ( set_prolog_flag(double_quotes, Double),
750 set_prolog_flag(back_quotes, Back) ),
751 Goal,
752 ( set_prolog_flag(double_quotes, ODouble),
753 set_prolog_flag(back_quotes, OBack) )).
754
755clipboard_content(Text) :-
756 ( current_predicate(get/3)
757 -> true
758 ; current_prolog_flag(gui, true),
759 use_module(library(pce), [get/3, in_pce_thread_sync/1])
760 ),
761 !,
762 in_pce_thread_sync(get(@(display), paste, primary, string(Text))).
763clipboard_content("")