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)  1998-2015, University of Amsterdam
    7                              VU University 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(prolog_edit,
   37          [ edit/1,                     % +Spec
   38            edit/0
   39          ]).   40:- autoload(library(lists),[member/2,append/3,nth1/3]).   41:- autoload(library(make),[make/0]).   42:- if(exists_source(library(pce))).   43:- autoload(library(pce),[in_pce_thread/1]).   44:- autoload(library(pce_emacs),[emacs/1]).   45:- endif.   46:- autoload(library(prolog_breakpoints),[breakpoint_property/2]).   47
   48
   49:- set_prolog_flag(generate_debug_info, false).   50
   51/** <module> Editor interface
   52
   53This module implements the generic editor  interface. It consists of two
   54extensible parts with little  in  between.   The  first  part deals with
   55translating the input into source-location, and the second with starting
   56an editor.
   57*/
   58
   59:- multifile
   60    locate/3,                       % +Partial, -FullSpec, -Location
   61    locate/2,                       % +FullSpec, -Location
   62    select_location/3,              % +Pairs, +Spec, -Location
   63    edit_source/1,                  % +Location
   64    edit_command/2,                 % +Editor, -Command
   65    load/0.                         % provides load-hooks
   66
   67%!  edit(+Spec)
   68%
   69%   Edit indicated object.
   70
   71edit(Spec) :-
   72    notrace(edit_no_trace(Spec)).
   73
   74edit_no_trace(Spec) :-
   75    var(Spec),
   76    !,
   77    throw(error(instantiation_error, _)).
   78edit_no_trace(Spec) :-
   79    load_extensions,
   80    findall(Location-FullSpec,
   81            locate(Spec, FullSpec, Location),
   82            Pairs0),
   83    merge_locations(Pairs0, Pairs),
   84    do_select_location(Pairs, Spec, Location),
   85    do_edit_source(Location).
   86
   87%!  edit
   88%
   89%   Edit associated or script file.  This is the Prolog file opened
   90%   by double-clicking or the file loaded using
   91%
   92%     ==
   93%     % swipl [-s] file.pl
   94%     ==
   95
   96edit :-
   97    current_prolog_flag(associated_file, File),
   98    !,
   99    edit(file(File)).
  100edit :-
  101    '$cmd_option_val'(script_file, OsFiles),
  102    OsFiles = [OsFile],
  103    !,
  104    prolog_to_os_filename(File, OsFile),
  105    edit(file(File)).
  106edit :-
  107    throw(error(context_error(edit, no_default_file), _)).
  108
  109
  110                 /*******************************
  111                 *            LOCATE            *
  112                 *******************************/
  113
  114%!  locate(+Spec, -FullSpec, -Location)
  115
  116locate(FileSpec:Line, file(Path, line(Line)), [file(Path), line(Line)]) :-
  117    integer(Line), Line >= 1,
  118    ground(FileSpec),                      % so specific; do not try alts
  119    !,
  120    locate(FileSpec, _, [file(Path)]).
  121locate(FileSpec:Line:LinePos,
  122       file(Path, line(Line), linepos(LinePos)),
  123       [file(Path), line(Line), linepos(LinePos)]) :-
  124    integer(Line), Line >= 1,
  125    integer(LinePos), LinePos >= 1,
  126    ground(FileSpec),                      % so specific; do not try alts
  127    !,
  128    locate(FileSpec, _, [file(Path)]).
  129locate(Path, file(Path), [file(Path)]) :-
  130    atom(Path),
  131    exists_file(Path),
  132    \+ exists_directory(Path).
  133locate(Pattern, file(Path), [file(Path)]) :-
  134    atom(Pattern),
  135    catch(expand_file_name(Pattern, Files), _, fail),
  136    member(Path, Files),
  137    exists_file(Path),
  138    \+ exists_directory(Path).
  139locate(FileBase, file(File), [file(File)]) :-
  140    atom(FileBase),
  141    absolute_file_name(FileBase,
  142                       [ file_type(prolog),
  143                         access(read),
  144                         file_errors(fail)
  145                       ],
  146                       File),
  147    \+ exists_directory(File).
  148locate(FileSpec, file(File), [file(File)]) :-
  149    catch(absolute_file_name(FileSpec,
  150                             [ file_type(prolog),
  151                               access(read),
  152                               file_errors(fail)
  153                             ],
  154                             File),
  155          _, fail).
  156locate(FileBase, source_file(Path), [file(Path)]) :-
  157    atom(FileBase),
  158    source_file(Path),
  159    file_base_name(Path, File),
  160    (   File == FileBase
  161    ->  true
  162    ;   file_name_extension(FileBase, _, File)
  163    ).
  164locate(FileBase, include_file(Path), [file(Path)]) :-
  165    atom(FileBase),
  166    setof(Path, include_file(Path), Paths),
  167    member(Path, Paths),
  168    file_base_name(Path, File),
  169    (   File == FileBase
  170    ->  true
  171    ;   file_name_extension(FileBase, _, File)
  172    ).
  173locate(Name, FullSpec, Location) :-
  174    atom(Name),
  175    locate(Name/_, FullSpec, Location).
  176locate(Name/Arity, Module:Name/Arity, Location) :-
  177    locate(Module:Name/Arity, Location).
  178locate(Name//DCGArity, FullSpec, Location) :-
  179    (   integer(DCGArity)
  180    ->  Arity is DCGArity+2,
  181        locate(Name/Arity, FullSpec, Location)
  182    ;   locate(Name/_, FullSpec, Location) % demand arity >= 2
  183    ).
  184locate(Name/Arity, library(File), [file(PlPath)]) :-
  185    atom(Name),
  186    '$in_library'(Name, Arity, Path),
  187    (   absolute_file_name(library(.),
  188                           [ file_type(directory),
  189                             solutions(all)
  190                           ],
  191                           Dir),
  192        atom_concat(Dir, File0, Path),
  193        atom_concat(/, File, File0)
  194    ->  absolute_file_name(Path,
  195                           [ file_type(prolog),
  196                             access(read),
  197                             file_errors(fail)
  198                           ],
  199                           PlPath)
  200    ;   fail
  201    ).
  202locate(Module:Name, Module:Name/Arity, Location) :-
  203    locate(Module:Name/Arity, Location).
  204locate(Module:Head, Module:Name/Arity, Location) :-
  205    callable(Head),
  206    \+ ( Head = (PName/_),
  207         atom(PName)
  208       ),
  209    functor(Head, Name, Arity),
  210    locate(Module:Name/Arity, Location).
  211locate(Spec, module(Spec), Location) :-
  212    locate(module(Spec), Location).
  213locate(Spec, Spec, Location) :-
  214    locate(Spec, Location).
  215
  216include_file(Path) :-
  217    source_file_property(Path, included_in(_,_)).
  218
  219
  220%!  locate(+Spec, -Location)
  221%
  222%   Locate object from the specified location.
  223
  224locate(file(File, line(Line)), [file(File), line(Line)]).
  225locate(file(File), [file(File)]).
  226locate(Module:Name/Arity, [file(File), line(Line)]) :-
  227    (   atom(Name), integer(Arity)
  228    ->  functor(Head, Name, Arity)
  229    ;   Head = _                    % leave unbound
  230    ),
  231    (   (   var(Module)
  232        ;   var(Name)
  233        )
  234    ->  NonImport = true
  235    ;   NonImport = false
  236    ),
  237    current_predicate(Name, Module:Head),
  238    \+ (   NonImport == true,
  239           Module \== system,
  240           predicate_property(Module:Head, imported_from(_))
  241       ),
  242    functor(Head, Name, Arity),     % bind arity
  243    predicate_property(Module:Head, file(File)),
  244    predicate_property(Module:Head, line_count(Line)).
  245locate(module(Module), [file(Path)|Rest]) :-
  246    atom(Module),
  247    module_property(Module, file(Path)),
  248    (   module_property(Module, line_count(Line))
  249    ->  Rest = [line(Line)]
  250    ;   Rest = []
  251    ).
  252locate(breakpoint(Id), Location) :-
  253    integer(Id),
  254    breakpoint_property(Id, clause(Ref)),
  255    (   breakpoint_property(Id, file(File)),
  256        breakpoint_property(Id, line_count(Line))
  257    ->  Location = [file(File),line(Line)]
  258    ;   locate(clause(Ref), Location)
  259    ).
  260locate(clause(Ref), [file(File), line(Line)]) :-
  261    clause_property(Ref, file(File)),
  262    clause_property(Ref, line_count(Line)).
  263locate(clause(Ref, _PC), [file(File), line(Line)]) :- % TBD: use clause
  264    clause_property(Ref, file(File)),
  265    clause_property(Ref, line_count(Line)).
  266
  267
  268                 /*******************************
  269                 *             EDIT             *
  270                 *******************************/
  271
  272%!  do_edit_source(+Location)
  273%
  274%   Actually call the editor to edit Location, a list of Name(Value)
  275%   that contains file(File) and may contain line(Line). First the
  276%   multifile hook edit_source/1 is called. If this fails the system
  277%   checks for XPCE and the prolog-flag editor. If the latter is
  278%   built_in or pce_emacs, it will start PceEmacs.
  279%
  280%   Finally, it will get the editor to use from the prolog-flag
  281%   editor and use edit_command/2 to determine how this editor
  282%   should be called.
  283
  284do_edit_source(Location) :-             % hook
  285    edit_source(Location),
  286    !.
  287:- if(current_predicate(emacs/1)).  288do_edit_source(Location) :-             % PceEmacs
  289    current_prolog_flag(editor, Editor),
  290    pceemacs(Editor),
  291    current_prolog_flag(gui, true),
  292    !,
  293    memberchk(file(File), Location),
  294    (   memberchk(line(Line), Location)
  295    ->  (   memberchk(linepos(LinePos), Location)
  296        ->  Pos = (File:Line:LinePos)
  297        ;   Pos = (File:Line)
  298        )
  299    ;   Pos = File
  300    ),
  301    in_pce_thread(emacs(Pos)).
  302:- endif.  303do_edit_source(Location) :-             % External editor
  304    external_edit_command(Location, Command),
  305    print_message(informational, edit(waiting_for_editor)),
  306    (   catch(shell(Command), E,
  307              (print_message(warning, E),
  308               fail))
  309    ->  print_message(informational, edit(make)),
  310        make
  311    ;   print_message(informational, edit(canceled))
  312    ).
  313
  314external_edit_command(Location, Command) :-
  315    memberchk(file(File), Location),
  316    memberchk(line(Line), Location),
  317    editor(Editor),
  318    file_base_name(Editor, EditorFile),
  319    file_name_extension(Base, _, EditorFile),
  320    edit_command(Base, Cmd),
  321    prolog_to_os_filename(File, OsFile),
  322    atom_codes(Cmd, S0),
  323    substitute('%e', Editor, S0, S1),
  324    substitute('%f', OsFile, S1, S2),
  325    substitute('%d', Line,   S2, S),
  326    !,
  327    atom_codes(Command, S).
  328external_edit_command(Location, Command) :-
  329    memberchk(file(File), Location),
  330    editor(Editor),
  331    file_base_name(Editor, EditorFile),
  332    file_name_extension(Base, _, EditorFile),
  333    edit_command(Base, Cmd),
  334    prolog_to_os_filename(File, OsFile),
  335    atom_codes(Cmd, S0),
  336    substitute('%e', Editor, S0, S1),
  337    substitute('%f', OsFile, S1, S),
  338    \+ substitute('%d', 1, S, _),
  339    !,
  340    atom_codes(Command, S).
  341external_edit_command(Location, Command) :-
  342    memberchk(file(File), Location),
  343    editor(Editor),
  344    atomic_list_concat(['"', Editor, '" "', File, '"'], Command).
  345
  346pceemacs(pce_emacs).
  347pceemacs(built_in).
  348
  349%!  editor(-Editor)
  350%
  351%   Determine the external editor to run.
  352
  353editor(Editor) :-                       % $EDITOR
  354    current_prolog_flag(editor, Editor),
  355    (   sub_atom(Editor, 0, _, _, $)
  356    ->  sub_atom(Editor, 1, _, 0, Var),
  357        catch(getenv(Var, Editor), _, fail), !
  358    ;   Editor == default
  359    ->  catch(getenv('EDITOR', Editor), _, fail), !
  360    ;   \+ pceemacs(Editor)
  361    ->  !
  362    ).
  363editor(Editor) :-                       % User defaults
  364    getenv('EDITOR', Editor),
  365    !.
  366editor(vi) :-                           % Platform defaults
  367    current_prolog_flag(unix, true),
  368    !.
  369editor(notepad) :-
  370    current_prolog_flag(windows, true),
  371    !.
  372editor(_) :-                            % No luck
  373    throw(error(existence_error(editor), _)).
  374
  375%!  edit_command(+Editor, -Command)
  376%
  377%   This predicate should specify the shell-command called to invoke
  378%   the user's editor. The following substitutions will be made:
  379%
  380%           | %e | Path name of the editor            |
  381%           | %f | Path name of the file to be edited |
  382%           | %d | Line number of the target          |
  383
  384
  385edit_command(vi,          '%e +%d \'%f\'').
  386edit_command(vi,          '%e \'%f\'').
  387edit_command(emacs,       '%e +%d \'%f\'').
  388edit_command(emacs,       '%e \'%f\'').
  389edit_command(notepad,     '"%e" "%f"').
  390edit_command(wordpad,     '"%e" "%f"').
  391edit_command(uedit32,     '%e "%f/%d/0"').      % ultraedit (www.ultraedit.com)
  392edit_command(jedit,       '%e -wait \'%f\' +line:%d').
  393edit_command(jedit,       '%e -wait \'%f\'').
  394edit_command(edit,        '%e %f:%d').          % PceEmacs client script
  395edit_command(edit,        '%e %f').
  396
  397edit_command(emacsclient, Command) :- edit_command(emacs, Command).
  398edit_command(vim,         Command) :- edit_command(vi,    Command).
  399edit_command(nvim,        Command) :- edit_command(vi,    Command).
  400
  401substitute(FromAtom, ToAtom, Old, New) :-
  402    atom_codes(FromAtom, From),
  403    (   atom(ToAtom)
  404    ->  atom_codes(ToAtom, To)
  405    ;   number_codes(ToAtom, To)
  406    ),
  407    append(Pre, S0, Old),
  408    append(From, Post, S0) ->
  409    append(Pre, To, S1),
  410    append(S1, Post, New),
  411    !.
  412substitute(_, _, Old, Old).
  413
  414
  415                 /*******************************
  416                 *            SELECT            *
  417                 *******************************/
  418
  419merge_locations(Pairs0, Pairs) :-
  420    keysort(Pairs0, Pairs1),
  421    merge_locations2(Pairs1, Pairs).
  422
  423merge_locations2([], []).
  424merge_locations2([H0|T0], [H|T]) :-
  425    remove_same_location(H0, H, T0, T1),
  426    merge_locations2(T1, T).
  427
  428remove_same_location(Pair0, H, [Pair1|T0], L) :-
  429    merge_locations(Pair0, Pair1, Pair2),
  430    !,
  431    remove_same_location(Pair2, H, T0, L).
  432remove_same_location(H, H, L, L).
  433
  434merge_locations(Loc1-Spec1, Loc2-Spec2, Loc-Spec) :-
  435    same_location(Loc1, Loc2, Loc),
  436    !,
  437    (   merge_specs(Spec1, Spec2, Spec)
  438    ;   merge_specs(Spec2, Spec1, Spec)
  439    ;   Spec = Spec1
  440    ),
  441    !.
  442merge_locations([file(X)]-_, Loc-Spec, Loc-Spec) :-
  443    memberchk(file(X), Loc),
  444    memberchk(line(_), Loc).
  445
  446same_location(L, L, L).
  447same_location([file(F1)], [file(F2)], [file(F)]) :-
  448    best_same_file(F1, F2, F).
  449same_location([file(F1),line(L)], [file(F2)], [file(F),line(L)]) :-
  450    best_same_file(F1, F2, F).
  451same_location([file(F1)], [file(F2),line(L)], [file(F),line(L)]) :-
  452    best_same_file(F1, F2, F).
  453
  454best_same_file(F1, F2, F) :-
  455    catch(same_file(F1, F2), _, fail),
  456    !,
  457    atom_length(F1, L1),
  458    atom_length(F2, L2),
  459    (   L1 < L2
  460    ->  F = F1
  461    ;   F = F2
  462    ).
  463
  464merge_specs(source_file(Path), _, source_file(Path)).
  465
  466%!  select_location(+Pairs, +UserSpec, -Location)
  467
  468do_select_location(Pairs, Spec, Location) :-
  469    select_location(Pairs, Spec, Location),                % HOOK
  470    !,
  471    Location \== [].
  472do_select_location([], Spec, _) :-
  473    !,
  474    print_message(warning, edit(not_found(Spec))),
  475    fail.
  476do_select_location([Location-_Spec], _, Location) :- !.
  477do_select_location(Pairs, _, Location) :-
  478    print_message(help, edit(select)),
  479    list_pairs(Pairs, 0, N),
  480    print_message(help, edit(prompt_select)),
  481    read_number(N, I),
  482    nth1(I, Pairs, Location-_Spec),
  483    !.
  484
  485list_pairs([], N, N).
  486list_pairs([H|T], N0, N) :-
  487    NN is N0 + 1,
  488    list_pair(H, NN),
  489    list_pairs(T, NN, N).
  490
  491list_pair(Pair, N) :-
  492    print_message(help, edit(target(Pair, N))).
  493
  494
  495read_number(Max, X) :-
  496    Max < 10,
  497    !,
  498    get_single_char(C),
  499    put_code(user_error, C),
  500    between(0'0, 0'9, C),
  501    X is C - 0'0.
  502read_number(_, X) :-
  503    read_line(Chars),
  504    name(X, Chars),
  505    integer(X).
  506
  507read_line(Chars) :-
  508    get0(user_input, C0),
  509    read_line(C0, Chars).
  510
  511read_line(10, []) :- !.
  512read_line(-1, []) :- !.
  513read_line(C, [C|T]) :-
  514    get0(user_input, C1),
  515    read_line(C1, T).
  516
  517
  518                 /*******************************
  519                 *             MESSAGES         *
  520                 *******************************/
  521
  522:- multifile
  523    prolog:message/3.  524
  525prolog:message(edit(not_found(Spec))) -->
  526    [ 'Cannot find anything to edit from "~p"'-[Spec] ],
  527    (   { atom(Spec) }
  528    ->  [ nl, '    Use edit(file(~q)) to create a new file'-[Spec] ]
  529    ;   []
  530    ).
  531prolog:message(edit(select)) -->
  532    [ 'Please select item to edit:', nl, nl ].
  533prolog:message(edit(prompt_select)) -->
  534    [ nl, 'Your choice? ', flush ].
  535prolog:message(edit(target(Location-Spec, N))) -->
  536    [ '~t~d~3| '-[N]],
  537    edit_specifier(Spec),
  538    [ '~t~32|' ],
  539    edit_location(Location).
  540prolog:message(edit(waiting_for_editor)) -->
  541    [ 'Waiting for editor ... ', flush ].
  542prolog:message(edit(make)) -->
  543    [ 'Running make to reload modified files' ].
  544prolog:message(edit(canceled)) -->
  545    [ 'Editor returned failure; skipped make/0 to reload files' ].
  546
  547edit_specifier(Module:Name/Arity) -->
  548    !,
  549    [ '~w:~w/~w'-[Module, Name, Arity] ].
  550edit_specifier(file(_Path)) -->
  551    !,
  552    [ '<file>' ].
  553edit_specifier(source_file(_Path)) -->
  554    !,
  555    [ '<loaded file>' ].
  556edit_specifier(include_file(_Path)) -->
  557    !,
  558    [ '<included file>' ].
  559edit_specifier(Term) -->
  560    [ '~p'-[Term] ].
  561
  562edit_location(Location) -->
  563    { memberchk(file(File), Location),
  564      memberchk(line(Line), Location),
  565      short_filename(File, Spec)
  566    },
  567    !,
  568    [ '~q:~d'-[Spec, Line] ].
  569edit_location(Location) -->
  570    { memberchk(file(File), Location),
  571      short_filename(File, Spec)
  572    },
  573    !,
  574    [ '~q'-[Spec] ].
  575
  576short_filename(Path, Spec) :-
  577    absolute_file_name('', Here),
  578    atom_concat(Here, Local0, Path),
  579    !,
  580    remove_leading_slash(Local0, Spec).
  581short_filename(Path, Spec) :-
  582    findall(LenAlias, aliased_path(Path, LenAlias), Keyed),
  583    keysort(Keyed, [_-Spec|_]).
  584short_filename(Path, Path).
  585
  586aliased_path(Path, Len-Spec) :-
  587    setof(Alias, file_alias_path(Alias), Aliases),
  588    member(Alias, Aliases),
  589    Alias \== autoload,             % confusing and covered by something else
  590    Term =.. [Alias, '.'],
  591    absolute_file_name(Term,
  592                       [ file_type(directory),
  593                         file_errors(fail),
  594                         solutions(all)
  595                       ], Prefix),
  596    atom_concat(Prefix, Local0, Path),
  597    remove_leading_slash(Local0, Local),
  598    atom_length(Local, Len),
  599    Spec =.. [Alias, Local].
  600
  601file_alias_path(Alias) :-
  602    user:file_search_path(Alias, _).
  603
  604remove_leading_slash(Path, Local) :-
  605    atom_concat(/, Local, Path),
  606    !.
  607remove_leading_slash(Path, Path).
  608
  609
  610                 /*******************************
  611                 *        LOAD EXTENSIONS       *
  612                 *******************************/
  613
  614load_extensions :-
  615    load,
  616    fail.
  617load_extensions.
  618
  619:- load_extensions.