View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2017-2025, VU University Amsterdam
    7                              CWI Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(editline,
   38          [ el_wrap/0,                          % wrap user_input, etc.
   39            el_wrap/1,                          % +Options
   40            el_wrap/4,                          % +Prog, +Input, +Output, +Error
   41            el_wrap/5,                          % +Prog, +Input, +Output, +Error, +Options
   42            el_wrapped/1,                       % +Input
   43            el_unwrap/1,                        % +Input
   44
   45            el_source/2,                        % +Input, +File
   46            el_bind/2,                          % +Input, +Args
   47            el_set/2,                           % +Input, +Action
   48            el_addfn/4,                         % +Input, +Name, +Help, :Goal
   49            el_cursor/2,                        % +Input, +Move
   50            el_line/2,                          % +Input, -Line
   51            el_insertstr/2,                     % +Input, +Text
   52            el_deletestr/2,                     % +Input, +Count
   53
   54            el_history/2,                       % +Input, ?Action
   55            el_history_events/2,                % +Input, -Events
   56            el_add_history/2,                   % +Input, +Line
   57            el_write_history/2,                 % +Input, +FileName
   58            el_read_history/2,                  % +Input, +FileName
   59
   60	    el_version/1			% -Version:integer
   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,                         % +Input
   76    prolog:complete_input/4.   77
   78
   79/** <module> BSD libedit based command line editing
   80
   81This library wraps the BSD  libedit   command  line  editor. The binding
   82provides a high level API to enable   command line editing on the Prolog
   83user streams and low level predicates  to   apply  the  library on other
   84streams and program the library.
   85*/
   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
   94%!  el_wrap is det.
   95%!  el_wrap(+Options) is det.
   96%
   97%   Enable using editline on the standard   user streams if `user_input`
   98%   is connected to a terminal. This is   the  high level predicate used
   99%   for most purposes. The remainder of the library interface deals with
  100%   low level predicates  that  allows   for  applying  and  programming
  101%   libedit in non-standard situations.
  102%
  103%   The library is registered  with  _ProgName_   set  to  `swipl`  (see
  104%   el_wrap/4).
  105%
  106%   Options processed:
  107%
  108%     - pipes(+Boolean)
  109%       Used by Epilog windows to indicate we are reading from a Windows
  110%       named pipe in _overlapped_ mode.  Ignored on other platforms.
  111%     - history(+Size)
  112%       Size of the history.  Default is defined by the Prolog flag
  113%       `history` or `100` if this flag is not defined.
  114%     - alert_signo(+Integer)
  115%       Signal used for making thread_signal/2 work while the thread
  116%       is in a blocking system call.
  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
  161%!  el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream) is det.
  162%!  el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream, +Options) is det.
  163%
  164%   Enable editline on  the  stream-triple   <In,Out,Error>.  From  this
  165%   moment on In is a handle to the command line editor.  Options:
  166%
  167%     - pipes(true)
  168%       Windows only. Assume the I/O is using pipes rather than a
  169%       console.  This is used for the Epilog terminal.
  170%
  171%   @arg ProgName is the name of the invoking program, used when reading
  172%   the editrc(5) file to determine which settings to use.
  173
  174el_wrap(ProgName, In, Out, Error) :-
  175    el_wrap(ProgName, In, Out, Error, []).
  176
  177%!  el_setup(+In:stream) is nondet.
  178%
  179%   This hooks is called as   forall(el_setup(Input),  true) _after_ the
  180%   input stream has been wrapped, the default Prolog commands have been
  181%   added and the  default  user  setup   file  has  been  sourced using
  182%   el_source/2. It can be used to define and bind additional commands.
  183
  184%!  el_wrapped(+In:stream) is semidet.
  185%
  186%   True if In is a stream wrapped by el_wrap/3.
  187
  188%!  el_unwrap(+In:stream) is det.
  189%
  190%   Remove the libedit wrapper for In and   the related output and error
  191%   streams.
  192%
  193%   @bug The wrapper creates =|FILE*|= handles that cannot be closed and
  194%   thus wrapping and unwrapping implies a (modest) memory leak.
  195
  196%!  el_source(+In:stream, +File) is det.
  197%
  198%   Initialise editline by reading the contents of File.  If File is
  199%   unbound try =|$HOME/.editrc|=
  200
  201
  202%!  el_bind(+In:stream, +Args) is det.
  203%
  204%   Invoke the libedit `bind` command  with   the  given  arguments. The
  205%   example below lists the current key bindings.
  206%
  207%   ```
  208%   ?- el_bind(user_input, ['-a']).
  209%   ```
  210%
  211%   The predicate el_bind/2 is typically used   to bind commands defined
  212%   using el_addfn/4. Note that the C proxy   function has only the last
  213%   character of the command as context to find the Prolog binding. This
  214%   implies we cannot both bind  e.g.,  "^[?"   _and_  "?"  to  a Prolog
  215%   function.
  216%
  217%   @see editrc(5) for more information.
  218
  219%!  el_addfn(+Input:stream, +Command, +Help, :Goal) is det.
  220%
  221%   Add a new command to the command  line editor associated with Input.
  222%   Command is the name of the command,  Help is the help string printed
  223%   with e.g. =|bind -a|= (see el_bind/2)  and   Goal  is  called of the
  224%   associated key-binding is activated.  Goal is called as
  225%
  226%       call(:Goal, +Input, +Char, -Continue)
  227%
  228%   where Input is the input stream providing access to the editor, Char
  229%   the activating character and Continue must   be instantated with one
  230%   of the known continuation  codes  as   defined  by  libedit: `norm`,
  231%   `newline`, `eof`, `arghack`, `refresh`,   `refresh_beep`,  `cursor`,
  232%   `redisplay`, `error` or `fatal`. In addition, the following Continue
  233%   code is provided.
  234%
  235%     * electric(Move, TimeOut, Continue)
  236%     Show _electric caret_ at Move positions to the left of the normal
  237%     cursor positions for the given TimeOut.  Continue as defined by
  238%     the Continue value.
  239%
  240%   The registered Goal typically used el_line/2 to fetch the input line
  241%   and el_cursor/2, el_insertstr/2 and/or  el_deletestr/2 to manipulate
  242%   the input line.
  243%
  244%   Normally el_bind/2 is used to associate   the defined command with a
  245%   keyboard sequence.
  246%
  247%   @see el_set(3) =EL_ADDFN= for details.
  248
  249%!  el_set(+Input:stream, +Action) is semidet.
  250%
  251%   Interface to el_set() and el_wset().   Currently provided values for
  252%   Action are:
  253%
  254%     - wordchars(+Text)
  255%       Set the characters considered part of a _word_.  This feature
  256%       depends on el_wsey() ``EL_WORDCHARS``, which is only provided
  257%       in some recent versions of `libedit`.
  258%
  259%   This predicate fails silently of Action  is not implemented. Illegal
  260%   input raises in an exception.
  261
  262%!  el_line(+Input:stream, -Line) is det.
  263%
  264%   Fetch the currently buffered input line. Line is a term line(Before,
  265%   After), where `Before` is  a  string   holding  the  text before the
  266%   cursor and `After` is a string holding the text after the cursor.
  267
  268%!  el_cursor(+Input:stream, +Move:integer) is det.
  269%
  270%   Move the cursor Move  character   forwards  (positive)  or backwards
  271%   (negative).
  272
  273%!  el_insertstr(+Input:stream, +Text) is det.
  274%
  275%   Insert Text at the cursor.
  276
  277%!  el_deletestr(+Input:stream, +Count) is det.
  278%
  279%   Delete Count characters before the cursor.
  280
  281%!  el_history(+In:stream, ?Action) is det.
  282%
  283%   Perform a generic action on the history. This provides an incomplete
  284%   interface to history() from libedit.  Supported actions are:
  285%
  286%     - clear
  287%       Clear the history.
  288%     - setsize(+Integer)
  289%       Set size of history to size elements.
  290%     - getsize(-Integer)
  291%       Unify Integer with the maximum size of the history.  Note that
  292%       this is _not_ the same as el_history() using ``H_GETSIZE``,
  293%       which returns the number of currently saved events. The number
  294%       of saved events may be computed from `first` and `last` or
  295%       using el_history_events/2.
  296%     - setunique(+Boolean)
  297%       Set flag that adjacent identical event strings should not be
  298%       entered into the history.
  299%     - first(-Num, -String)
  300%     - last(-Num, -String)
  301%     - curr(-Num, -String)
  302%     - prev(-Num, -String)
  303%     - next(-Num, -String)
  304%       Retrieve an event.  Num is the event number and String is the
  305%       event string.  Note that `first` is the most recent event and
  306%       `last` the oldest.
  307%     - set(Num)
  308%       Set the notion of _current_ to Num.
  309%     - prev_str(+Search, -Num, -String)
  310%     - next_str(+Search, -Num, -String)
  311%       Retrieve the previous or next event whose String starts with
  312%       Search.
  313%     - event(+Num, -String)
  314%       True when String represents event Num.   This is an extension to
  315%       the history() API, retrieving a numbered event without changing
  316%       the current notion.
  317
  318%!  el_history_events(+In:stream, -Events:list(pair)) is det.
  319%
  320%   Unify Events with a list of pairs   of  the form `Num-String`, where
  321%   `Num` is the event number  and   `String`  is  the associated string
  322%   without terminating newline.
  323
  324%!  el_add_history(+In:stream, +Line:text) is det.
  325%
  326%   Add a line to the command line history.
  327
  328%!  el_read_history(+In:stream, +File:file) is det.
  329%
  330%   Read the history saved using el_write_history/2.
  331%
  332%   @arg File is a file specification for absolute_file_name/3.
  333
  334%!  el_write_history(+In:stream, +File:file) is det.
  335%
  336%   Save editline history to File.  The   history  may be reloaded using
  337%   el_read_history/2.
  338%
  339%   @arg File is a file specification for absolute_file_name/3.
  340
  341%!  el_version(-Version)
  342%
  343%   True when Version  is ``LIBEDIT_MAJOR*10000 + LIBEDIT_MINOR*100``.
  344%   The  version is  generated from  the include  file ``histedit.h``,
  345%   which implies that the actual version of the shared library may be
  346%   different.
  347
  348%!  prolog:history(+Input, ?Action) is semidet.
  349%
  350%   Provide  the  plugable  interface  into   the  system  command  line
  351%   management.
  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
  384%!  compat_read_history(+Input, +File) is det.
  385%
  386%   Read the saved history. This loads both  the LibEdit and old history
  387%   format used by `swipl-win.exe` before migrating to SDL.
  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		 /*******************************
  411		 *        ELECTRIC CARET	*
  412		 *******************************/
  413
  414%!  bind_electric(+Input) is det.
  415%
  416%   Bind known close statements for electric input
  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
  427%!  electric(+Input, +Char, -Continue) is det.
  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(_,_)                   % open quote
  437        ->  Continue = refresh
  438        ;   matching_open(RevNesting, Close, _, Index)
  439        ->  string_length(Before, Len),         % Proper match
  440            Move is Index-Len,
  441            Continue = electric(Move, 500, refresh)
  442        ;   Continue = refresh_beep             % Not properly nested
  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)]                   % Open quote
  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		 /*******************************
  537		 *           COMPLETION		*
  538		 *******************************/
  539
  540%!  complete(+Input, +Char, -Continue) is det.
  541%
  542%   Implementation of the registered `complete`   editline function. The
  543%   predicate is called with three arguments,  the first being the input
  544%   stream used to access  the  libedit   functions  and  the second the
  545%   activating character. The last argument tells   libedit  what to do.
  546%   Consult el_set(3), =EL_ADDFN= for details.
  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
  602%!  show_completions(+Input, +Char, -Continue) is det.
  603%
  604%   Editline command to show possible completions.
  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
  616%!  common_competion(+Alternatives, -Common) is det.
  617%
  618%   True when Common is the common prefix of all candidate Alternatives.
  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
  629%!  common_prefix(+Atoms, -Common) is det.
  630%
  631%   True when Common is the common prefix of all Atoms.
  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
  641%!  common_prefix(+A1, +A2, -Prefix:string) is det.
  642%
  643%   True when Prefix is the common prefix of the atoms A1 and A2
  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
  666%!  list_alternatives(+Alternatives)
  667%
  668%   List possible completions at the current point.
  669%
  670%   @tbd currently ignores the Comment in Text-Comment alternatives.
  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		 /*******************************
  731		 *             SEARCH		*
  732		 *******************************/
  733
  734%!  isearch_history(+Input, +Char, -Continue) is det.
  735%
  736%   Incremental search through the history.  The behavior is based
  737%   on GNU readline.
  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) :-    % C-g: abort
  757    !,
  758    clear_line.
  759search(18, Input, For, Current, Nth, Line) :-   % C-r: search previous
  760    !,
  761    N2 is Nth+1,
  762    search_(Input, For, Current, N2, Line).
  763search(19, Input, For, Current, Nth, Line) :-   % C-s: search next
  764    !,
  765    N2 is max(1,Nth-1),
  766    search_(Input, For, Current, N2, Line).
  767search(127, Input, For, Current, _Nth, Line) :- % DEL/BS: shorten search
  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                /*******************************
  813                *         PASTE QUOTED         *
  814                *******************************/
  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
  826%!  paste_quoted(+Input, +Char, -Continue) is det.
  827%
  828%   Paste the selection as quoted Prolog value.   The quoting type
  829%   depends on the quote before the caret.  If there is no quote
  830%   before the caret we paste as an atom.
  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                /*******************************
  884                *           MESSAGE            *
  885                *******************************/
  886
  887:- multifile prolog:error_message//1.  888
  889prolog:error_message(editline(Msg)) -->
  890    [ 'editline: ~s'-[Msg] ]