36
37:- module(editline,
38 [ el_wrap/0, 39 el_wrap/1, 40 el_wrap/4, 41 el_wrap/5, 42 el_wrapped/1, 43 el_unwrap/1, 44
45 el_source/2, 46 el_bind/2, 47 el_addfn/4, 48 el_cursor/2, 49 el_line/2, 50 el_insertstr/2, 51 el_deletestr/2, 52
53 el_history/2, 54 el_history_events/2, 55 el_add_history/2, 56 el_write_history/2, 57 el_read_history/2, 58
59 el_version/1 60 ]). 61:- autoload(library(apply),[maplist/2,maplist/3]). 62:- autoload(library(lists),[reverse/2,max_list/2,append/3,member/2]). 63:- autoload(library(solution_sequences),[call_nth/2]). 64:- autoload(library(option), [merge_options/3]). 65
66:- use_foreign_library(foreign(libedit4pl)). 67
68:- initialization el_wrap_if_ok. 69
70:- meta_predicate
71 el_addfn(+,+,+,3). 72
73:- multifile
74 el_setup/1, 75 prolog:complete_input/4. 76
77
85
86el_wrap_if_ok :-
87 \+ current_prolog_flag(readline, readline),
88 stream_property(user_input, tty(true)),
89 !,
90 el_wrap.
91el_wrap_if_ok.
92
113
114el_wrap :-
115 el_wrap([]).
116
117el_wrap(_) :-
118 el_wrapped(user_input),
119 !.
120el_wrap(Options) :-
121 stream_property(user_input, tty(true)), !,
122 findall(Opt, history_default(Opt), Defaults),
123 merge_options(Options, Defaults, Options1),
124 el_wrap(swipl, user_input, user_output, user_error, Options1),
125 add_prolog_commands(user_input),
126 forall(el_setup(user_input), true).
127el_wrap(_).
128
129history_default(history(Size)) :-
130 current_prolog_flag(history, Value),
131 ( integer(Value),
132 Value >= 0
133 -> Size = Value
134 ; Value == false
135 -> Size = 0
136 ).
137
138add_prolog_commands(Input) :-
139 el_addfn(Input, complete, 'Complete atoms and files', complete),
140 el_addfn(Input, show_completions, 'List completions', show_completions),
141 el_addfn(Input, electric, 'Indicate matching bracket', electric),
142 el_addfn(Input, isearch_history, 'Incremental search in history',
143 isearch_history),
144 el_bind(Input, ["^I", complete]),
145 el_bind(Input, ["^[?", show_completions]),
146 el_bind(Input, ["^R", isearch_history]),
147 bind_electric(Input),
148 add_paste_quoted(Input),
149 el_source(Input, _).
150
163
164el_wrap(ProgName, In, Out, Error) :-
165 el_wrap(ProgName, In, Out, Error, []).
166
173
177
185
190
191
208
238
244
249
253
257
294
300
304
310
317
324
329
330:- multifile
331 prolog:history/2. 332
333prolog:history(Input, enabled) :-
334 !,
335 el_wrapped(Input),
336 el_history(Input, getsize(Size)),
337 Size > 0.
338prolog:history(Input, add(Line)) :-
339 !,
340 el_add_history(Input, Line).
341prolog:history(Input, load(File)) :-
342 !,
343 compat_read_history(Input, File).
344prolog:history(Input, save(File)) :-
345 !,
346 el_write_history(Input, File).
347prolog:history(Input, events(Events)) :-
348 !,
349 el_history_events(Input, Events).
350prolog:history(Input, Command) :-
351 public_command(Command),
352 !,
353 el_history(Input, Command).
354
355public_command(first(_Num, _String)).
356public_command(curr(_Num, _String)).
357public_command(event(_Num, _String)).
358public_command(prev_str(_Search, _Num, _String)).
359public_command(clear).
360
365
366compat_read_history(Input, File) :-
367 catch(el_read_history(Input, File), error(editline(_),_), fail),
368 !.
369compat_read_history(Input, File) :-
370 access_file(File, read),
371 setup_call_cleanup(
372 open(File, read, In, [encoding(utf8)]),
373 read_old_history(Input, In),
374 close(In)),
375 !.
376compat_read_history(_, _).
377
378read_old_history(Input, From) :-
379 catch('$raw_read'(From, Line), error(_,_), fail),
380 ( Line == end_of_file
381 -> true
382 ; string_concat(Line, '.', Event),
383 el_add_history(Input, Event),
384 read_old_history(Input, From)
385 ).
386
387 390
394
395bind_electric(Input) :-
396 forall(bracket(_Open, Close), bind_code(Input, Close, electric)),
397 forall(quote(Close), bind_code(Input, Close, electric)).
398
399bind_code(Input, Code, Command) :-
400 string_codes(Key, [Code]),
401 el_bind(Input, [Key, Command]).
402
403
405
406electric(Input, Char, Continue) :-
407 string_codes(Str, [Char]),
408 el_insertstr(Input, Str),
409 el_line(Input, line(Before, _)),
410 ( string_codes(Before, Codes),
411 nesting(Codes, 0, Nesting),
412 reverse(Nesting, [Close|RevNesting])
413 -> ( Close = open(_,_) 414 -> Continue = refresh
415 ; matching_open(RevNesting, Close, _, Index)
416 -> string_length(Before, Len), 417 Move is Index-Len,
418 Continue = electric(Move, 500, refresh)
419 ; Continue = refresh_beep 420 )
421 ; Continue = refresh_beep
422 ).
423
424matching_open_index(String, Index) :-
425 string_codes(String, Codes),
426 nesting(Codes, 0, Nesting),
427 reverse(Nesting, [Close|RevNesting]),
428 matching_open(RevNesting, Close, _, Index).
429
430matching_open([Open|Rest], Close, Rest, Index) :-
431 Open = open(Index,_),
432 match(Open, Close),
433 !.
434matching_open([Close1|Rest1], Close, Rest, Index) :-
435 Close1 = close(_,_),
436 matching_open(Rest1, Close1, Rest2, _),
437 matching_open(Rest2, Close, Rest, Index).
438
439match(open(_,Open),close(_,Close)) :-
440 ( bracket(Open, Close)
441 -> true
442 ; Open == Close,
443 quote(Open)
444 ).
445
446bracket(0'(, 0')).
447bracket(0'[, 0']).
448bracket(0'{, 0'}).
449
450quote(0'\').
451quote(0'\").
452quote(0'\`).
453
454nesting([], _, []).
455nesting([H|T], I, Nesting) :-
456 ( bracket(H, _Close)
457 -> Nesting = [open(I,H)|Nest]
458 ; bracket(_Open, H)
459 -> Nesting = [close(I,H)|Nest]
460 ),
461 !,
462 I2 is I+1,
463 nesting(T, I2, Nest).
464nesting([0'0, 0'\'|T], I, Nesting) :-
465 !,
466 phrase(skip_code, T, T1),
467 difflist_length(T, T1, Len),
468 I2 is I+Len+2,
469 nesting(T1, I2, Nesting).
470nesting([H|T], I, Nesting) :-
471 quote(H),
472 !,
473 ( phrase(skip_quoted(H), T, T1)
474 -> difflist_length(T, T1, Len),
475 I2 is I+Len+1,
476 Nesting = [open(I,H),close(I2,H)|Nest],
477 nesting(T1, I2, Nest)
478 ; Nesting = [open(I,H)] 479 ).
480nesting([_|T], I, Nesting) :-
481 I2 is I+1,
482 nesting(T, I2, Nesting).
483
484difflist_length(List, Tail, Len) :-
485 difflist_length(List, Tail, 0, Len).
486
487difflist_length(List, Tail, Len0, Len) :-
488 List == Tail,
489 !,
490 Len = Len0.
491difflist_length([_|List], Tail, Len0, Len) :-
492 Len1 is Len0+1,
493 difflist_length(List, Tail, Len1, Len).
494
495skip_quoted(H) -->
496 [H],
497 !.
498skip_quoted(H) -->
499 "\\", [H],
500 !,
501 skip_quoted(H).
502skip_quoted(H) -->
503 [_],
504 skip_quoted(H).
505
506skip_code -->
507 "\\", [_],
508 !.
509skip_code -->
510 [_].
511
512
513 516
524
525
526:- dynamic
527 last_complete/2. 528
529complete(Input, _Char, Continue) :-
530 el_line(Input, line(Before, After)),
531 ensure_input_completion,
532 prolog:complete_input(Before, After, Delete, Completions),
533 ( Completions = [One]
534 -> string_length(Delete, Len),
535 el_deletestr(Input, Len),
536 complete_text(One, Text),
537 el_insertstr(Input, Text),
538 Continue = refresh
539 ; Completions == []
540 -> Continue = refresh_beep
541 ; get_time(Now),
542 retract(last_complete(TLast, Before)),
543 Now - TLast < 2
544 -> nl(user_error),
545 list_alternatives(Completions),
546 Continue = redisplay
547 ; retractall(last_complete(_,_)),
548 get_time(Now),
549 asserta(last_complete(Now, Before)),
550 common_competion(Completions, Extend),
551 ( Delete == Extend
552 -> Continue = refresh_beep
553 ; string_length(Delete, Len),
554 el_deletestr(Input, Len),
555 el_insertstr(Input, Extend),
556 Continue = refresh
557 )
558 ).
559
560:- dynamic
561 input_completion_loaded/0. 562
563ensure_input_completion :-
564 input_completion_loaded,
565 !.
566ensure_input_completion :-
567 predicate_property(prolog:complete_input(_,_,_,_),
568 number_of_clauses(N)),
569 N > 0,
570 !.
571ensure_input_completion :-
572 exists_source(library(console_input)),
573 !,
574 use_module(library(console_input), []),
575 asserta(input_completion_loaded).
576ensure_input_completion.
577
578
582
583show_completions(Input, _Char, Continue) :-
584 el_line(Input, line(Before, After)),
585 prolog:complete_input(Before, After, _Delete, Completions),
586 nl(user_error),
587 list_alternatives(Completions),
588 Continue = redisplay.
589
590complete_text(Text-_Comment, Text) :- !.
591complete_text(Text, Text).
592
596
597common_competion(Alternatives, Common) :-
598 maplist(atomic, Alternatives),
599 !,
600 common_prefix(Alternatives, Common).
601common_competion(Alternatives, Common) :-
602 maplist(complete_text, Alternatives, AltText),
603 !,
604 common_prefix(AltText, Common).
605
609
610common_prefix([A1|T], Common) :-
611 common_prefix_(T, A1, Common).
612
613common_prefix_([], Common, Common).
614common_prefix_([H|T], Common0, Common) :-
615 common_prefix(H, Common0, Common1),
616 common_prefix_(T, Common1, Common).
617
621
622common_prefix(A1, A2, Prefix) :-
623 sub_atom(A1, 0, _, _, A2),
624 !,
625 Prefix = A2.
626common_prefix(A1, A2, Prefix) :-
627 sub_atom(A2, 0, _, _, A1),
628 !,
629 Prefix = A1.
630common_prefix(A1, A2, Prefix) :-
631 atom_codes(A1, C1),
632 atom_codes(A2, C2),
633 list_common_prefix(C1, C2, C),
634 string_codes(Prefix, C).
635
636list_common_prefix([H|T0], [H|T1], [H|T]) :-
637 !,
638 list_common_prefix(T0, T1, T).
639list_common_prefix(_, _, []).
640
641
642
648
649list_alternatives(Alternatives) :-
650 maplist(atomic, Alternatives),
651 !,
652 length(Alternatives, Count),
653 maplist(atom_length, Alternatives, Lengths),
654 max_list(Lengths, Max),
655 tty_size(_, Cols),
656 ColW is Max+2,
657 Columns is max(1, Cols // ColW),
658 RowCount is (Count+Columns-1)//Columns,
659 length(Rows, RowCount),
660 to_matrix(Alternatives, Rows, Rows),
661 ( RowCount > 11
662 -> length(First, 10),
663 Skipped is RowCount - 10,
664 append(First, _, Rows),
665 maplist(write_row(ColW), First),
666 format(user_error, '... skipped ~D rows~n', [Skipped])
667 ; maplist(write_row(ColW), Rows)
668 ).
669list_alternatives(Alternatives) :-
670 maplist(complete_text, Alternatives, AltText),
671 list_alternatives(AltText).
672
673to_matrix([], _, Rows) :-
674 !,
675 maplist(close_list, Rows).
676to_matrix([H|T], [RH|RT], Rows) :-
677 !,
678 add_list(RH, H),
679 to_matrix(T, RT, Rows).
680to_matrix(List, [], Rows) :-
681 to_matrix(List, Rows, Rows).
682
683add_list(Var, Elem) :-
684 var(Var), !,
685 Var = [Elem|_].
686add_list([_|T], Elem) :-
687 add_list(T, Elem).
688
689close_list(List) :-
690 append(List, [], _),
691 !.
692
693write_row(ColW, Row) :-
694 length(Row, Columns),
695 make_format(Columns, ColW, Format),
696 format(user_error, Format, Row).
697
698make_format(N, ColW, Format) :-
699 format(string(PerCol), '~~w~~t~~~d+', [ColW]),
700 Front is N - 1,
701 length(LF, Front),
702 maplist(=(PerCol), LF),
703 append(LF, ['~w~n'], Parts),
704 atomics_to_string(Parts, Format).
705
706
707 710
715
716isearch_history(Input, _Char, Continue) :-
717 el_line(Input, line(Before, After)),
718 string_concat(Before, After, Current),
719 string_length(Current, Len),
720 search_print('', "", Current),
721 search(Input, "", Current, 1, Line),
722 el_deletestr(Input, Len),
723 el_insertstr(Input, Line),
724 Continue = redisplay.
725
726search(Input, For, Current, Nth, Line) :-
727 el_getc(Input, Next),
728 Next \== -1,
729 !,
730 search(Next, Input, For, Current, Nth, Line).
731search(_Input, _For, _Current, _Nth, "").
732
733search(7, _Input, _, Current, _, Current) :- 734 !,
735 clear_line.
736search(18, Input, For, Current, Nth, Line) :- 737 !,
738 N2 is Nth+1,
739 search_(Input, For, Current, N2, Line).
740search(19, Input, For, Current, Nth, Line) :- 741 !,
742 N2 is max(1,Nth-1),
743 search_(Input, For, Current, N2, Line).
744search(127, Input, For, Current, _Nth, Line) :- 745 sub_string(For, 0, _, 1, For1),
746 !,
747 search_(Input, For1, Current, 1, Line).
748search(Char, Input, For, Current, Nth, Line) :-
749 code_type(Char, cntrl),
750 !,
751 search_end(Input, For, Current, Nth, Line),
752 el_push(Input, Char).
753search(Char, Input, For, Current, _Nth, Line) :-
754 format(string(For1), '~w~c', [For,Char]),
755 search_(Input, For1, Current, 1, Line).
756
757search_(Input, For1, Current, Nth, Line) :-
758 ( find_in_history(Input, For1, Current, Nth, Candidate)
759 -> search_print('', For1, Candidate)
760 ; search_print('failed ', For1, Current)
761 ),
762 search(Input, For1, Current, Nth, Line).
763
764search_end(Input, For, Current, Nth, Line) :-
765 ( find_in_history(Input, For, Current, Nth, Line)
766 -> true
767 ; Line = Current
768 ),
769 clear_line.
770
771find_in_history(_, "", Current, _, Current) :-
772 !.
773find_in_history(Input, For, _, Nth, Line) :-
774 el_history_events(Input, History),
775 call_nth(( member(_N-Line, History),
776 sub_string(Line, _, _, _, For)
777 ),
778 Nth),
779 !.
780
781search_print(State, Search, Current) :-
782 format(user_error, '\r(~wreverse-i-search)`~w\': ~w\e[0K',
783 [State, Search, Current]).
784
785clear_line :-
786 format(user_error, '\r\e[0K', []).
787
788
789 792
793:- meta_predicate
794 with_quote_flags(+,+,0). 795
796add_paste_quoted(Input) :-
797 current_prolog_flag(gui, true),
798 !,
799 el_addfn(Input, paste_quoted, 'Paste as quoted atom', paste_quoted),
800 el_bind(Input, ["^Y", paste_quoted]).
801add_paste_quoted(_).
802
808
809paste_quoted(Input, _Char, Continue) :-
810 clipboard_content(String),
811 quote_text(Input, String, Quoted),
812 el_insertstr(Input, Quoted),
813 Continue = refresh.
814
815quote_text(Input, String, Value) :-
816 el_line(Input, line(Before, _After)),
817 ( sub_string(Before, _, 1, 0, Quote)
818 -> true
819 ; Quote = "'"
820 ),
821 quote_text(Input, Quote, String, Value).
822
823quote_text(Input, "'", Text, Quoted) =>
824 format(string(Quoted), '~q', [Text]),
825 el_deletestr(Input, 1).
826quote_text(Input, "\"", Text, Quoted) =>
827 atom_string(Text, String),
828 with_quote_flags(
829 string, codes,
830 format(string(Quoted), '~q', [String])),
831 el_deletestr(Input, 1).
832quote_text(Input, "`", Text, Quoted) =>
833 atom_string(Text, String),
834 with_quote_flags(
835 codes, string,
836 format(string(Quoted), '~q', [String])),
837 el_deletestr(Input, 1).
838quote_text(_, _, Text, Quoted) =>
839 format(string(Quoted), '~q', [Text]).
840
841with_quote_flags(Double, Back, Goal) :-
842 current_prolog_flag(double_quotes, ODouble),
843 current_prolog_flag(back_quotes, OBack),
844 setup_call_cleanup(
845 ( set_prolog_flag(double_quotes, Double),
846 set_prolog_flag(back_quotes, Back) ),
847 Goal,
848 ( set_prolog_flag(double_quotes, ODouble),
849 set_prolog_flag(back_quotes, OBack) )).
850
851clipboard_content(Text) :-
852 current_prolog_flag(gui, true),
853 !,
854 autoload_call(in_pce_thread_sync(
855 autoload_call(
856 get(@(display), paste, primary, string(Text))))).
857clipboard_content("").
858
859
860 863
864:- multifile prolog:error_message//1. 865
866prolog:error_message(editline(Msg)) -->
867 [ 'editline: ~s'-[Msg] ]