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_addfn/4,                         % +Input, +Name, +Help, :Goal
   48            el_cursor/2,                        % +Input, +Move
   49            el_line/2,                          % +Input, -Line
   50            el_insertstr/2,                     % +Input, +Text
   51            el_deletestr/2,                     % +Input, +Count
   52
   53            el_history/2,                       % +Input, ?Action
   54            el_history_events/2,                % +Input, -Events
   55            el_add_history/2,                   % +Input, +Line
   56            el_write_history/2,                 % +Input, +FileName
   57            el_read_history/2,                  % +Input, +FileName
   58
   59	    el_version/1			% -Version:integer
   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,                         % +Input
   75    prolog:complete_input/4.   76
   77
   78/** <module> BSD libedit based command line editing
   79
   80This library wraps the BSD  libedit   command  line  editor. The binding
   81provides a high level API to enable   command line editing on the Prolog
   82user streams and low level predicates  to   apply  the  library on other
   83streams and program the library.
   84*/
   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
   93%!  el_wrap is det.
   94%!  el_wrap(+Options) is det.
   95%
   96%   Enable using editline on the standard   user streams if `user_input`
   97%   is connected to a terminal. This is   the  high level predicate used
   98%   for most purposes. The remainder of the library interface deals with
   99%   low level predicates  that  allows   for  applying  and  programming
  100%   libedit in non-standard situations.
  101%
  102%   The library is registered  with  _ProgName_   set  to  `swipl`  (see
  103%   el_wrap/4).
  104%
  105%   Options processed:
  106%
  107%     - pipes(+Boolean)
  108%       Used by Epilog windows to indicate we are reading from a Windows
  109%       named pipe in _overlapped_ mode.  Ignored on other platforms.
  110%     - history(+Size)
  111%       Size of the history.  Default is defined by the Prolog flag
  112%       `history` or `100` if this flag is not defined.
  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
  151%!  el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream) is det.
  152%!  el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream, +Options) is det.
  153%
  154%   Enable editline on  the  stream-triple   <In,Out,Error>.  From  this
  155%   moment on In is a handle to the command line editor.  Options:
  156%
  157%     - pipes(true)
  158%       Windows only. Assume the I/O is using pipes rather than a
  159%       console.  This is used for the Epilog terminal.
  160%
  161%   @arg ProgName is the name of the invoking program, used when reading
  162%   the editrc(5) file to determine which settings to use.
  163
  164el_wrap(ProgName, In, Out, Error) :-
  165    el_wrap(ProgName, In, Out, Error, []).
  166
  167%!  el_setup(+In:stream) is nondet.
  168%
  169%   This hooks is called as   forall(el_setup(Input),  true) _after_ the
  170%   input stream has been wrapped, the default Prolog commands have been
  171%   added and the  default  user  setup   file  has  been  sourced using
  172%   el_source/2. It can be used to define and bind additional commands.
  173
  174%!  el_wrapped(+In:stream) is semidet.
  175%
  176%   True if In is a stream wrapped by el_wrap/3.
  177
  178%!  el_unwrap(+In:stream) is det.
  179%
  180%   Remove the libedit wrapper for In and   the related output and error
  181%   streams.
  182%
  183%   @bug The wrapper creates =|FILE*|= handles that cannot be closed and
  184%   thus wrapping and unwrapping implies a (modest) memory leak.
  185
  186%!  el_source(+In:stream, +File) is det.
  187%
  188%   Initialise editline by reading the contents of File.  If File is
  189%   unbound try =|$HOME/.editrc|=
  190
  191
  192%!  el_bind(+In:stream, +Args) is det.
  193%
  194%   Invoke the libedit `bind` command  with   the  given  arguments. The
  195%   example below lists the current key bindings.
  196%
  197%   ```
  198%   ?- el_bind(user_input, ['-a']).
  199%   ```
  200%
  201%   The predicate el_bind/2 is typically used   to bind commands defined
  202%   using el_addfn/4. Note that the C proxy   function has only the last
  203%   character of the command as context to find the Prolog binding. This
  204%   implies we cannot both bind  e.g.,  "^[?"   _and_  "?"  to  a Prolog
  205%   function.
  206%
  207%   @see editrc(5) for more information.
  208
  209%!  el_addfn(+Input:stream, +Command, +Help, :Goal) is det.
  210%
  211%   Add a new command to the command  line editor associated with Input.
  212%   Command is the name of the command,  Help is the help string printed
  213%   with e.g. =|bind -a|= (see el_bind/2)  and   Goal  is  called of the
  214%   associated key-binding is activated.  Goal is called as
  215%
  216%       call(:Goal, +Input, +Char, -Continue)
  217%
  218%   where Input is the input stream providing access to the editor, Char
  219%   the activating character and Continue must   be instantated with one
  220%   of the known continuation  codes  as   defined  by  libedit: `norm`,
  221%   `newline`, `eof`, `arghack`, `refresh`,   `refresh_beep`,  `cursor`,
  222%   `redisplay`, `error` or `fatal`. In addition, the following Continue
  223%   code is provided.
  224%
  225%     * electric(Move, TimeOut, Continue)
  226%     Show _electric caret_ at Move positions to the left of the normal
  227%     cursor positions for the given TimeOut.  Continue as defined by
  228%     the Continue value.
  229%
  230%   The registered Goal typically used el_line/2 to fetch the input line
  231%   and el_cursor/2, el_insertstr/2 and/or  el_deletestr/2 to manipulate
  232%   the input line.
  233%
  234%   Normally el_bind/2 is used to associate   the defined command with a
  235%   keyboard sequence.
  236%
  237%   @see el_set(3) =EL_ADDFN= for details.
  238
  239%!  el_line(+Input:stream, -Line) is det.
  240%
  241%   Fetch the currently buffered input line. Line is a term line(Before,
  242%   After), where `Before` is  a  string   holding  the  text before the
  243%   cursor and `After` is a string holding the text after the cursor.
  244
  245%!  el_cursor(+Input:stream, +Move:integer) is det.
  246%
  247%   Move the cursor Move  character   forwards  (positive)  or backwards
  248%   (negative).
  249
  250%!  el_insertstr(+Input:stream, +Text) is det.
  251%
  252%   Insert Text at the cursor.
  253
  254%!  el_deletestr(+Input:stream, +Count) is det.
  255%
  256%   Delete Count characters before the cursor.
  257
  258%!  el_history(+In:stream, ?Action) is det.
  259%
  260%   Perform a generic action on the history. This provides an incomplete
  261%   interface to history() from libedit.  Supported actions are:
  262%
  263%     - clear
  264%       Clear the history.
  265%     - setsize(+Integer)
  266%       Set size of history to size elements.
  267%     - getsize(-Integer)
  268%       Unify Integer with the maximum size of the history.  Note that
  269%       this is _not_ the same as el_history() using ``H_GETSIZE``,
  270%       which returns the number of currently saved events. The number
  271%       of saved events may be computed from `first` and `last` or
  272%       using el_history_events/2.
  273%     - setunique(+Boolean)
  274%       Set flag that adjacent identical event strings should not be
  275%       entered into the history.
  276%     - first(-Num, -String)
  277%     - last(-Num, -String)
  278%     - curr(-Num, -String)
  279%     - prev(-Num, -String)
  280%     - next(-Num, -String)
  281%       Retrieve an event.  Num is the event number and String is the
  282%       event string.  Note that `first` is the most recent event and
  283%       `last` the oldest.
  284%     - set(Num)
  285%       Set the notion of _current_ to Num.
  286%     - prev_str(+Search, -Num, -String)
  287%     - next_str(+Search, -Num, -String)
  288%       Retrieve the previous or next event whose String starts with
  289%       Search.
  290%     - event(+Num, -String)
  291%       True when String represents event Num.   This is an extension to
  292%       the history() API, retrieving a numbered event without changing
  293%       the current notion.
  294
  295%!  el_history_events(+In:stream, -Events:list(pair)) is det.
  296%
  297%   Unify Events with a list of pairs   of  the form `Num-String`, where
  298%   `Num` is the event number  and   `String`  is  the associated string
  299%   without terminating newline.
  300
  301%!  el_add_history(+In:stream, +Line:text) is det.
  302%
  303%   Add a line to the command line history.
  304
  305%!  el_read_history(+In:stream, +File:file) is det.
  306%
  307%   Read the history saved using el_write_history/2.
  308%
  309%   @arg File is a file specification for absolute_file_name/3.
  310
  311%!  el_write_history(+In:stream, +File:file) is det.
  312%
  313%   Save editline history to File.  The   history  may be reloaded using
  314%   el_read_history/2.
  315%
  316%   @arg File is a file specification for absolute_file_name/3.
  317
  318%!  el_version(-Version)
  319%
  320%   True when Version  is ``LIBEDIT_MAJOR*10000 + LIBEDIT_MINOR*100``.
  321%   The  version is  generated from  the include  file ``histedit.h``,
  322%   which implies that the actual version of the shared library may be
  323%   different.
  324
  325%!  prolog:history(+Input, ?Action) is semidet.
  326%
  327%   Provide  the  plugable  interface  into   the  system  command  line
  328%   management.
  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
  361%!  compat_read_history(+Input, +File) is det.
  362%
  363%   Read the saved history. This loads both  the LibEdit and old history
  364%   format used by `swipl-win.exe` before migrating to SDL.
  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		 /*******************************
  388		 *        ELECTRIC CARET	*
  389		 *******************************/
  390
  391%!  bind_electric(+Input) is det.
  392%
  393%   Bind known close statements for electric input
  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
  404%!  electric(+Input, +Char, -Continue) is det.
  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(_,_)                   % open quote
  414        ->  Continue = refresh
  415        ;   matching_open(RevNesting, Close, _, Index)
  416        ->  string_length(Before, Len),         % Proper match
  417            Move is Index-Len,
  418            Continue = electric(Move, 500, refresh)
  419        ;   Continue = refresh_beep             % Not properly nested
  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)]                   % Open quote
  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		 /*******************************
  514		 *           COMPLETION		*
  515		 *******************************/
  516
  517%!  complete(+Input, +Char, -Continue) is det.
  518%
  519%   Implementation of the registered `complete`   editline function. The
  520%   predicate is called with three arguments,  the first being the input
  521%   stream used to access  the  libedit   functions  and  the second the
  522%   activating character. The last argument tells   libedit  what to do.
  523%   Consult el_set(3), =EL_ADDFN= for details.
  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
  579%!  show_completions(+Input, +Char, -Continue) is det.
  580%
  581%   Editline command to show possible completions.
  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
  593%!  common_competion(+Alternatives, -Common) is det.
  594%
  595%   True when Common is the common prefix of all candidate Alternatives.
  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
  606%!  common_prefix(+Atoms, -Common) is det.
  607%
  608%   True when Common is the common prefix of all Atoms.
  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
  618%!  common_prefix(+A1, +A2, -Prefix:string) is det.
  619%
  620%   True when Prefix is the common prefix of the atoms A1 and A2
  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
  643%!  list_alternatives(+Alternatives)
  644%
  645%   List possible completions at the current point.
  646%
  647%   @tbd currently ignores the Comment in Text-Comment alternatives.
  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		 /*******************************
  708		 *             SEARCH		*
  709		 *******************************/
  710
  711%!  isearch_history(+Input, +Char, -Continue) is det.
  712%
  713%   Incremental search through the history.  The behavior is based
  714%   on GNU readline.
  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) :-    % C-g: abort
  734    !,
  735    clear_line.
  736search(18, Input, For, Current, Nth, Line) :-   % C-r: search previous
  737    !,
  738    N2 is Nth+1,
  739    search_(Input, For, Current, N2, Line).
  740search(19, Input, For, Current, Nth, Line) :-   % C-s: search next
  741    !,
  742    N2 is max(1,Nth-1),
  743    search_(Input, For, Current, N2, Line).
  744search(127, Input, For, Current, _Nth, Line) :- % DEL/BS: shorten search
  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                /*******************************
  790                *         PASTE QUOTED         *
  791                *******************************/
  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
  803%!  paste_quoted(+Input, +Char, -Continue) is det.
  804%
  805%   Paste the selection as quoted Prolog value.   The quoting type
  806%   depends on the quote before the caret.  If there is no quote
  807%   before the caret we paste as an atom.
  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                /*******************************
  861                *           MESSAGE            *
  862                *******************************/
  863
  864:- multifile prolog:error_message//1.  865
  866prolog:error_message(editline(Msg)) -->
  867    [ 'editline: ~s'-[Msg] ]