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
  60:- use_foreign_library(foreign(libedit4pl)).
  61
  62:- meta_predicate
  63    el_addfn(+,+,+,3).
  64
  65:- multifile
  66    el_setup/1.                         % +Input
  67
  68
  69/** <module> BSD libedit based command line editing
  70
  71This library wraps the BSD  libedit   command  line  editor. The binding
  72provides a high level API to enable   command line editing on the Prolog
  73user streams and low level predicates  to   apply  the  library on other
  74streams and program the library.
  75*/
  76
  77:- initialization
  78    el_wrap.
  79
  80%!  el_wrap is det.
  81%
  82%   Enable using editline on the standard   user streams if `user_input`
  83%   is connected to a terminal. This is   the  high level predicate used
  84%   for most purposes. The remainder of the library interface deals with
  85%   low level predicates  that  allows   for  applying  and  programming
  86%   libedit in non-standard situations.
  87%
  88%   The library is registered  with  _ProgName_   set  to  =swipl=  (see
  89%   el_wrap/4).
  90
  91el_wrap :-
  92    el_wrapped(user_input),
  93    !.
  94el_wrap :-
  95    stream_property(user_input, tty(true)), !,
  96    el_wrap(swipl, user_input, user_output, user_error),
  97    add_prolog_commands(user_input),
  98    forall(el_setup(user_input), true).
  99el_wrap.
 100
 101add_prolog_commands(Input) :-
 102    el_addfn(Input, complete, 'Complete atoms and files', complete),
 103    el_addfn(Input, show_completions, 'List completions', show_completions),
 104    el_addfn(Input, electric, 'Indicate matching bracket', electric),
 105    el_bind(Input, ["^I",  complete]),
 106    el_bind(Input, ["^[?", show_completions]),
 107    bind_electric(Input),
 108    el_source(Input, _).
 109
 110%!  el_wrap(+ProgName:atom, +In:stream, +Out:stream, +Error:stream) is det.
 111%
 112%   Enable editline on  the  stream-triple   <In,Out,Error>.  From  this
 113%   moment on In is a handle to the command line editor.
 114%
 115%   @arg ProgName is the name of the invoking program, used when reading
 116%   the editrc(5) file to determine which settings to use.
 117
 118%!  el_setup(+In:stream) is nondet.
 119%
 120%   This hooks is called as   forall(el_setup(Input),  true) _after_ the
 121%   input stream has been wrapped, the default Prolog commands have been
 122%   added and the  default  user  setup   file  has  been  sourced using
 123%   el_source/2. It can be used to define and bind additional commands.
 124
 125%!  el_wrapped(+In:stream) is semidet.
 126%
 127%   True if In is a stream wrapped by el_wrap/3.
 128
 129%!  el_unwrap(+In:stream) is det.
 130%
 131%   Remove the libedit wrapper for In and   the related output and error
 132%   streams.
 133%
 134%   @bug The wrapper creates =|FILE*|= handles that cannot be closed and
 135%   thus wrapping and unwrapping implies a (modest) memory leak.
 136
 137%!  el_source(+In:stream, +File) is det.
 138%
 139%   Initialise editline by reading the contents of File.  If File is
 140%   unbound try =|$HOME/.editrc|=
 141
 142
 143%!  el_bind(+In:stream, +Args) is det.
 144%
 145%   Invoke the libedit `bind` command  with   the  given  arguments. The
 146%   example below lists the current key bindings.
 147%
 148%   ```
 149%   ?- el_bind(user_input, ['-a']).
 150%   ```
 151%
 152%   The predicate el_bind/2 is typically used   to bind commands defined
 153%   using el_addfn/4. Note that the C proxy   function has only the last
 154%   character of the command as context to find the Prolog binding. This
 155%   implies we cannot both  bind  e.g.,  "^[?"  *and  "?"  to  a  Prolog
 156%   function.
 157%
 158%   @see editrc(5) for more information.
 159
 160%!  el_addfn(+Input:stream, +Command, +Help, :Goal) is det.
 161%
 162%   Add a new command to the command  line editor associated with Input.
 163%   Command is the name of the command,  Help is the help string printed
 164%   with e.g. =|bind -a|= (see el_bind/2)  and   Goal  is  called of the
 165%   associated key-binding is activated.  Goal is called as
 166%
 167%       call(:Goal, +Input, +Char, -Continue)
 168%
 169%   where Input is the input stream providing access to the editor, Char
 170%   the activating character and Continue must   be instantated with one
 171%   of the known continuation  codes  as   defined  by  libedit: `norm`,
 172%   `newline`, `eof`, `arghack`, `refresh`,   `refresh_beep`,  `cursor`,
 173%   `redisplay`, `error` or `fatal`. In addition, the following Continue
 174%   code is provided.
 175%
 176%     * electric(Move, TimeOut, Continue)
 177%     Show _electric caret_ at Move positions to the left of the normal
 178%     cursor positions for the given TimeOut.  Continue as defined by
 179%     the Continue value.
 180%
 181%   The registered Goal typically used el_line/2 to fetch the input line
 182%   and el_cursor/2, el_insertstr/2 and/or  el_deletestr/2 to manipulate
 183%   the input line.
 184%
 185%   Normally el_bind/2 is used to associate   the defined command with a
 186%   keyboard sequence.
 187%
 188%   @see el_set(3) =EL_ADDFN= for details.
 189
 190%!  el_line(+Input:stream, -Line) is det.
 191%
 192%   Fetch the currently buffered input line. Line is a term line(Before,
 193%   After), where `Before` is  a  string   holding  the  text before the
 194%   cursor and `After` is a string holding the text after the cursor.
 195
 196%!  el_cursor(+Input:stream, +Move:integer) is det.
 197%
 198%   Move the cursor Move  character   forwards  (positive)  or backwards
 199%   (negative).
 200
 201%!  el_insertstr(+Input:stream, +Text) is det.
 202%
 203%   Insert Text at the cursor.
 204
 205%!  el_deletestr(+Input:stream, +Count) is det.
 206%
 207%   Delete Count characters before the cursor.
 208
 209%!  el_history(+In:stream, ?Action) is det.
 210%
 211%   Perform a generic action on the history. This provides an incomplete
 212%   interface to history() from libedit.  Supported actions are:
 213%
 214%     * clear
 215%     Clear the history.
 216%     * setsize(+Integer)
 217%     Set size of history to size elements.
 218%     * setunique(+Boolean)
 219%     Set flag that adjacent identical event strings should not be
 220%     entered into the history.
 221
 222%!  el_history_events(+In:stream, -Events:list(pair)) is det.
 223%
 224%   Unify Events with a list of pairs   of  the form `Num-String`, where
 225%   `Num` is the event number  and   `String`  is  the associated string
 226%   without terminating newline.
 227
 228%!  el_add_history(+In:stream, +Line:text) is det.
 229%
 230%   Add a line to the command line history.
 231
 232%!  el_read_history(+In:stream, +File:file) is det.
 233%
 234%   Read the history saved using el_write_history/2.
 235%
 236%   @arg File is a file specification for absolute_file_name/3.
 237
 238%!  el_write_history(+In:stream, +File:file) is det.
 239%
 240%   Save editline history to File.  The   history  may be reloaded using
 241%   el_read_history/2.
 242%
 243%   @arg File is a file specification for absolute_file_name/3.
 244
 245
 246:- multifile
 247    prolog:history/2.
 248
 249prolog:history(Input, add(Line)) :-
 250    el_add_history(Input, Line).
 251prolog:history(Input, load(File)) :-
 252    el_read_history(Input, File).
 253prolog:history(Input, save(File)) :-
 254    el_write_history(Input, File).
 255prolog:history(Input, load) :-
 256    el_history_events(Input, Events),
 257    '$reverse'(Events, RevEvents),
 258    forall('$member'(Ev, RevEvents),
 259           add_event(Ev)).
 260
 261add_event(Num-String) :-
 262    remove_dot(String, String1),
 263    '$save_history_event'(Num-String1).
 264
 265remove_dot(String0, String) :-
 266    string_concat(String, ".", String0),
 267    !.
 268remove_dot(String, String).
 269
 270
 271		 /*******************************
 272		 *        ELECTRIC CARET	*
 273		 *******************************/
 274
 275%!  bind_electric(+Input) is det.
 276%
 277%   Bind known close statements for electric input
 278
 279bind_electric(Input) :-
 280    forall(bracket(_Open, Close), bind_code(Input, Close, electric)),
 281    forall(quote(Close), bind_code(Input, Close, electric)).
 282
 283bind_code(Input, Code, Command) :-
 284    string_codes(Key, [Code]),
 285    el_bind(Input, [Key, Command]).
 286
 287
 288%!  electric(+Input, +Char, -Continue) is det.
 289
 290electric(Input, Char, Continue) :-
 291    string_codes(Str, [Char]),
 292    el_insertstr(Input, Str),
 293    el_line(Input, line(Before, _)),
 294    (   string_codes(Before, Codes),
 295        nesting(Codes, 0, Nesting),
 296        reverse(Nesting, [Close|RevNesting])
 297    ->  (   Close = open(_,_)                   % open quote
 298        ->  Continue = refresh
 299        ;   matching_open(RevNesting, Close, _, Index)
 300        ->  string_length(Before, Len),         % Proper match
 301            Move is Index-Len,
 302            Continue = electric(Move, 500, refresh)
 303        ;   Continue = refresh_beep             % Not properly nested
 304        )
 305    ;   Continue = refresh_beep
 306    ).
 307
 308matching_open_index(String, Index) :-
 309    string_codes(String, Codes),
 310    nesting(Codes, 0, Nesting),
 311    reverse(Nesting, [Close|RevNesting]),
 312    matching_open(RevNesting, Close, _, Index).
 313
 314matching_open([Open|Rest], Close, Rest, Index) :-
 315    Open = open(Index,_),
 316    match(Open, Close),
 317    !.
 318matching_open([Close1|Rest1], Close, Rest, Index) :-
 319    Close1 = close(_,_),
 320    matching_open(Rest1, Close1, Rest2, _),
 321    matching_open(Rest2, Close, Rest, Index).
 322
 323match(open(_,Open),close(_,Close)) :-
 324    (   bracket(Open, Close)
 325    ->  true
 326    ;   Open == Close,
 327        quote(Open)
 328    ).
 329
 330bracket(0'(, 0')).
 331bracket(0'[, 0']).
 332bracket(0'{, 0'}).
 333
 334quote(0'\').
 335quote(0'\").
 336quote(0'\`).
 337
 338nesting([], _, []).
 339nesting([H|T], I, Nesting) :-
 340    (   bracket(H, _Close)
 341    ->  Nesting = [open(I,H)|Nest]
 342    ;   bracket(_Open, H)
 343    ->  Nesting = [close(I,H)|Nest]
 344    ),
 345    !,
 346    I2 is I+1,
 347    nesting(T, I2, Nest).
 348nesting([0'0, 0'\'|T], I, Nesting) :-
 349    !,
 350    phrase(skip_code, T, T1),
 351    difflist_length(T, T1, Len),
 352    I2 is I+Len+2,
 353    nesting(T1, I2, Nesting).
 354nesting([H|T], I, Nesting) :-
 355    quote(H),
 356    !,
 357    (   phrase(skip_quoted(H), T, T1)
 358    ->  difflist_length(T, T1, Len),
 359        I2 is I+Len+1,
 360        Nesting = [open(I,H),close(I2,H)|Nest],
 361        nesting(T1, I2, Nest)
 362    ;   Nesting = [open(I,H)]                   % Open quote
 363    ).
 364nesting([_|T], I, Nesting) :-
 365    I2 is I+1,
 366    nesting(T, I2, Nesting).
 367
 368difflist_length(List, Tail, Len) :-
 369    difflist_length(List, Tail, 0, Len).
 370
 371difflist_length(List, Tail, Len0, Len) :-
 372    List == Tail,
 373    !,
 374    Len = Len0.
 375difflist_length([_|List], Tail, Len0, Len) :-
 376    Len1 is Len0+1,
 377    difflist_length(List, Tail, Len1, Len).
 378
 379skip_quoted(H) -->
 380    [H],
 381    !.
 382skip_quoted(H) -->
 383    "\\", [H],
 384    !,
 385    skip_quoted(H).
 386skip_quoted(H) -->
 387    [_],
 388    skip_quoted(H).
 389
 390skip_code -->
 391    "\\", [_],
 392    !.
 393skip_code -->
 394    [_].
 395
 396
 397		 /*******************************
 398		 *           COMPLETION		*
 399		 *******************************/
 400
 401%!  complete(+Input, +Char, -Continue) is det.
 402%
 403%   Implementation of the registered `complete`   editline function. The
 404%   predicate is called with three arguments,  the first being the input
 405%   stream used to access  the  libedit   functions  and  the second the
 406%   activating character. The last argument tells   libedit  what to do.
 407%   Consult el_set(3), =EL_ADDFN= for details.
 408
 409
 410:- dynamic
 411    last_complete/2.
 412
 413complete(Input, _Char, Continue) :-
 414    el_line(Input, line(Before, After)),
 415    prolog:complete_input(Before, After, Delete, Completions),
 416    (   Completions = [One]
 417    ->  string_length(Delete, Len),
 418        el_deletestr(Input, Len),
 419        complete_text(One, Text),
 420        el_insertstr(Input, Text),
 421        Continue = refresh
 422    ;   Completions == []
 423    ->  Continue = refresh_beep
 424    ;   get_time(Now),
 425        retract(last_complete(TLast, Before)),
 426        Now - TLast < 2
 427    ->  nl(user_error),
 428        list_alternatives(Completions),
 429        Continue = redisplay
 430    ;   retractall(last_complete(_,_)),
 431        get_time(Now),
 432        asserta(last_complete(Now, Before)),
 433        common_competion(Completions, Extend),
 434        (   Delete == Extend
 435        ->  Continue = refresh_beep
 436        ;   string_length(Delete, Len),
 437            el_deletestr(Input, Len),
 438            el_insertstr(Input, Extend),
 439            Continue = refresh
 440        )
 441    ).
 442
 443%!  show_completions(+Input, +Char, -Continue) is det.
 444%
 445%   Editline command to show possible completions.
 446
 447show_completions(Input, _Char, Continue) :-
 448    el_line(Input, line(Before, After)),
 449    prolog:complete_input(Before, After, _Delete, Completions),
 450    nl(user_error),
 451    list_alternatives(Completions),
 452    Continue = redisplay.
 453
 454complete_text(Text-_Comment, Text) :- !.
 455complete_text(Text, Text).
 456
 457%!  common_competion(+Alternatives, -Common) is det.
 458%
 459%   True when Common is the common prefix of all candidate Alternatives.
 460
 461common_competion(Alternatives, Common) :-
 462    maplist(atomic, Alternatives),
 463    !,
 464    common_prefix(Alternatives, Common).
 465common_competion(Alternatives, Common) :-
 466    maplist(complete_text, Alternatives, AltText),
 467    !,
 468    common_prefix(AltText, Common).
 469
 470%!  common_prefix(+Atoms, -Common) is det.
 471%
 472%   True when Common is the common prefix of all Atoms.
 473
 474common_prefix([A1|T], Common) :-
 475    common_prefix_(T, A1, Common).
 476
 477common_prefix_([], Common, Common).
 478common_prefix_([H|T], Common0, Common) :-
 479    common_prefix(H, Common0, Common1),
 480    common_prefix_(T, Common1, Common).
 481
 482%!  common_prefix(+A1, +A2, -Prefix:string) is det.
 483%
 484%   True when Prefix is the common prefix of the atoms A1 and A2
 485
 486common_prefix(A1, A2, Prefix) :-
 487    sub_atom(A1, 0, _, _, A2),
 488    !,
 489    Prefix = A2.
 490common_prefix(A1, A2, Prefix) :-
 491    sub_atom(A2, 0, _, _, A1),
 492    !,
 493    Prefix = A1.
 494common_prefix(A1, A2, Prefix) :-
 495    atom_codes(A1, C1),
 496    atom_codes(A2, C2),
 497    list_common_prefix(C1, C2, C),
 498    string_codes(Prefix, C).
 499
 500list_common_prefix([H|T0], [H|T1], [H|T]) :-
 501    !,
 502    list_common_prefix(T0, T1, T).
 503list_common_prefix(_, _, []).
 504
 505
 506
 507%!  list_alternatives(+Alternatives)
 508%
 509%   List possible completions at the current point.
 510%
 511%   @tbd currently ignores the Comment in Text-Comment alternatives.
 512
 513list_alternatives(Alternatives) :-
 514    maplist(atomic, Alternatives),
 515    !,
 516    length(Alternatives, Count),
 517    maplist(atom_length, Alternatives, Lengths),
 518    max_list(Lengths, Max),
 519    tty_size(_, Cols),
 520    ColW is Max+2,
 521    Columns is Cols // ColW,
 522    RowCount is (Count+Columns-1)//Columns,
 523    length(Rows, RowCount),
 524    to_matrix(Alternatives, Rows, Rows),
 525    (   RowCount > 11
 526    ->  length(First, 10),
 527        Skipped is RowCount - 10,
 528        append(First, _, Rows),
 529        maplist(write_row(ColW), First),
 530        format(user_error, '... skipped ~D rows~n', [Skipped])
 531    ;   maplist(write_row(ColW), Rows)
 532    ).
 533list_alternatives(Alternatives) :-
 534    maplist(complete_text, Alternatives, AltText),
 535    list_alternatives(AltText).
 536
 537to_matrix([], _, Rows) :-
 538    !,
 539    maplist(close_list, Rows).
 540to_matrix([H|T], [RH|RT], Rows) :-
 541    !,
 542    add_list(RH, H),
 543    to_matrix(T, RT, Rows).
 544to_matrix(List, [], Rows) :-
 545    to_matrix(List, Rows, Rows).
 546
 547add_list(Var, Elem) :-
 548    var(Var), !,
 549    Var = [Elem|_].
 550add_list([_|T], Elem) :-
 551    add_list(T, Elem).
 552
 553close_list(List) :-
 554    append(List, [], _),
 555    !.
 556
 557write_row(ColW, Row) :-
 558    length(Row, Columns),
 559    make_format(Columns, ColW, Format),
 560    format(user_error, Format, Row).
 561
 562make_format(N, ColW, Format) :-
 563    format(string(PerCol), '~~w~~t~~~d+', [ColW]),
 564    Front is N - 1,
 565    length(LF, Front),
 566    maplist(=(PerCol), LF),
 567    append(LF, ['~w~n'], Parts),
 568    atomics_to_string(Parts, Format).