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:- autoload(library(apply),[maplist/2,maplist/3]).   60:- autoload(library(lists),[reverse/2,max_list/2,append/3,member/2]).   61:- autoload(library(solution_sequences),[call_nth/2]).   62
   63:- use_foreign_library(foreign(libedit4pl)).   64
   65:- initialization el_wrap_if_ok.   66
   67:- meta_predicate
   68    el_addfn(+,+,+,3).   69
   70:- multifile
   71    el_setup/1,                         % +Input
   72    prolog:complete_input/4.   73
   74
   75/** <module> BSD libedit based command line editing
   76
   77This library wraps the BSD  libedit   command  line  editor. The binding
   78provides a high level API to enable   command line editing on the Prolog
   79user streams and low level predicates  to   apply  the  library on other
   80streams and program the library.
   81*/
   82
   83el_wrap_if_ok :-
   84    \+ current_prolog_flag(console_menu_version, qt),
   85    \+ current_prolog_flag(readline, readline),
   86    stream_property(user_input, tty(true)),
   87    !,
   88    el_wrap.
   89el_wrap_if_ok.
   90
   91%!  el_wrap is det.
   92%!  el_wrap(+Options) is det.
   93%
   94%   Enable using editline on the standard   user streams if `user_input`
   95%   is connected to a terminal. This is   the  high level predicate used
   96%   for most purposes. The remainder of the library interface deals with
   97%   low level predicates  that  allows   for  applying  and  programming
   98%   libedit in non-standard situations.
   99%
  100%   The library is registered  with  _ProgName_   set  to  =swipl=  (see
  101%   el_wrap/4).
  102
  103el_wrap :-
  104    el_wrap([]).
  105
  106el_wrap(_) :-
  107    el_wrapped(user_input),
  108    !.
  109el_wrap(Options) :-
  110    stream_property(user_input, tty(true)), !,
  111    el_wrap(swipl, user_input, user_output, user_error, Options),
  112    add_prolog_commands(user_input),
  113    forall(el_setup(user_input), true).
  114el_wrap(_).
  115
  116add_prolog_commands(Input) :-
  117    el_addfn(Input, complete, 'Complete atoms and files', complete),
  118    el_addfn(Input, show_completions, 'List completions', show_completions),
  119    el_addfn(Input, electric, 'Indicate matching bracket', electric),
  120    el_addfn(Input, isearch_history, 'Incremental search in history',
  121             isearch_history),
  122    el_bind(Input, ["^I",  complete]),
  123    el_bind(Input, ["^[?", show_completions]),
  124    el_bind(Input, ["^R",  isearch_history]),
  125    bind_electric(Input),
  126    add_paste_quoted(Input),
  127    el_source(Input, _).
  128
  129%!  el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream) is det.
  130%!  el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream, +Options) is det.
  131%
  132%   Enable editline on  the  stream-triple   <In,Out,Error>.  From  this
  133%   moment on In is a handle to the command line editor.  Options:
  134%
  135%     - pipes(true)
  136%       Windows only. Assume the I/O is using pipes rather than a
  137%       console.  This is used for the Epilog terminal.
  138%
  139%   @arg ProgName is the name of the invoking program, used when reading
  140%   the editrc(5) file to determine which settings to use.
  141
  142el_wrap(ProgName, In, Out, Error) :-
  143    el_wrap(ProgName, In, Out, Error, []).
  144
  145%!  el_setup(+In:stream) is nondet.
  146%
  147%   This hooks is called as   forall(el_setup(Input),  true) _after_ the
  148%   input stream has been wrapped, the default Prolog commands have been
  149%   added and the  default  user  setup   file  has  been  sourced using
  150%   el_source/2. It can be used to define and bind additional commands.
  151
  152%!  el_wrapped(+In:stream) is semidet.
  153%
  154%   True if In is a stream wrapped by el_wrap/3.
  155
  156%!  el_unwrap(+In:stream) is det.
  157%
  158%   Remove the libedit wrapper for In and   the related output and error
  159%   streams.
  160%
  161%   @bug The wrapper creates =|FILE*|= handles that cannot be closed and
  162%   thus wrapping and unwrapping implies a (modest) memory leak.
  163
  164%!  el_source(+In:stream, +File) is det.
  165%
  166%   Initialise editline by reading the contents of File.  If File is
  167%   unbound try =|$HOME/.editrc|=
  168
  169
  170%!  el_bind(+In:stream, +Args) is det.
  171%
  172%   Invoke the libedit `bind` command  with   the  given  arguments. The
  173%   example below lists the current key bindings.
  174%
  175%   ```
  176%   ?- el_bind(user_input, ['-a']).
  177%   ```
  178%
  179%   The predicate el_bind/2 is typically used   to bind commands defined
  180%   using el_addfn/4. Note that the C proxy   function has only the last
  181%   character of the command as context to find the Prolog binding. This
  182%   implies we cannot both  bind  e.g.,  "^[?"  *and  "?"  to  a  Prolog
  183%   function.
  184%
  185%   @see editrc(5) for more information.
  186
  187%!  el_addfn(+Input:stream, +Command, +Help, :Goal) is det.
  188%
  189%   Add a new command to the command  line editor associated with Input.
  190%   Command is the name of the command,  Help is the help string printed
  191%   with e.g. =|bind -a|= (see el_bind/2)  and   Goal  is  called of the
  192%   associated key-binding is activated.  Goal is called as
  193%
  194%       call(:Goal, +Input, +Char, -Continue)
  195%
  196%   where Input is the input stream providing access to the editor, Char
  197%   the activating character and Continue must   be instantated with one
  198%   of the known continuation  codes  as   defined  by  libedit: `norm`,
  199%   `newline`, `eof`, `arghack`, `refresh`,   `refresh_beep`,  `cursor`,
  200%   `redisplay`, `error` or `fatal`. In addition, the following Continue
  201%   code is provided.
  202%
  203%     * electric(Move, TimeOut, Continue)
  204%     Show _electric caret_ at Move positions to the left of the normal
  205%     cursor positions for the given TimeOut.  Continue as defined by
  206%     the Continue value.
  207%
  208%   The registered Goal typically used el_line/2 to fetch the input line
  209%   and el_cursor/2, el_insertstr/2 and/or  el_deletestr/2 to manipulate
  210%   the input line.
  211%
  212%   Normally el_bind/2 is used to associate   the defined command with a
  213%   keyboard sequence.
  214%
  215%   @see el_set(3) =EL_ADDFN= for details.
  216
  217%!  el_line(+Input:stream, -Line) is det.
  218%
  219%   Fetch the currently buffered input line. Line is a term line(Before,
  220%   After), where `Before` is  a  string   holding  the  text before the
  221%   cursor and `After` is a string holding the text after the cursor.
  222
  223%!  el_cursor(+Input:stream, +Move:integer) is det.
  224%
  225%   Move the cursor Move  character   forwards  (positive)  or backwards
  226%   (negative).
  227
  228%!  el_insertstr(+Input:stream, +Text) is det.
  229%
  230%   Insert Text at the cursor.
  231
  232%!  el_deletestr(+Input:stream, +Count) is det.
  233%
  234%   Delete Count characters before the cursor.
  235
  236%!  el_history(+In:stream, ?Action) is det.
  237%
  238%   Perform a generic action on the history. This provides an incomplete
  239%   interface to history() from libedit.  Supported actions are:
  240%
  241%     * clear
  242%     Clear the history.
  243%     * setsize(+Integer)
  244%     Set size of history to size elements.
  245%     * setunique(+Boolean)
  246%     Set flag that adjacent identical event strings should not be
  247%     entered into the history.
  248
  249%!  el_history_events(+In:stream, -Events:list(pair)) is det.
  250%
  251%   Unify Events with a list of pairs   of  the form `Num-String`, where
  252%   `Num` is the event number  and   `String`  is  the associated string
  253%   without terminating newline.
  254
  255%!  el_add_history(+In:stream, +Line:text) is det.
  256%
  257%   Add a line to the command line history.
  258
  259%!  el_read_history(+In:stream, +File:file) is det.
  260%
  261%   Read the history saved using el_write_history/2.
  262%
  263%   @arg File is a file specification for absolute_file_name/3.
  264
  265%!  el_write_history(+In:stream, +File:file) is det.
  266%
  267%   Save editline history to File.  The   history  may be reloaded using
  268%   el_read_history/2.
  269%
  270%   @arg File is a file specification for absolute_file_name/3.
  271
  272
  273:- multifile
  274    prolog:history/2.  275
  276prolog:history(Input, add(Line)) :-
  277    el_add_history(Input, Line).
  278prolog:history(Input, load(File)) :-
  279    el_read_history(Input, File).
  280prolog:history(Input, save(File)) :-
  281    el_write_history(Input, File).
  282prolog:history(Input, load) :-
  283    el_history_events(Input, Events),
  284    load_history_events(Events).
  285
  286%!  load_history_events(+Events)
  287%
  288%   Load events into the history handling of `boot/history.pl`
  289
  290load_history_events(Events) :-
  291    '$reverse'(Events, RevEvents),
  292    forall('$member'(Ev, RevEvents),
  293           add_event(Ev)).
  294
  295add_event(Num-String) :-
  296    remove_dot(String, String1),
  297    '$save_history_event'(Num-String1).
  298
  299remove_dot(String0, String) :-
  300    string_concat(String, ".", String0),
  301    !.
  302remove_dot(String, String).
  303
  304
  305		 /*******************************
  306		 *        ELECTRIC CARET	*
  307		 *******************************/
  308
  309%!  bind_electric(+Input) is det.
  310%
  311%   Bind known close statements for electric input
  312
  313bind_electric(Input) :-
  314    forall(bracket(_Open, Close), bind_code(Input, Close, electric)),
  315    forall(quote(Close), bind_code(Input, Close, electric)).
  316
  317bind_code(Input, Code, Command) :-
  318    string_codes(Key, [Code]),
  319    el_bind(Input, [Key, Command]).
  320
  321
  322%!  electric(+Input, +Char, -Continue) is det.
  323
  324electric(Input, Char, Continue) :-
  325    string_codes(Str, [Char]),
  326    el_insertstr(Input, Str),
  327    el_line(Input, line(Before, _)),
  328    (   string_codes(Before, Codes),
  329        nesting(Codes, 0, Nesting),
  330        reverse(Nesting, [Close|RevNesting])
  331    ->  (   Close = open(_,_)                   % open quote
  332        ->  Continue = refresh
  333        ;   matching_open(RevNesting, Close, _, Index)
  334        ->  string_length(Before, Len),         % Proper match
  335            Move is Index-Len,
  336            Continue = electric(Move, 500, refresh)
  337        ;   Continue = refresh_beep             % Not properly nested
  338        )
  339    ;   Continue = refresh_beep
  340    ).
  341
  342matching_open_index(String, Index) :-
  343    string_codes(String, Codes),
  344    nesting(Codes, 0, Nesting),
  345    reverse(Nesting, [Close|RevNesting]),
  346    matching_open(RevNesting, Close, _, Index).
  347
  348matching_open([Open|Rest], Close, Rest, Index) :-
  349    Open = open(Index,_),
  350    match(Open, Close),
  351    !.
  352matching_open([Close1|Rest1], Close, Rest, Index) :-
  353    Close1 = close(_,_),
  354    matching_open(Rest1, Close1, Rest2, _),
  355    matching_open(Rest2, Close, Rest, Index).
  356
  357match(open(_,Open),close(_,Close)) :-
  358    (   bracket(Open, Close)
  359    ->  true
  360    ;   Open == Close,
  361        quote(Open)
  362    ).
  363
  364bracket(0'(, 0')).
  365bracket(0'[, 0']).
  366bracket(0'{, 0'}).
  367
  368quote(0'\').
  369quote(0'\").
  370quote(0'\`).
  371
  372nesting([], _, []).
  373nesting([H|T], I, Nesting) :-
  374    (   bracket(H, _Close)
  375    ->  Nesting = [open(I,H)|Nest]
  376    ;   bracket(_Open, H)
  377    ->  Nesting = [close(I,H)|Nest]
  378    ),
  379    !,
  380    I2 is I+1,
  381    nesting(T, I2, Nest).
  382nesting([0'0, 0'\'|T], I, Nesting) :-
  383    !,
  384    phrase(skip_code, T, T1),
  385    difflist_length(T, T1, Len),
  386    I2 is I+Len+2,
  387    nesting(T1, I2, Nesting).
  388nesting([H|T], I, Nesting) :-
  389    quote(H),
  390    !,
  391    (   phrase(skip_quoted(H), T, T1)
  392    ->  difflist_length(T, T1, Len),
  393        I2 is I+Len+1,
  394        Nesting = [open(I,H),close(I2,H)|Nest],
  395        nesting(T1, I2, Nest)
  396    ;   Nesting = [open(I,H)]                   % Open quote
  397    ).
  398nesting([_|T], I, Nesting) :-
  399    I2 is I+1,
  400    nesting(T, I2, Nesting).
  401
  402difflist_length(List, Tail, Len) :-
  403    difflist_length(List, Tail, 0, Len).
  404
  405difflist_length(List, Tail, Len0, Len) :-
  406    List == Tail,
  407    !,
  408    Len = Len0.
  409difflist_length([_|List], Tail, Len0, Len) :-
  410    Len1 is Len0+1,
  411    difflist_length(List, Tail, Len1, Len).
  412
  413skip_quoted(H) -->
  414    [H],
  415    !.
  416skip_quoted(H) -->
  417    "\\", [H],
  418    !,
  419    skip_quoted(H).
  420skip_quoted(H) -->
  421    [_],
  422    skip_quoted(H).
  423
  424skip_code -->
  425    "\\", [_],
  426    !.
  427skip_code -->
  428    [_].
  429
  430
  431		 /*******************************
  432		 *           COMPLETION		*
  433		 *******************************/
  434
  435%!  complete(+Input, +Char, -Continue) is det.
  436%
  437%   Implementation of the registered `complete`   editline function. The
  438%   predicate is called with three arguments,  the first being the input
  439%   stream used to access  the  libedit   functions  and  the second the
  440%   activating character. The last argument tells   libedit  what to do.
  441%   Consult el_set(3), =EL_ADDFN= for details.
  442
  443
  444:- dynamic
  445    last_complete/2.  446
  447complete(Input, _Char, Continue) :-
  448    el_line(Input, line(Before, After)),
  449    ensure_input_completion,
  450    prolog:complete_input(Before, After, Delete, Completions),
  451    (   Completions = [One]
  452    ->  string_length(Delete, Len),
  453        el_deletestr(Input, Len),
  454        complete_text(One, Text),
  455        el_insertstr(Input, Text),
  456        Continue = refresh
  457    ;   Completions == []
  458    ->  Continue = refresh_beep
  459    ;   get_time(Now),
  460        retract(last_complete(TLast, Before)),
  461        Now - TLast < 2
  462    ->  nl(user_error),
  463        list_alternatives(Completions),
  464        Continue = redisplay
  465    ;   retractall(last_complete(_,_)),
  466        get_time(Now),
  467        asserta(last_complete(Now, Before)),
  468        common_competion(Completions, Extend),
  469        (   Delete == Extend
  470        ->  Continue = refresh_beep
  471        ;   string_length(Delete, Len),
  472            el_deletestr(Input, Len),
  473            el_insertstr(Input, Extend),
  474            Continue = refresh
  475        )
  476    ).
  477
  478:- dynamic
  479    input_completion_loaded/0.  480
  481ensure_input_completion :-
  482    input_completion_loaded,
  483    !.
  484ensure_input_completion :-
  485    predicate_property(prolog:complete_input(_,_,_,_),
  486                       number_of_clauses(N)),
  487    N > 0,
  488    !.
  489ensure_input_completion :-
  490    exists_source(library(console_input)),
  491    !,
  492    use_module(library(console_input), []),
  493    asserta(input_completion_loaded).
  494ensure_input_completion.
  495
  496
  497%!  show_completions(+Input, +Char, -Continue) is det.
  498%
  499%   Editline command to show possible completions.
  500
  501show_completions(Input, _Char, Continue) :-
  502    el_line(Input, line(Before, After)),
  503    prolog:complete_input(Before, After, _Delete, Completions),
  504    nl(user_error),
  505    list_alternatives(Completions),
  506    Continue = redisplay.
  507
  508complete_text(Text-_Comment, Text) :- !.
  509complete_text(Text, Text).
  510
  511%!  common_competion(+Alternatives, -Common) is det.
  512%
  513%   True when Common is the common prefix of all candidate Alternatives.
  514
  515common_competion(Alternatives, Common) :-
  516    maplist(atomic, Alternatives),
  517    !,
  518    common_prefix(Alternatives, Common).
  519common_competion(Alternatives, Common) :-
  520    maplist(complete_text, Alternatives, AltText),
  521    !,
  522    common_prefix(AltText, Common).
  523
  524%!  common_prefix(+Atoms, -Common) is det.
  525%
  526%   True when Common is the common prefix of all Atoms.
  527
  528common_prefix([A1|T], Common) :-
  529    common_prefix_(T, A1, Common).
  530
  531common_prefix_([], Common, Common).
  532common_prefix_([H|T], Common0, Common) :-
  533    common_prefix(H, Common0, Common1),
  534    common_prefix_(T, Common1, Common).
  535
  536%!  common_prefix(+A1, +A2, -Prefix:string) is det.
  537%
  538%   True when Prefix is the common prefix of the atoms A1 and A2
  539
  540common_prefix(A1, A2, Prefix) :-
  541    sub_atom(A1, 0, _, _, A2),
  542    !,
  543    Prefix = A2.
  544common_prefix(A1, A2, Prefix) :-
  545    sub_atom(A2, 0, _, _, A1),
  546    !,
  547    Prefix = A1.
  548common_prefix(A1, A2, Prefix) :-
  549    atom_codes(A1, C1),
  550    atom_codes(A2, C2),
  551    list_common_prefix(C1, C2, C),
  552    string_codes(Prefix, C).
  553
  554list_common_prefix([H|T0], [H|T1], [H|T]) :-
  555    !,
  556    list_common_prefix(T0, T1, T).
  557list_common_prefix(_, _, []).
  558
  559
  560
  561%!  list_alternatives(+Alternatives)
  562%
  563%   List possible completions at the current point.
  564%
  565%   @tbd currently ignores the Comment in Text-Comment alternatives.
  566
  567list_alternatives(Alternatives) :-
  568    maplist(atomic, Alternatives),
  569    !,
  570    length(Alternatives, Count),
  571    maplist(atom_length, Alternatives, Lengths),
  572    max_list(Lengths, Max),
  573    tty_size(_, Cols),
  574    ColW is Max+2,
  575    Columns is max(1, Cols // ColW),
  576    RowCount is (Count+Columns-1)//Columns,
  577    length(Rows, RowCount),
  578    to_matrix(Alternatives, Rows, Rows),
  579    (   RowCount > 11
  580    ->  length(First, 10),
  581        Skipped is RowCount - 10,
  582        append(First, _, Rows),
  583        maplist(write_row(ColW), First),
  584        format(user_error, '... skipped ~D rows~n', [Skipped])
  585    ;   maplist(write_row(ColW), Rows)
  586    ).
  587list_alternatives(Alternatives) :-
  588    maplist(complete_text, Alternatives, AltText),
  589    list_alternatives(AltText).
  590
  591to_matrix([], _, Rows) :-
  592    !,
  593    maplist(close_list, Rows).
  594to_matrix([H|T], [RH|RT], Rows) :-
  595    !,
  596    add_list(RH, H),
  597    to_matrix(T, RT, Rows).
  598to_matrix(List, [], Rows) :-
  599    to_matrix(List, Rows, Rows).
  600
  601add_list(Var, Elem) :-
  602    var(Var), !,
  603    Var = [Elem|_].
  604add_list([_|T], Elem) :-
  605    add_list(T, Elem).
  606
  607close_list(List) :-
  608    append(List, [], _),
  609    !.
  610
  611write_row(ColW, Row) :-
  612    length(Row, Columns),
  613    make_format(Columns, ColW, Format),
  614    format(user_error, Format, Row).
  615
  616make_format(N, ColW, Format) :-
  617    format(string(PerCol), '~~w~~t~~~d+', [ColW]),
  618    Front is N - 1,
  619    length(LF, Front),
  620    maplist(=(PerCol), LF),
  621    append(LF, ['~w~n'], Parts),
  622    atomics_to_string(Parts, Format).
  623
  624
  625		 /*******************************
  626		 *             SEARCH		*
  627		 *******************************/
  628
  629%!  isearch_history(+Input, +Char, -Continue) is det.
  630%
  631%   Incremental search through the history.  The behavior is based
  632%   on GNU readline.
  633
  634isearch_history(Input, _Char, Continue) :-
  635    el_line(Input, line(Before, After)),
  636    string_concat(Before, After, Current),
  637    string_length(Current, Len),
  638    search_print('', "", Current),
  639    search(Input, "", Current, 1, Line),
  640    el_deletestr(Input, Len),
  641    el_insertstr(Input, Line),
  642    Continue = redisplay.
  643
  644search(Input, For, Current, Nth, Line) :-
  645    el_getc(Input, Next),
  646    Next \== -1,
  647    !,
  648    search(Next, Input, For, Current, Nth, Line).
  649search(_Input, _For, _Current, _Nth, "").
  650
  651search(7, _Input, _, Current, _, Current) :-    % C-g: abort
  652    !,
  653    clear_line.
  654search(18, Input, For, Current, Nth, Line) :-   % C-r: search previous
  655    !,
  656    N2 is Nth+1,
  657    search_(Input, For, Current, N2, Line).
  658search(19, Input, For, Current, Nth, Line) :-   % C-s: search next
  659    !,
  660    N2 is max(1,Nth-1),
  661    search_(Input, For, Current, N2, Line).
  662search(127, Input, For, Current, _Nth, Line) :- % DEL/BS: shorten search
  663    sub_string(For, 0, _, 1, For1),
  664    !,
  665    search_(Input, For1, Current, 1, Line).
  666search(Char, Input, For, Current, Nth, Line) :-
  667    code_type(Char, cntrl),
  668    !,
  669    search_end(Input, For, Current, Nth, Line),
  670    el_push(Input, Char).
  671search(Char, Input, For, Current, _Nth, Line) :-
  672    format(string(For1), '~w~c', [For,Char]),
  673    search_(Input, For1, Current, 1, Line).
  674
  675search_(Input, For1, Current, Nth, Line) :-
  676    (   find_in_history(Input, For1, Current, Nth, Candidate)
  677    ->  search_print('', For1, Candidate)
  678    ;   search_print('failed ', For1, Current)
  679    ),
  680    search(Input, For1, Current, Nth, Line).
  681
  682search_end(Input, For, Current, Nth, Line) :-
  683    (   find_in_history(Input, For, Current, Nth, Line)
  684    ->  true
  685    ;   Line = Current
  686    ),
  687    clear_line.
  688
  689find_in_history(_, "", Current, _, Current) :-
  690    !.
  691find_in_history(Input, For, _, Nth, Line) :-
  692    el_history_events(Input, History),
  693    call_nth(( member(_N-Line, History),
  694               sub_string(Line, _, _, _, For)
  695             ),
  696             Nth),
  697    !.
  698
  699search_print(State, Search, Current) :-
  700    format(user_error, '\r(~wreverse-i-search)`~w\': ~w\e[0K',
  701           [State, Search, Current]).
  702
  703clear_line :-
  704    format(user_error, '\r\e[0K', []).
  705
  706
  707                /*******************************
  708                *         PASTE QUOTED         *
  709                *******************************/
  710
  711:- meta_predicate
  712    with_quote_flags(+,+,0).  713
  714add_paste_quoted(Input) :-
  715    current_prolog_flag(gui, true),
  716    !,
  717    el_addfn(Input, paste_quoted, 'Paste as quoted atom', paste_quoted),
  718    el_bind(Input, ["^Y",  paste_quoted]).
  719add_paste_quoted(_).
  720
  721%!  paste_quoted(+Input, +Char, -Continue) is det.
  722%
  723%   Paste the selection as quoted Prolog value.   The quoting type
  724%   depends on the quote before the caret.  If there is no quote
  725%   before the caret we paste as an atom.
  726
  727paste_quoted(Input, _Char, Continue) :-
  728    clipboard_content(String),
  729    quote_text(Input, String, Quoted),
  730    el_insertstr(Input, Quoted),
  731    Continue = refresh.
  732
  733quote_text(Input, String, Value) :-
  734    el_line(Input, line(Before, _After)),
  735    (   sub_string(Before, _, 1, 0, Quote)
  736    ->  true
  737    ;   Quote = "'"
  738    ),
  739    quote_text(Input, Quote, String, Value).
  740
  741quote_text(Input, "'", Text, Quoted) =>
  742    format(string(Quoted), '~q', [Text]),
  743    el_deletestr(Input, 1).
  744quote_text(Input, "\"", Text, Quoted) =>
  745    atom_string(Text, String),
  746    with_quote_flags(
  747        string, codes,
  748        format(string(Quoted), '~q', [String])),
  749    el_deletestr(Input, 1).
  750quote_text(Input, "`", Text, Quoted) =>
  751    atom_string(Text, String),
  752    with_quote_flags(
  753        codes, string,
  754        format(string(Quoted), '~q', [String])),
  755    el_deletestr(Input, 1).
  756quote_text(_, _, Text, Quoted) =>
  757    format(string(Quoted), '~q', [Text]).
  758
  759with_quote_flags(Double, Back, Goal) :-
  760    current_prolog_flag(double_quotes, ODouble),
  761    current_prolog_flag(back_quotes, OBack),
  762    setup_call_cleanup(
  763        ( set_prolog_flag(double_quotes, Double),
  764          set_prolog_flag(back_quotes, Back) ),
  765        Goal,
  766        ( set_prolog_flag(double_quotes, ODouble),
  767          set_prolog_flag(back_quotes, OBack) )).
  768
  769clipboard_content(Text) :-
  770    current_prolog_flag(gui, true),
  771    !,
  772    autoload_call(in_pce_thread_sync(
  773                      autoload_call(
  774                          get(@(display), paste, primary, string(Text))))).
  775clipboard_content("")