View source with raw 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/4,                          % +Prog, +Input, +Output, +Error
   40            el_wrapped/1,                       % +Input
   41            el_unwrap/1,			% +Input
   42
   43            el_source/2,			% +Input, +File
   44            el_bind/2,                          % +Input, +Args
   45            el_addfn/4,                         % +Input, +Name, +Help, :Goal
   46            el_cursor/2,                        % +Input, +Move
   47            el_line/2,                          % +Input, -Line
   48            el_insertstr/2,                     % +Input, +Text
   49            el_deletestr/2,                     % +Input, +Count
   50
   51            el_history/2,                       % +Input, ?Action
   52            el_history_events/2,                % +Input, -Events
   53            el_add_history/2,                   % +Input, +Line
   54            el_write_history/2,                 % +Input, +FileName
   55            el_read_history/2                   % +Input, +FileName
   56          ]).   57:- autoload(library(apply),[maplist/2,maplist/3]).   58:- autoload(library(lists),[reverse/2,max_list/2,append/3,member/2]).   59:- autoload(library(solution_sequences),[call_nth/2]).   60
   61:- use_foreign_library(foreign(libedit4pl)).   62
   63:- initialization el_wrap_if_ok.   64
   65:- meta_predicate
   66    el_addfn(+,+,+,3).   67
   68:- multifile
   69    el_setup/1,                         % +Input
   70    prolog:complete_input/4.

BSD libedit based command line editing

This library wraps the BSD libedit command line editor. The binding provides a high level API to enable command line editing on the Prolog user streams and low level predicates to apply the library on other streams and program the library. */

   81el_wrap_if_ok :-
   82    \+ current_prolog_flag(console_menu_version, qt),
   83    \+ current_prolog_flag(readline, readline),
   84    stream_property(user_input, tty(true)),
   85    !,
   86    el_wrap.
   87el_wrap_if_ok.
 el_wrap is det
Enable using editline on the standard user streams if user_input is connected to a terminal. This is the high level predicate used for most purposes. The remainder of the library interface deals with low level predicates that allows for applying and programming libedit in non-standard situations.

The library is registered with ProgName set to swipl (see el_wrap/4).

  100el_wrap :-
  101    el_wrapped(user_input),
  102    !.
  103el_wrap :-
  104    stream_property(user_input, tty(true)), !,
  105    el_wrap(swipl, user_input, user_output, user_error),
  106    add_prolog_commands(user_input),
  107    forall(el_setup(user_input), true).
  108el_wrap.
  109
  110add_prolog_commands(Input) :-
  111    el_addfn(Input, complete, 'Complete atoms and files', complete),
  112    el_addfn(Input, show_completions, 'List completions', show_completions),
  113    el_addfn(Input, electric, 'Indicate matching bracket', electric),
  114    el_addfn(Input, isearch_history, 'Incremental search in history',
  115             isearch_history),
  116    el_bind(Input, ["^I",  complete]),
  117    el_bind(Input, ["^[?", show_completions]),
  118    el_bind(Input, ["^R",  isearch_history]),
  119    bind_electric(Input),
  120    add_paste_quoted(Input),
  121    el_source(Input, _).
 el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream) is det
Enable editline on the stream-triple <In,Out,Error>. From this moment on In is a handle to the command line editor.
Arguments:
ProgName- is the name of the invoking program, used when reading the editrc(5) file to determine which settings to use.
 el_setup(+In:stream) is nondet
This hooks is called as forall(el_setup(Input), true) after the input stream has been wrapped, the default Prolog commands have been added and the default user setup file has been sourced using el_source/2. It can be used to define and bind additional commands.
 el_wrapped(+In:stream) is semidet
True if In is a stream wrapped by el_wrap/3.
 el_unwrap(+In:stream) is det
Remove the libedit wrapper for In and the related output and error streams.
bug
- The wrapper creates FILE* handles that cannot be closed and thus wrapping and unwrapping implies a (modest) memory leak.
 el_source(+In:stream, +File) is det
Initialise editline by reading the contents of File. If File is unbound try $HOME/.editrc
 el_bind(+In:stream, +Args) is det
Invoke the libedit bind command with the given arguments. The example below lists the current key bindings.
?- el_bind(user_input, ['-a']).

The predicate el_bind/2 is typically used to bind commands defined using el_addfn/4. Note that the C proxy function has only the last character of the command as context to find the Prolog binding. This implies we cannot both bind e.g., "^[?" *and "?" to a Prolog function.

See also
- editrc(5) for more information.
 el_addfn(+Input:stream, +Command, +Help, :Goal) is det
Add a new command to the command line editor associated with Input. Command is the name of the command, Help is the help string printed with e.g. bind -a (see el_bind/2) and Goal is called of the associated key-binding is activated. Goal is called as
call(:Goal, +Input, +Char, -Continue)

where Input is the input stream providing access to the editor, Char the activating character and Continue must be instantated with one of the known continuation codes as defined by libedit: norm, newline, eof, arghack, refresh, refresh_beep, cursor, redisplay, error or fatal. In addition, the following Continue code is provided.

electric(Move, TimeOut, Continue)
Show electric caret at Move positions to the left of the normal cursor positions for the given TimeOut. Continue as defined by the Continue value.

The registered Goal typically used el_line/2 to fetch the input line and el_cursor/2, el_insertstr/2 and/or el_deletestr/2 to manipulate the input line.

Normally el_bind/2 is used to associate the defined command with a keyboard sequence.

See also
- el_set(3) EL_ADDFN for details.
 el_line(+Input:stream, -Line) is det
Fetch the currently buffered input line. Line is a term line(Before, After), where Before is a string holding the text before the cursor and After is a string holding the text after the cursor.
 el_cursor(+Input:stream, +Move:integer) is det
Move the cursor Move character forwards (positive) or backwards (negative).
 el_insertstr(+Input:stream, +Text) is det
Insert Text at the cursor.
 el_deletestr(+Input:stream, +Count) is det
Delete Count characters before the cursor.
 el_history(+In:stream, ?Action) is det
Perform a generic action on the history. This provides an incomplete interface to history() from libedit. Supported actions are:
clear
Clear the history.
setsize(+Integer)
Set size of history to size elements.
setunique(+Boolean)
Set flag that adjacent identical event strings should not be entered into the history.
 el_history_events(+In:stream, -Events:list(pair)) is det
Unify Events with a list of pairs of the form Num-String, where Num is the event number and String is the associated string without terminating newline.
 el_add_history(+In:stream, +Line:text) is det
Add a line to the command line history.
 el_read_history(+In:stream, +File:file) is det
Read the history saved using el_write_history/2.
Arguments:
File- is a file specification for absolute_file_name/3.
 el_write_history(+In:stream, +File:file) is det
Save editline history to File. The history may be reloaded using el_read_history/2.
Arguments:
File- is a file specification for absolute_file_name/3.
  259:- multifile
  260    prolog:history/2.  261
  262prolog:history(Input, add(Line)) :-
  263    el_add_history(Input, Line).
  264prolog:history(Input, load(File)) :-
  265    el_read_history(Input, File).
  266prolog:history(Input, save(File)) :-
  267    el_write_history(Input, File).
  268prolog:history(Input, load) :-
  269    el_history_events(Input, Events),
  270    '$reverse'(Events, RevEvents),
  271    forall('$member'(Ev, RevEvents),
  272           add_event(Ev)).
  273
  274add_event(Num-String) :-
  275    remove_dot(String, String1),
  276    '$save_history_event'(Num-String1).
  277
  278remove_dot(String0, String) :-
  279    string_concat(String, ".", String0),
  280    !.
  281remove_dot(String, String).
  282
  283
  284		 /*******************************
  285		 *        ELECTRIC CARET	*
  286		 *******************************/
 bind_electric(+Input) is det
Bind known close statements for electric input
  292bind_electric(Input) :-
  293    forall(bracket(_Open, Close), bind_code(Input, Close, electric)),
  294    forall(quote(Close), bind_code(Input, Close, electric)).
  295
  296bind_code(Input, Code, Command) :-
  297    string_codes(Key, [Code]),
  298    el_bind(Input, [Key, Command]).
 electric(+Input, +Char, -Continue) is det
  303electric(Input, Char, Continue) :-
  304    string_codes(Str, [Char]),
  305    el_insertstr(Input, Str),
  306    el_line(Input, line(Before, _)),
  307    (   string_codes(Before, Codes),
  308        nesting(Codes, 0, Nesting),
  309        reverse(Nesting, [Close|RevNesting])
  310    ->  (   Close = open(_,_)                   % open quote
  311        ->  Continue = refresh
  312        ;   matching_open(RevNesting, Close, _, Index)
  313        ->  string_length(Before, Len),         % Proper match
  314            Move is Index-Len,
  315            Continue = electric(Move, 500, refresh)
  316        ;   Continue = refresh_beep             % Not properly nested
  317        )
  318    ;   Continue = refresh_beep
  319    ).
  320
  321matching_open_index(String, Index) :-
  322    string_codes(String, Codes),
  323    nesting(Codes, 0, Nesting),
  324    reverse(Nesting, [Close|RevNesting]),
  325    matching_open(RevNesting, Close, _, Index).
  326
  327matching_open([Open|Rest], Close, Rest, Index) :-
  328    Open = open(Index,_),
  329    match(Open, Close),
  330    !.
  331matching_open([Close1|Rest1], Close, Rest, Index) :-
  332    Close1 = close(_,_),
  333    matching_open(Rest1, Close1, Rest2, _),
  334    matching_open(Rest2, Close, Rest, Index).
  335
  336match(open(_,Open),close(_,Close)) :-
  337    (   bracket(Open, Close)
  338    ->  true
  339    ;   Open == Close,
  340        quote(Open)
  341    ).
  342
  343bracket(0'(, 0')).
  344bracket(0'[, 0']).
  345bracket(0'{, 0'}).
  346
  347quote(0'\').
  348quote(0'\").
  349quote(0'\`).
  350
  351nesting([], _, []).
  352nesting([H|T], I, Nesting) :-
  353    (   bracket(H, _Close)
  354    ->  Nesting = [open(I,H)|Nest]
  355    ;   bracket(_Open, H)
  356    ->  Nesting = [close(I,H)|Nest]
  357    ),
  358    !,
  359    I2 is I+1,
  360    nesting(T, I2, Nest).
  361nesting([0'0, 0'\'|T], I, Nesting) :-
  362    !,
  363    phrase(skip_code, T, T1),
  364    difflist_length(T, T1, Len),
  365    I2 is I+Len+2,
  366    nesting(T1, I2, Nesting).
  367nesting([H|T], I, Nesting) :-
  368    quote(H),
  369    !,
  370    (   phrase(skip_quoted(H), T, T1)
  371    ->  difflist_length(T, T1, Len),
  372        I2 is I+Len+1,
  373        Nesting = [open(I,H),close(I2,H)|Nest],
  374        nesting(T1, I2, Nest)
  375    ;   Nesting = [open(I,H)]                   % Open quote
  376    ).
  377nesting([_|T], I, Nesting) :-
  378    I2 is I+1,
  379    nesting(T, I2, Nesting).
  380
  381difflist_length(List, Tail, Len) :-
  382    difflist_length(List, Tail, 0, Len).
  383
  384difflist_length(List, Tail, Len0, Len) :-
  385    List == Tail,
  386    !,
  387    Len = Len0.
  388difflist_length([_|List], Tail, Len0, Len) :-
  389    Len1 is Len0+1,
  390    difflist_length(List, Tail, Len1, Len).
  391
  392skip_quoted(H) -->
  393    [H],
  394    !.
  395skip_quoted(H) -->
  396    "\\", [H],
  397    !,
  398    skip_quoted(H).
  399skip_quoted(H) -->
  400    [_],
  401    skip_quoted(H).
  402
  403skip_code -->
  404    "\\", [_],
  405    !.
  406skip_code -->
  407    [_].
  408
  409
  410		 /*******************************
  411		 *           COMPLETION		*
  412		 *******************************/
 complete(+Input, +Char, -Continue) is det
Implementation of the registered complete editline function. The predicate is called with three arguments, the first being the input stream used to access the libedit functions and the second the activating character. The last argument tells libedit what to do. Consult el_set(3), EL_ADDFN for details.
  423:- dynamic
  424    last_complete/2.  425
  426complete(Input, _Char, Continue) :-
  427    el_line(Input, line(Before, After)),
  428    ensure_input_completion,
  429    prolog:complete_input(Before, After, Delete, Completions),
  430    (   Completions = [One]
  431    ->  string_length(Delete, Len),
  432        el_deletestr(Input, Len),
  433        complete_text(One, Text),
  434        el_insertstr(Input, Text),
  435        Continue = refresh
  436    ;   Completions == []
  437    ->  Continue = refresh_beep
  438    ;   get_time(Now),
  439        retract(last_complete(TLast, Before)),
  440        Now - TLast < 2
  441    ->  nl(user_error),
  442        list_alternatives(Completions),
  443        Continue = redisplay
  444    ;   retractall(last_complete(_,_)),
  445        get_time(Now),
  446        asserta(last_complete(Now, Before)),
  447        common_competion(Completions, Extend),
  448        (   Delete == Extend
  449        ->  Continue = refresh_beep
  450        ;   string_length(Delete, Len),
  451            el_deletestr(Input, Len),
  452            el_insertstr(Input, Extend),
  453            Continue = refresh
  454        )
  455    ).
  456
  457:- dynamic
  458    input_completion_loaded/0.  459
  460ensure_input_completion :-
  461    input_completion_loaded,
  462    !.
  463ensure_input_completion :-
  464    predicate_property(prolog:complete_input(_,_,_,_),
  465                       number_of_clauses(N)),
  466    N > 0,
  467    !.
  468ensure_input_completion :-
  469    exists_source(library(console_input)),
  470    !,
  471    use_module(library(console_input), []),
  472    asserta(input_completion_loaded).
  473ensure_input_completion.
 show_completions(+Input, +Char, -Continue) is det
Editline command to show possible completions.
  480show_completions(Input, _Char, Continue) :-
  481    el_line(Input, line(Before, After)),
  482    prolog:complete_input(Before, After, _Delete, Completions),
  483    nl(user_error),
  484    list_alternatives(Completions),
  485    Continue = redisplay.
  486
  487complete_text(Text-_Comment, Text) :- !.
  488complete_text(Text, Text).
 common_competion(+Alternatives, -Common) is det
True when Common is the common prefix of all candidate Alternatives.
  494common_competion(Alternatives, Common) :-
  495    maplist(atomic, Alternatives),
  496    !,
  497    common_prefix(Alternatives, Common).
  498common_competion(Alternatives, Common) :-
  499    maplist(complete_text, Alternatives, AltText),
  500    !,
  501    common_prefix(AltText, Common).
 common_prefix(+Atoms, -Common) is det
True when Common is the common prefix of all Atoms.
  507common_prefix([A1|T], Common) :-
  508    common_prefix_(T, A1, Common).
  509
  510common_prefix_([], Common, Common).
  511common_prefix_([H|T], Common0, Common) :-
  512    common_prefix(H, Common0, Common1),
  513    common_prefix_(T, Common1, Common).
 common_prefix(+A1, +A2, -Prefix:string) is det
True when Prefix is the common prefix of the atoms A1 and A2
  519common_prefix(A1, A2, Prefix) :-
  520    sub_atom(A1, 0, _, _, A2),
  521    !,
  522    Prefix = A2.
  523common_prefix(A1, A2, Prefix) :-
  524    sub_atom(A2, 0, _, _, A1),
  525    !,
  526    Prefix = A1.
  527common_prefix(A1, A2, Prefix) :-
  528    atom_codes(A1, C1),
  529    atom_codes(A2, C2),
  530    list_common_prefix(C1, C2, C),
  531    string_codes(Prefix, C).
  532
  533list_common_prefix([H|T0], [H|T1], [H|T]) :-
  534    !,
  535    list_common_prefix(T0, T1, T).
  536list_common_prefix(_, _, []).
 list_alternatives(+Alternatives)
List possible completions at the current point.
To be done
- currently ignores the Comment in Text-Comment alternatives.
  546list_alternatives(Alternatives) :-
  547    maplist(atomic, Alternatives),
  548    !,
  549    length(Alternatives, Count),
  550    maplist(atom_length, Alternatives, Lengths),
  551    max_list(Lengths, Max),
  552    tty_size(_, Cols),
  553    ColW is Max+2,
  554    Columns is max(1, Cols // ColW),
  555    RowCount is (Count+Columns-1)//Columns,
  556    length(Rows, RowCount),
  557    to_matrix(Alternatives, Rows, Rows),
  558    (   RowCount > 11
  559    ->  length(First, 10),
  560        Skipped is RowCount - 10,
  561        append(First, _, Rows),
  562        maplist(write_row(ColW), First),
  563        format(user_error, '... skipped ~D rows~n', [Skipped])
  564    ;   maplist(write_row(ColW), Rows)
  565    ).
  566list_alternatives(Alternatives) :-
  567    maplist(complete_text, Alternatives, AltText),
  568    list_alternatives(AltText).
  569
  570to_matrix([], _, Rows) :-
  571    !,
  572    maplist(close_list, Rows).
  573to_matrix([H|T], [RH|RT], Rows) :-
  574    !,
  575    add_list(RH, H),
  576    to_matrix(T, RT, Rows).
  577to_matrix(List, [], Rows) :-
  578    to_matrix(List, Rows, Rows).
  579
  580add_list(Var, Elem) :-
  581    var(Var), !,
  582    Var = [Elem|_].
  583add_list([_|T], Elem) :-
  584    add_list(T, Elem).
  585
  586close_list(List) :-
  587    append(List, [], _),
  588    !.
  589
  590write_row(ColW, Row) :-
  591    length(Row, Columns),
  592    make_format(Columns, ColW, Format),
  593    format(user_error, Format, Row).
  594
  595make_format(N, ColW, Format) :-
  596    format(string(PerCol), '~~w~~t~~~d+', [ColW]),
  597    Front is N - 1,
  598    length(LF, Front),
  599    maplist(=(PerCol), LF),
  600    append(LF, ['~w~n'], Parts),
  601    atomics_to_string(Parts, Format).
  602
  603
  604		 /*******************************
  605		 *             SEARCH		*
  606		 *******************************/
 isearch_history(+Input, +Char, -Continue) is det
Incremental search through the history. The behavior is based on GNU readline.
  613isearch_history(Input, _Char, Continue) :-
  614    el_line(Input, line(Before, After)),
  615    string_concat(Before, After, Current),
  616    string_length(Current, Len),
  617    search_print('', "", Current),
  618    search(Input, "", Current, 1, Line),
  619    el_deletestr(Input, Len),
  620    el_insertstr(Input, Line),
  621    Continue = redisplay.
  622
  623search(Input, For, Current, Nth, Line) :-
  624    el_getc(Input, Next),
  625    Next \== -1,
  626    !,
  627    search(Next, Input, For, Current, Nth, Line).
  628search(_Input, _For, _Current, _Nth, "").
  629
  630search(7, _Input, _, Current, _, Current) :-    % C-g: abort
  631    !,
  632    clear_line.
  633search(18, Input, For, Current, Nth, Line) :-   % C-r: search previous
  634    !,
  635    N2 is Nth+1,
  636    search_(Input, For, Current, N2, Line).
  637search(19, Input, For, Current, Nth, Line) :-   % C-s: search next
  638    !,
  639    N2 is max(1,Nth-1),
  640    search_(Input, For, Current, N2, Line).
  641search(127, Input, For, Current, _Nth, Line) :- % DEL/BS: shorten search
  642    sub_string(For, 0, _, 1, For1),
  643    !,
  644    search_(Input, For1, Current, 1, Line).
  645search(Char, Input, For, Current, Nth, Line) :-
  646    code_type(Char, cntrl),
  647    !,
  648    search_end(Input, For, Current, Nth, Line),
  649    el_push(Input, Char).
  650search(Char, Input, For, Current, _Nth, Line) :-
  651    format(string(For1), '~w~c', [For,Char]),
  652    search_(Input, For1, Current, 1, Line).
  653
  654search_(Input, For1, Current, Nth, Line) :-
  655    (   find_in_history(Input, For1, Current, Nth, Candidate)
  656    ->  search_print('', For1, Candidate)
  657    ;   search_print('failed ', For1, Current)
  658    ),
  659    search(Input, For1, Current, Nth, Line).
  660
  661search_end(Input, For, Current, Nth, Line) :-
  662    (   find_in_history(Input, For, Current, Nth, Line)
  663    ->  true
  664    ;   Line = Current
  665    ),
  666    clear_line.
  667
  668find_in_history(_, "", Current, _, Current) :-
  669    !.
  670find_in_history(Input, For, _, Nth, Line) :-
  671    el_history_events(Input, History),
  672    call_nth(( member(_N-Line, History),
  673               sub_string(Line, _, _, _, For)
  674             ),
  675             Nth),
  676    !.
  677
  678search_print(State, Search, Current) :-
  679    format(user_error, '\r(~wreverse-i-search)`~w\': ~w\e[0K',
  680           [State, Search, Current]).
  681
  682clear_line :-
  683    format(user_error, '\r\e[0K', []).
  684
  685
  686                /*******************************
  687                *         PASTE QUOTED         *
  688                *******************************/
  689
  690:- meta_predicate
  691    with_quote_flags(+,+,0).  692
  693add_paste_quoted(Input) :-
  694    current_prolog_flag(gui, true),
  695    !,
  696    el_addfn(Input, paste_quoted, 'Paste as quoted atom', paste_quoted),
  697    el_bind(Input, ["^Y",  paste_quoted]).
  698add_paste_quoted(_).
 paste_quoted(+Input, +Char, -Continue) is det
Paste the selection as quoted Prolog value. The quoting type depends on the quote before the caret. If there is no quote before the caret we paste as an atom.
  706paste_quoted(Input, _Char, Continue) :-
  707    clipboard_content(String),
  708    quote_text(Input, String, Quoted),
  709    el_insertstr(Input, Quoted),
  710    Continue = refresh.
  711
  712quote_text(Input, String, Value) :-
  713    el_line(Input, line(Before, _After)),
  714    (   sub_string(Before, _, 1, 0, Quote)
  715    ->  true
  716    ;   Quote = "'"
  717    ),
  718    quote_text(Input, Quote, String, Value).
  719
  720quote_text(Input, "'", Text, Quoted) =>
  721    format(string(Quoted), '~q', [Text]),
  722    el_deletestr(Input, 1).
  723quote_text(Input, "\"", Text, Quoted) =>
  724    atom_string(Text, String),
  725    with_quote_flags(
  726        string, codes,
  727        format(string(Quoted), '~q', [String])),
  728    el_deletestr(Input, 1).
  729quote_text(Input, "`", Text, Quoted) =>
  730    atom_string(Text, String),
  731    with_quote_flags(
  732        codes, string,
  733        format(string(Quoted), '~q', [String])),
  734    el_deletestr(Input, 1).
  735quote_text(_, _, Text, Quoted) =>
  736    format(string(Quoted), '~q', [Text]).
  737
  738with_quote_flags(Double, Back, Goal) :-
  739    current_prolog_flag(double_quotes, ODouble),
  740    current_prolog_flag(back_quotes, OBack),
  741    setup_call_cleanup(
  742        ( set_prolog_flag(double_quotes, Double),
  743          set_prolog_flag(back_quotes, Back) ),
  744        Goal,
  745        ( set_prolog_flag(double_quotes, ODouble),
  746          set_prolog_flag(back_quotes, OBack) )).
  747
  748clipboard_content(Text) :-
  749    (   current_predicate(get/3)
  750    ->  true
  751    ;   current_prolog_flag(gui, true),
  752        use_module(library(pce), [get/3, in_pce_thread_sync/1])
  753    ),
  754    !,
  755    in_pce_thread_sync(get(@(display), paste, primary, string(Text))).
  756clipboard_content("")