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, VU University Amsterdam
    7                         CWI Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(editline,
   37          [ el_wrap/0,				% wrap user_input, etc.
   38            el_wrap/4,                          % +Prog, +Input, +Output, +Error
   39            el_wrapped/1,                       % +Input
   40            el_unwrap/1,			% +Input
   41
   42            el_source/2,			% +Input, +File
   43            el_bind/2,                          % +Input, +Args
   44            el_addfn/4,                         % +Input, +Name, +Help, :Goal
   45            el_cursor/2,                        % +Input, +Move
   46            el_line/2,                          % +Input, -Line
   47            el_insertstr/2,                     % +Input, +Text
   48            el_deletestr/2,                     % +Input, +Count
   49
   50            el_history/2,                       % +Input, ?Action
   51            el_history_events/2,                % +Input, -Events
   52            el_add_history/2,                   % +Input, +Line
   53            el_write_history/2,                 % +Input, +FileName
   54            el_read_history/2                   % +Input, +FileName
   55          ]).   56:- use_module(library(console_input)).   57:- use_module(library(apply)).   58:- use_module(library(lists)).   59
   60editline_ok :-
   61    \+ current_prolog_flag(console_menu_version, qt),
   62    \+ current_prolog_flag(readline, readline),
   63    stream_property(user_input, tty(true)).
   64
   65:- use_foreign_library(foreign(libedit4pl)).   66
   67:- if(editline_ok).   68:- initialization el_wrap.   69:- endif.   70
   71:- meta_predicate
   72    el_addfn(+,+,+,3).   73
   74:- multifile
   75    el_setup/1.                         % +Input

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. */

 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).

   97el_wrap :-
   98    el_wrapped(user_input),
   99    !.
  100el_wrap :-
  101    stream_property(user_input, tty(true)), !,
  102    el_wrap(swipl, user_input, user_output, user_error),
  103    add_prolog_commands(user_input),
  104    forall(el_setup(user_input), true).
  105el_wrap.
  106
  107add_prolog_commands(Input) :-
  108    el_addfn(Input, complete, 'Complete atoms and files', complete),
  109    el_addfn(Input, show_completions, 'List completions', show_completions),
  110    el_addfn(Input, electric, 'Indicate matching bracket', electric),
  111    el_bind(Input, ["^I",  complete]),
  112    el_bind(Input, ["^[?", show_completions]),
  113    bind_electric(Input),
  114    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.
  252:- multifile
  253    prolog:history/2.  254
  255prolog:history(Input, add(Line)) :-
  256    el_add_history(Input, Line).
  257prolog:history(Input, load(File)) :-
  258    el_read_history(Input, File).
  259prolog:history(Input, save(File)) :-
  260    el_write_history(Input, File).
  261prolog:history(Input, load) :-
  262    el_history_events(Input, Events),
  263    '$reverse'(Events, RevEvents),
  264    forall('$member'(Ev, RevEvents),
  265           add_event(Ev)).
  266
  267add_event(Num-String) :-
  268    remove_dot(String, String1),
  269    '$save_history_event'(Num-String1).
  270
  271remove_dot(String0, String) :-
  272    string_concat(String, ".", String0),
  273    !.
  274remove_dot(String, String).
  275
  276
  277		 /*******************************
  278		 *        ELECTRIC CARET	*
  279		 *******************************/
 bind_electric(+Input) is det
Bind known close statements for electric input
  285bind_electric(Input) :-
  286    forall(bracket(_Open, Close), bind_code(Input, Close, electric)),
  287    forall(quote(Close), bind_code(Input, Close, electric)).
  288
  289bind_code(Input, Code, Command) :-
  290    string_codes(Key, [Code]),
  291    el_bind(Input, [Key, Command]).
 electric(+Input, +Char, -Continue) is det
  296electric(Input, Char, Continue) :-
  297    string_codes(Str, [Char]),
  298    el_insertstr(Input, Str),
  299    el_line(Input, line(Before, _)),
  300    (   string_codes(Before, Codes),
  301        nesting(Codes, 0, Nesting),
  302        reverse(Nesting, [Close|RevNesting])
  303    ->  (   Close = open(_,_)                   % open quote
  304        ->  Continue = refresh
  305        ;   matching_open(RevNesting, Close, _, Index)
  306        ->  string_length(Before, Len),         % Proper match
  307            Move is Index-Len,
  308            Continue = electric(Move, 500, refresh)
  309        ;   Continue = refresh_beep             % Not properly nested
  310        )
  311    ;   Continue = refresh_beep
  312    ).
  313
  314matching_open_index(String, Index) :-
  315    string_codes(String, Codes),
  316    nesting(Codes, 0, Nesting),
  317    reverse(Nesting, [Close|RevNesting]),
  318    matching_open(RevNesting, Close, _, Index).
  319
  320matching_open([Open|Rest], Close, Rest, Index) :-
  321    Open = open(Index,_),
  322    match(Open, Close),
  323    !.
  324matching_open([Close1|Rest1], Close, Rest, Index) :-
  325    Close1 = close(_,_),
  326    matching_open(Rest1, Close1, Rest2, _),
  327    matching_open(Rest2, Close, Rest, Index).
  328
  329match(open(_,Open),close(_,Close)) :-
  330    (   bracket(Open, Close)
  331    ->  true
  332    ;   Open == Close,
  333        quote(Open)
  334    ).
  335
  336bracket(0'(, 0')).
  337bracket(0'[, 0']).
  338bracket(0'{, 0'}).
  339
  340quote(0'\').
  341quote(0'\").
  342quote(0'\`).
  343
  344nesting([], _, []).
  345nesting([H|T], I, Nesting) :-
  346    (   bracket(H, _Close)
  347    ->  Nesting = [open(I,H)|Nest]
  348    ;   bracket(_Open, H)
  349    ->  Nesting = [close(I,H)|Nest]
  350    ),
  351    !,
  352    I2 is I+1,
  353    nesting(T, I2, Nest).
  354nesting([0'0, 0'\'|T], I, Nesting) :-
  355    !,
  356    phrase(skip_code, T, T1),
  357    difflist_length(T, T1, Len),
  358    I2 is I+Len+2,
  359    nesting(T1, I2, Nesting).
  360nesting([H|T], I, Nesting) :-
  361    quote(H),
  362    !,
  363    (   phrase(skip_quoted(H), T, T1)
  364    ->  difflist_length(T, T1, Len),
  365        I2 is I+Len+1,
  366        Nesting = [open(I,H),close(I2,H)|Nest],
  367        nesting(T1, I2, Nest)
  368    ;   Nesting = [open(I,H)]                   % Open quote
  369    ).
  370nesting([_|T], I, Nesting) :-
  371    I2 is I+1,
  372    nesting(T, I2, Nesting).
  373
  374difflist_length(List, Tail, Len) :-
  375    difflist_length(List, Tail, 0, Len).
  376
  377difflist_length(List, Tail, Len0, Len) :-
  378    List == Tail,
  379    !,
  380    Len = Len0.
  381difflist_length([_|List], Tail, Len0, Len) :-
  382    Len1 is Len0+1,
  383    difflist_length(List, Tail, Len1, Len).
  384
  385skip_quoted(H) -->
  386    [H],
  387    !.
  388skip_quoted(H) -->
  389    "\\", [H],
  390    !,
  391    skip_quoted(H).
  392skip_quoted(H) -->
  393    [_],
  394    skip_quoted(H).
  395
  396skip_code -->
  397    "\\", [_],
  398    !.
  399skip_code -->
  400    [_].
  401
  402
  403		 /*******************************
  404		 *           COMPLETION		*
  405		 *******************************/
 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.
  416:- dynamic
  417    last_complete/2.  418
  419complete(Input, _Char, Continue) :-
  420    el_line(Input, line(Before, After)),
  421    prolog:complete_input(Before, After, Delete, Completions),
  422    (   Completions = [One]
  423    ->  string_length(Delete, Len),
  424        el_deletestr(Input, Len),
  425        complete_text(One, Text),
  426        el_insertstr(Input, Text),
  427        Continue = refresh
  428    ;   Completions == []
  429    ->  Continue = refresh_beep
  430    ;   get_time(Now),
  431        retract(last_complete(TLast, Before)),
  432        Now - TLast < 2
  433    ->  nl(user_error),
  434        list_alternatives(Completions),
  435        Continue = redisplay
  436    ;   retractall(last_complete(_,_)),
  437        get_time(Now),
  438        asserta(last_complete(Now, Before)),
  439        common_competion(Completions, Extend),
  440        (   Delete == Extend
  441        ->  Continue = refresh_beep
  442        ;   string_length(Delete, Len),
  443            el_deletestr(Input, Len),
  444            el_insertstr(Input, Extend),
  445            Continue = refresh
  446        )
  447    ).
 show_completions(+Input, +Char, -Continue) is det
Editline command to show possible completions.
  453show_completions(Input, _Char, Continue) :-
  454    el_line(Input, line(Before, After)),
  455    prolog:complete_input(Before, After, _Delete, Completions),
  456    nl(user_error),
  457    list_alternatives(Completions),
  458    Continue = redisplay.
  459
  460complete_text(Text-_Comment, Text) :- !.
  461complete_text(Text, Text).
 common_competion(+Alternatives, -Common) is det
True when Common is the common prefix of all candidate Alternatives.
  467common_competion(Alternatives, Common) :-
  468    maplist(atomic, Alternatives),
  469    !,
  470    common_prefix(Alternatives, Common).
  471common_competion(Alternatives, Common) :-
  472    maplist(complete_text, Alternatives, AltText),
  473    !,
  474    common_prefix(AltText, Common).
 common_prefix(+Atoms, -Common) is det
True when Common is the common prefix of all Atoms.
  480common_prefix([A1|T], Common) :-
  481    common_prefix_(T, A1, Common).
  482
  483common_prefix_([], Common, Common).
  484common_prefix_([H|T], Common0, Common) :-
  485    common_prefix(H, Common0, Common1),
  486    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
  492common_prefix(A1, A2, Prefix) :-
  493    sub_atom(A1, 0, _, _, A2),
  494    !,
  495    Prefix = A2.
  496common_prefix(A1, A2, Prefix) :-
  497    sub_atom(A2, 0, _, _, A1),
  498    !,
  499    Prefix = A1.
  500common_prefix(A1, A2, Prefix) :-
  501    atom_codes(A1, C1),
  502    atom_codes(A2, C2),
  503    list_common_prefix(C1, C2, C),
  504    string_codes(Prefix, C).
  505
  506list_common_prefix([H|T0], [H|T1], [H|T]) :-
  507    !,
  508    list_common_prefix(T0, T1, T).
  509list_common_prefix(_, _, []).
 list_alternatives(+Alternatives)
List possible completions at the current point.
To be done
- currently ignores the Comment in Text-Comment alternatives.
  519list_alternatives(Alternatives) :-
  520    maplist(atomic, Alternatives),
  521    !,
  522    length(Alternatives, Count),
  523    maplist(atom_length, Alternatives, Lengths),
  524    max_list(Lengths, Max),
  525    tty_size(_, Cols),
  526    ColW is Max+2,
  527    Columns is max(1, Cols // ColW),
  528    RowCount is (Count+Columns-1)//Columns,
  529    length(Rows, RowCount),
  530    to_matrix(Alternatives, Rows, Rows),
  531    (   RowCount > 11
  532    ->  length(First, 10),
  533        Skipped is RowCount - 10,
  534        append(First, _, Rows),
  535        maplist(write_row(ColW), First),
  536        format(user_error, '... skipped ~D rows~n', [Skipped])
  537    ;   maplist(write_row(ColW), Rows)
  538    ).
  539list_alternatives(Alternatives) :-
  540    maplist(complete_text, Alternatives, AltText),
  541    list_alternatives(AltText).
  542
  543to_matrix([], _, Rows) :-
  544    !,
  545    maplist(close_list, Rows).
  546to_matrix([H|T], [RH|RT], Rows) :-
  547    !,
  548    add_list(RH, H),
  549    to_matrix(T, RT, Rows).
  550to_matrix(List, [], Rows) :-
  551    to_matrix(List, Rows, Rows).
  552
  553add_list(Var, Elem) :-
  554    var(Var), !,
  555    Var = [Elem|_].
  556add_list([_|T], Elem) :-
  557    add_list(T, Elem).
  558
  559close_list(List) :-
  560    append(List, [], _),
  561    !.
  562
  563write_row(ColW, Row) :-
  564    length(Row, Columns),
  565    make_format(Columns, ColW, Format),
  566    format(user_error, Format, Row).
  567
  568make_format(N, ColW, Format) :-
  569    format(string(PerCol), '~~w~~t~~~d+', [ColW]),
  570    Front is N - 1,
  571    length(LF, Front),
  572    maplist(=(PerCol), LF),
  573    append(LF, ['~w~n'], Parts),
  574    atomics_to_string(Parts, Format)