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_set/2, 48 el_addfn/4, 49 el_cursor/2, 50 el_line/2, 51 el_insertstr/2, 52 el_deletestr/2, 53
54 el_history/2, 55 el_history_events/2, 56 el_add_history/2, 57 el_write_history/2, 58 el_read_history/2, 59
60 el_version/1 61 ]). 62:- autoload(library(apply),[maplist/2,maplist/3]). 63:- autoload(library(lists),[reverse/2,max_list/2,append/3,member/2]). 64:- autoload(library(solution_sequences),[call_nth/2]). 65:- autoload(library(option), [merge_options/3]). 66
67:- use_foreign_library(foreign(libedit4pl)). 68
69:- initialization el_wrap_if_ok. 70
71:- meta_predicate
72 el_addfn(+,+,+,3). 73
74:- multifile
75 el_setup/1, 76 prolog:complete_input/4. 77
78
86
87el_wrap_if_ok :-
88 \+ current_prolog_flag(readline, readline),
89 stream_property(user_input, tty(true)),
90 !,
91 el_wrap.
92el_wrap_if_ok.
93
117
118el_wrap :-
119 el_wrap([]).
120
121el_wrap(_) :-
122 el_wrapped(user_input),
123 !.
124el_wrap(Options) :-
125 stream_property(user_input, tty(true)), !,
126 findall(Opt, el_default(Opt), Defaults),
127 merge_options(Options, Defaults, Options1),
128 el_wrap(swipl, user_input, user_output, user_error, Options1),
129 add_prolog_commands(user_input),
130 ignore(el_set(user_input, wordchars("_"))),
131 forall(el_setup(user_input), true).
132el_wrap(_).
133
134el_default(history(Size)) :-
135 current_prolog_flag(history, Value),
136 ( integer(Value),
137 Value >= 0
138 -> Size = Value
139 ; Value == false
140 -> Size = 0
141 ).
142:- if(current_predicate(prolog_alert_signal/2)). 143el_default(alert_signo(SigNo)) :-
144 prolog_alert_signal(SigName, SigName),
145 current_signal(SigName, SigNo, _Handler).
146:- endif. 147
148add_prolog_commands(Input) :-
149 el_addfn(Input, complete, 'Complete atoms and files', complete),
150 el_addfn(Input, show_completions, 'List completions', show_completions),
151 el_addfn(Input, electric, 'Indicate matching bracket', electric),
152 el_addfn(Input, isearch_history, 'Incremental search in history',
153 isearch_history),
154 el_bind(Input, ["^I", complete]),
155 el_bind(Input, ["^[?", show_completions]),
156 el_bind(Input, ["^R", isearch_history]),
157 bind_electric(Input),
158 add_paste_quoted(Input),
159 el_source(Input, _).
160
173
174el_wrap(ProgName, In, Out, Error) :-
175 el_wrap(ProgName, In, Out, Error, []).
176
183
187
195
200
201
218
248
261
267
272
276
280
317
323
327
333
340
347
352
353:- multifile
354 prolog:history/2. 355
356prolog:history(Input, enabled) :-
357 !,
358 el_wrapped(Input),
359 el_history(Input, getsize(Size)),
360 Size > 0.
361prolog:history(Input, add(Line)) :-
362 !,
363 el_add_history(Input, Line).
364prolog:history(Input, load(File)) :-
365 !,
366 compat_read_history(Input, File).
367prolog:history(Input, save(File)) :-
368 !,
369 el_write_history(Input, File).
370prolog:history(Input, events(Events)) :-
371 !,
372 el_history_events(Input, Events).
373prolog:history(Input, Command) :-
374 public_command(Command),
375 !,
376 el_history(Input, Command).
377
378public_command(first(_Num, _String)).
379public_command(curr(_Num, _String)).
380public_command(event(_Num, _String)).
381public_command(prev_str(_Search, _Num, _String)).
382public_command(clear).
383
388
389compat_read_history(Input, File) :-
390 catch(el_read_history(Input, File), error(editline(_),_), fail),
391 !.
392compat_read_history(Input, File) :-
393 access_file(File, read),
394 setup_call_cleanup(
395 open(File, read, In, [encoding(utf8)]),
396 read_old_history(Input, In),
397 close(In)),
398 !.
399compat_read_history(_, _).
400
401read_old_history(Input, From) :-
402 catch('$raw_read'(From, Line), error(_,_), fail),
403 ( Line == end_of_file
404 -> true
405 ; string_concat(Line, '.', Event),
406 el_add_history(Input, Event),
407 read_old_history(Input, From)
408 ).
409
410 413
417
418bind_electric(Input) :-
419 forall(bracket(_Open, Close), bind_code(Input, Close, electric)),
420 forall(quote(Close), bind_code(Input, Close, electric)).
421
422bind_code(Input, Code, Command) :-
423 string_codes(Key, [Code]),
424 el_bind(Input, [Key, Command]).
425
426
428
429electric(Input, Char, Continue) :-
430 string_codes(Str, [Char]),
431 el_insertstr(Input, Str),
432 el_line(Input, line(Before, _)),
433 ( string_codes(Before, Codes),
434 nesting(Codes, 0, Nesting),
435 reverse(Nesting, [Close|RevNesting])
436 -> ( Close = open(_,_) 437 -> Continue = refresh
438 ; matching_open(RevNesting, Close, _, Index)
439 -> string_length(Before, Len), 440 Move is Index-Len,
441 Continue = electric(Move, 500, refresh)
442 ; Continue = refresh_beep 443 )
444 ; Continue = refresh_beep
445 ).
446
447matching_open_index(String, Index) :-
448 string_codes(String, Codes),
449 nesting(Codes, 0, Nesting),
450 reverse(Nesting, [Close|RevNesting]),
451 matching_open(RevNesting, Close, _, Index).
452
453matching_open([Open|Rest], Close, Rest, Index) :-
454 Open = open(Index,_),
455 match(Open, Close),
456 !.
457matching_open([Close1|Rest1], Close, Rest, Index) :-
458 Close1 = close(_,_),
459 matching_open(Rest1, Close1, Rest2, _),
460 matching_open(Rest2, Close, Rest, Index).
461
462match(open(_,Open),close(_,Close)) :-
463 ( bracket(Open, Close)
464 -> true
465 ; Open == Close,
466 quote(Open)
467 ).
468
469bracket(0'(, 0')).
470bracket(0'[, 0']).
471bracket(0'{, 0'}).
472
473quote(0'\').
474quote(0'\").
475quote(0'\`).
476
477nesting([], _, []).
478nesting([H|T], I, Nesting) :-
479 ( bracket(H, _Close)
480 -> Nesting = [open(I,H)|Nest]
481 ; bracket(_Open, H)
482 -> Nesting = [close(I,H)|Nest]
483 ),
484 !,
485 I2 is I+1,
486 nesting(T, I2, Nest).
487nesting([0'0, 0'\'|T], I, Nesting) :-
488 !,
489 phrase(skip_code, T, T1),
490 difflist_length(T, T1, Len),
491 I2 is I+Len+2,
492 nesting(T1, I2, Nesting).
493nesting([H|T], I, Nesting) :-
494 quote(H),
495 !,
496 ( phrase(skip_quoted(H), T, T1)
497 -> difflist_length(T, T1, Len),
498 I2 is I+Len+1,
499 Nesting = [open(I,H),close(I2,H)|Nest],
500 nesting(T1, I2, Nest)
501 ; Nesting = [open(I,H)] 502 ).
503nesting([_|T], I, Nesting) :-
504 I2 is I+1,
505 nesting(T, I2, Nesting).
506
507difflist_length(List, Tail, Len) :-
508 difflist_length(List, Tail, 0, Len).
509
510difflist_length(List, Tail, Len0, Len) :-
511 List == Tail,
512 !,
513 Len = Len0.
514difflist_length([_|List], Tail, Len0, Len) :-
515 Len1 is Len0+1,
516 difflist_length(List, Tail, Len1, Len).
517
518skip_quoted(H) -->
519 [H],
520 !.
521skip_quoted(H) -->
522 "\\", [H],
523 !,
524 skip_quoted(H).
525skip_quoted(H) -->
526 [_],
527 skip_quoted(H).
528
529skip_code -->
530 "\\", [_],
531 !.
532skip_code -->
533 [_].
534
535
536 539
547
548
549:- dynamic
550 last_complete/2. 551
552complete(Input, _Char, Continue) :-
553 el_line(Input, line(Before, After)),
554 ensure_input_completion,
555 prolog:complete_input(Before, After, Delete, Completions),
556 ( Completions = [One]
557 -> string_length(Delete, Len),
558 el_deletestr(Input, Len),
559 complete_text(One, Text),
560 el_insertstr(Input, Text),
561 Continue = refresh
562 ; Completions == []
563 -> Continue = refresh_beep
564 ; get_time(Now),
565 retract(last_complete(TLast, Before)),
566 Now - TLast < 2
567 -> nl(user_error),
568 list_alternatives(Completions),
569 Continue = redisplay
570 ; retractall(last_complete(_,_)),
571 get_time(Now),
572 asserta(last_complete(Now, Before)),
573 common_competion(Completions, Extend),
574 ( Delete == Extend
575 -> Continue = refresh_beep
576 ; string_length(Delete, Len),
577 el_deletestr(Input, Len),
578 el_insertstr(Input, Extend),
579 Continue = refresh
580 )
581 ).
582
583:- dynamic
584 input_completion_loaded/0. 585
586ensure_input_completion :-
587 input_completion_loaded,
588 !.
589ensure_input_completion :-
590 predicate_property(prolog:complete_input(_,_,_,_),
591 number_of_clauses(N)),
592 N > 0,
593 !.
594ensure_input_completion :-
595 exists_source(library(console_input)),
596 !,
597 use_module(library(console_input), []),
598 asserta(input_completion_loaded).
599ensure_input_completion.
600
601
605
606show_completions(Input, _Char, Continue) :-
607 el_line(Input, line(Before, After)),
608 prolog:complete_input(Before, After, _Delete, Completions),
609 nl(user_error),
610 list_alternatives(Completions),
611 Continue = redisplay.
612
613complete_text(Text-_Comment, Text) :- !.
614complete_text(Text, Text).
615
619
620common_competion(Alternatives, Common) :-
621 maplist(atomic, Alternatives),
622 !,
623 common_prefix(Alternatives, Common).
624common_competion(Alternatives, Common) :-
625 maplist(complete_text, Alternatives, AltText),
626 !,
627 common_prefix(AltText, Common).
628
632
633common_prefix([A1|T], Common) :-
634 common_prefix_(T, A1, Common).
635
636common_prefix_([], Common, Common).
637common_prefix_([H|T], Common0, Common) :-
638 common_prefix(H, Common0, Common1),
639 common_prefix_(T, Common1, Common).
640
644
645common_prefix(A1, A2, Prefix) :-
646 sub_atom(A1, 0, _, _, A2),
647 !,
648 Prefix = A2.
649common_prefix(A1, A2, Prefix) :-
650 sub_atom(A2, 0, _, _, A1),
651 !,
652 Prefix = A1.
653common_prefix(A1, A2, Prefix) :-
654 atom_codes(A1, C1),
655 atom_codes(A2, C2),
656 list_common_prefix(C1, C2, C),
657 string_codes(Prefix, C).
658
659list_common_prefix([H|T0], [H|T1], [H|T]) :-
660 !,
661 list_common_prefix(T0, T1, T).
662list_common_prefix(_, _, []).
663
664
665
671
672list_alternatives(Alternatives) :-
673 maplist(atomic, Alternatives),
674 !,
675 length(Alternatives, Count),
676 maplist(atom_length, Alternatives, Lengths),
677 max_list(Lengths, Max),
678 tty_size(_, Cols),
679 ColW is Max+2,
680 Columns is max(1, Cols // ColW),
681 RowCount is (Count+Columns-1)//Columns,
682 length(Rows, RowCount),
683 to_matrix(Alternatives, Rows, Rows),
684 ( RowCount > 11
685 -> length(First, 10),
686 Skipped is RowCount - 10,
687 append(First, _, Rows),
688 maplist(write_row(ColW), First),
689 format(user_error, '... skipped ~D rows~n', [Skipped])
690 ; maplist(write_row(ColW), Rows)
691 ).
692list_alternatives(Alternatives) :-
693 maplist(complete_text, Alternatives, AltText),
694 list_alternatives(AltText).
695
696to_matrix([], _, Rows) :-
697 !,
698 maplist(close_list, Rows).
699to_matrix([H|T], [RH|RT], Rows) :-
700 !,
701 add_list(RH, H),
702 to_matrix(T, RT, Rows).
703to_matrix(List, [], Rows) :-
704 to_matrix(List, Rows, Rows).
705
706add_list(Var, Elem) :-
707 var(Var), !,
708 Var = [Elem|_].
709add_list([_|T], Elem) :-
710 add_list(T, Elem).
711
712close_list(List) :-
713 append(List, [], _),
714 !.
715
716write_row(ColW, Row) :-
717 length(Row, Columns),
718 make_format(Columns, ColW, Format),
719 format(user_error, Format, Row).
720
721make_format(N, ColW, Format) :-
722 format(string(PerCol), '~~w~~t~~~d+', [ColW]),
723 Front is N - 1,
724 length(LF, Front),
725 maplist(=(PerCol), LF),
726 append(LF, ['~w~n'], Parts),
727 atomics_to_string(Parts, Format).
728
729
730 733
738
739isearch_history(Input, _Char, Continue) :-
740 el_line(Input, line(Before, After)),
741 string_concat(Before, After, Current),
742 string_length(Current, Len),
743 search_print('', "", Current),
744 search(Input, "", Current, 1, Line),
745 el_deletestr(Input, Len),
746 el_insertstr(Input, Line),
747 Continue = redisplay.
748
749search(Input, For, Current, Nth, Line) :-
750 el_getc(Input, Next),
751 Next \== -1,
752 !,
753 search(Next, Input, For, Current, Nth, Line).
754search(_Input, _For, _Current, _Nth, "").
755
756search(7, _Input, _, Current, _, Current) :- 757 !,
758 clear_line.
759search(18, Input, For, Current, Nth, Line) :- 760 !,
761 N2 is Nth+1,
762 search_(Input, For, Current, N2, Line).
763search(19, Input, For, Current, Nth, Line) :- 764 !,
765 N2 is max(1,Nth-1),
766 search_(Input, For, Current, N2, Line).
767search(127, Input, For, Current, _Nth, Line) :- 768 sub_string(For, 0, _, 1, For1),
769 !,
770 search_(Input, For1, Current, 1, Line).
771search(Char, Input, For, Current, Nth, Line) :-
772 code_type(Char, cntrl),
773 !,
774 search_end(Input, For, Current, Nth, Line),
775 el_push(Input, Char).
776search(Char, Input, For, Current, _Nth, Line) :-
777 format(string(For1), '~w~c', [For,Char]),
778 search_(Input, For1, Current, 1, Line).
779
780search_(Input, For1, Current, Nth, Line) :-
781 ( find_in_history(Input, For1, Current, Nth, Candidate)
782 -> search_print('', For1, Candidate)
783 ; search_print('failed ', For1, Current)
784 ),
785 search(Input, For1, Current, Nth, Line).
786
787search_end(Input, For, Current, Nth, Line) :-
788 ( find_in_history(Input, For, Current, Nth, Line)
789 -> true
790 ; Line = Current
791 ),
792 clear_line.
793
794find_in_history(_, "", Current, _, Current) :-
795 !.
796find_in_history(Input, For, _, Nth, Line) :-
797 el_history_events(Input, History),
798 call_nth(( member(_N-Line, History),
799 sub_string(Line, _, _, _, For)
800 ),
801 Nth),
802 !.
803
804search_print(State, Search, Current) :-
805 format(user_error, '\r(~wreverse-i-search)`~w\': ~w\e[0K',
806 [State, Search, Current]).
807
808clear_line :-
809 format(user_error, '\r\e[0K', []).
810
811
812 815
816:- meta_predicate
817 with_quote_flags(+,+,0). 818
819add_paste_quoted(Input) :-
820 current_prolog_flag(gui, true),
821 !,
822 el_addfn(Input, paste_quoted, 'Paste as quoted atom', paste_quoted),
823 el_bind(Input, ["^Y", paste_quoted]).
824add_paste_quoted(_).
825
831
832paste_quoted(Input, _Char, Continue) :-
833 clipboard_content(String),
834 quote_text(Input, String, Quoted),
835 el_insertstr(Input, Quoted),
836 Continue = refresh.
837
838quote_text(Input, String, Value) :-
839 el_line(Input, line(Before, _After)),
840 ( sub_string(Before, _, 1, 0, Quote)
841 -> true
842 ; Quote = "'"
843 ),
844 quote_text(Input, Quote, String, Value).
845
846quote_text(Input, "'", Text, Quoted) =>
847 format(string(Quoted), '~q', [Text]),
848 el_deletestr(Input, 1).
849quote_text(Input, "\"", Text, Quoted) =>
850 atom_string(Text, String),
851 with_quote_flags(
852 string, codes,
853 format(string(Quoted), '~q', [String])),
854 el_deletestr(Input, 1).
855quote_text(Input, "`", Text, Quoted) =>
856 atom_string(Text, String),
857 with_quote_flags(
858 codes, string,
859 format(string(Quoted), '~q', [String])),
860 el_deletestr(Input, 1).
861quote_text(_, _, Text, Quoted) =>
862 format(string(Quoted), '~q', [Text]).
863
864with_quote_flags(Double, Back, Goal) :-
865 current_prolog_flag(double_quotes, ODouble),
866 current_prolog_flag(back_quotes, OBack),
867 setup_call_cleanup(
868 ( set_prolog_flag(double_quotes, Double),
869 set_prolog_flag(back_quotes, Back) ),
870 Goal,
871 ( set_prolog_flag(double_quotes, ODouble),
872 set_prolog_flag(back_quotes, OBack) )).
873
874clipboard_content(Text) :-
875 current_prolog_flag(gui, true),
876 !,
877 autoload_call(in_pce_thread_sync(
878 autoload_call(
879 get(@(display), paste, primary, string(Text))))).
880clipboard_content("").
881
882
883 886
887:- multifile prolog:error_message//1. 888
889prolog:error_message(editline(Msg)) -->
890 [ 'editline: ~s'-[Msg] ]