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)  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:- autoload(library(pce),[in_pce_thread/1]).   43:- autoload(library(pce_emacs),[emacs/1]).   44:- autoload(library(prolog_breakpoints),[breakpoint_property/2]).   45
   46
   47:- set_prolog_flag(generate_debug_info, false).

Editor interface

This module implements the generic editor interface. It consists of two extensible parts with little in between. The first part deals with translating the input into source-location, and the second with starting an editor. */

   57:- multifile
   58    locate/3,                       % +Partial, -FullSpec, -Location
   59    locate/2,                       % +FullSpec, -Location
   60    select_location/3,              % +Pairs, +Spec, -Location
   61    edit_source/1,                  % +Location
   62    edit_command/2,                 % +Editor, -Command
   63    load/0.                         % provides load-hooks
 edit(+Spec)
Edit indicated object.
   69edit(Spec) :-
   70    notrace(edit_no_trace(Spec)).
   71
   72edit_no_trace(Spec) :-
   73    var(Spec),
   74    !,
   75    throw(error(instantiation_error, _)).
   76edit_no_trace(Spec) :-
   77    load_extensions,
   78    findall(Location-FullSpec,
   79            locate(Spec, FullSpec, Location),
   80            Pairs0),
   81    merge_locations(Pairs0, Pairs),
   82    do_select_location(Pairs, Spec, Location),
   83    do_edit_source(Location).
 edit
Edit associated or script file. This is the Prolog file opened by double-clicking or the file loaded using
% swipl [-s] file.pl
   94edit :-
   95    current_prolog_flag(associated_file, File),
   96    !,
   97    edit(file(File)).
   98edit :-
   99    '$cmd_option_val'(script_file, OsFiles),
  100    OsFiles = [OsFile],
  101    !,
  102    prolog_to_os_filename(File, OsFile),
  103    edit(file(File)).
  104edit :-
  105    throw(error(context_error(edit, no_default_file), _)).
  106
  107
  108                 /*******************************
  109                 *            LOCATE            *
  110                 *******************************/
 locate(+Spec, -FullSpec, -Location)
  114locate(FileSpec:Line, file(Path, line(Line)), [file(Path), line(Line)]) :-
  115    integer(Line), Line >= 1,
  116    ground(FileSpec),                      % so specific; do not try alts
  117    !,
  118    locate(FileSpec, _, [file(Path)]).
  119locate(FileSpec:Line:LinePos,
  120       file(Path, line(Line), linepos(LinePos)),
  121       [file(Path), line(Line), linepos(LinePos)]) :-
  122    integer(Line), Line >= 1,
  123    integer(LinePos), LinePos >= 1,
  124    ground(FileSpec),                      % so specific; do not try alts
  125    !,
  126    locate(FileSpec, _, [file(Path)]).
  127locate(Path, file(Path), [file(Path)]) :-
  128    atom(Path),
  129    exists_file(Path),
  130    \+ exists_directory(Path).
  131locate(Pattern, file(Path), [file(Path)]) :-
  132    atom(Pattern),
  133    catch(expand_file_name(Pattern, Files), _, fail),
  134    member(Path, Files),
  135    exists_file(Path),
  136    \+ exists_directory(Path).
  137locate(FileBase, file(File), [file(File)]) :-
  138    atom(FileBase),
  139    absolute_file_name(FileBase,
  140                       [ file_type(prolog),
  141                         access(read),
  142                         file_errors(fail)
  143                       ],
  144                       File),
  145    \+ exists_directory(File).
  146locate(FileSpec, file(File), [file(File)]) :-
  147    catch(absolute_file_name(FileSpec,
  148                             [ file_type(prolog),
  149                               access(read),
  150                               file_errors(fail)
  151                             ],
  152                             File),
  153          _, fail).
  154locate(FileBase, source_file(Path), [file(Path)]) :-
  155    atom(FileBase),
  156    source_file(Path),
  157    file_base_name(Path, File),
  158    (   File == FileBase
  159    ->  true
  160    ;   file_name_extension(FileBase, _, File)
  161    ).
  162locate(FileBase, include_file(Path), [file(Path)]) :-
  163    atom(FileBase),
  164    setof(Path, include_file(Path), Paths),
  165    member(Path, Paths),
  166    file_base_name(Path, File),
  167    (   File == FileBase
  168    ->  true
  169    ;   file_name_extension(FileBase, _, File)
  170    ).
  171locate(Name, FullSpec, Location) :-
  172    atom(Name),
  173    locate(Name/_, FullSpec, Location).
  174locate(Name/Arity, Module:Name/Arity, Location) :-
  175    locate(Module:Name/Arity, Location).
  176locate(Name//DCGArity, FullSpec, Location) :-
  177    (   integer(DCGArity)
  178    ->  Arity is DCGArity+2,
  179        locate(Name/Arity, FullSpec, Location)
  180    ;   locate(Name/_, FullSpec, Location) % demand arity >= 2
  181    ).
  182locate(Name/Arity, library(File), [file(PlPath)]) :-
  183    atom(Name),
  184    '$in_library'(Name, Arity, Path),
  185    (   absolute_file_name(library(.),
  186                           [ file_type(directory),
  187                             solutions(all)
  188                           ],
  189                           Dir),
  190        atom_concat(Dir, File0, Path),
  191        atom_concat(/, File, File0)
  192    ->  absolute_file_name(Path,
  193                           [ file_type(prolog),
  194                             access(read),
  195                             file_errors(fail)
  196                           ],
  197                           PlPath)
  198    ;   fail
  199    ).
  200locate(Module:Name, Module:Name/Arity, Location) :-
  201    locate(Module:Name/Arity, Location).
  202locate(Module:Head, Module:Name/Arity, Location) :-
  203    callable(Head),
  204    \+ ( Head = (PName/_),
  205         atom(PName)
  206       ),
  207    functor(Head, Name, Arity),
  208    locate(Module:Name/Arity, Location).
  209locate(Spec, module(Spec), Location) :-
  210    locate(module(Spec), Location).
  211locate(Spec, Spec, Location) :-
  212    locate(Spec, Location).
  213
  214include_file(Path) :-
  215    source_file_property(Path, included_in(_,_)).
 locate(+Spec, -Location)
Locate object from the specified location.
  222locate(file(File, line(Line)), [file(File), line(Line)]).
  223locate(file(File), [file(File)]).
  224locate(Module:Name/Arity, [file(File), line(Line)]) :-
  225    (   atom(Name), integer(Arity)
  226    ->  functor(Head, Name, Arity)
  227    ;   Head = _                    % leave unbound
  228    ),
  229    (   (   var(Module)
  230        ;   var(Name)
  231        )
  232    ->  NonImport = true
  233    ;   NonImport = false
  234    ),
  235    current_predicate(Name, Module:Head),
  236    \+ (   NonImport == true,
  237           Module \== system,
  238           predicate_property(Module:Head, imported_from(_))
  239       ),
  240    functor(Head, Name, Arity),     % bind arity
  241    predicate_property(Module:Head, file(File)),
  242    predicate_property(Module:Head, line_count(Line)).
  243locate(module(Module), [file(Path)|Rest]) :-
  244    atom(Module),
  245    module_property(Module, file(Path)),
  246    (   module_property(Module, line_count(Line))
  247    ->  Rest = [line(Line)]
  248    ;   Rest = []
  249    ).
  250locate(breakpoint(Id), Location) :-
  251    integer(Id),
  252    breakpoint_property(Id, clause(Ref)),
  253    (   breakpoint_property(Id, file(File)),
  254        breakpoint_property(Id, line_count(Line))
  255    ->  Location = [file(File),line(Line)]
  256    ;   locate(clause(Ref), Location)
  257    ).
  258locate(clause(Ref), [file(File), line(Line)]) :-
  259    clause_property(Ref, file(File)),
  260    clause_property(Ref, line_count(Line)).
  261locate(clause(Ref, _PC), [file(File), line(Line)]) :- % TBD: use clause
  262    clause_property(Ref, file(File)),
  263    clause_property(Ref, line_count(Line)).
  264
  265
  266                 /*******************************
  267                 *             EDIT             *
  268                 *******************************/
 do_edit_source(+Location)
Actually call the editor to edit Location, a list of Name(Value) that contains file(File) and may contain line(Line). First the multifile hook edit_source/1 is called. If this fails the system checks for XPCE and the prolog-flag editor. If the latter is built_in or pce_emacs, it will start PceEmacs.

Finally, it will get the editor to use from the prolog-flag editor and use edit_command/2 to determine how this editor should be called.

  282do_edit_source(Location) :-             % hook
  283    edit_source(Location),
  284    !.
  285do_edit_source(Location) :-             % PceEmacs
  286    current_prolog_flag(editor, Editor),
  287    pceemacs(Editor),
  288    current_prolog_flag(gui, true),
  289    !,
  290    memberchk(file(File), Location),
  291    (   memberchk(line(Line), Location)
  292    ->  (   memberchk(linepos(LinePos), Location)
  293        ->  Pos = (File:Line:LinePos)
  294        ;   Pos = (File:Line)
  295        )
  296    ;   Pos = File
  297    ),
  298    in_pce_thread(emacs(Pos)).
  299do_edit_source(Location) :-             % External editor
  300    external_edit_command(Location, Command),
  301    print_message(informational, edit(waiting_for_editor)),
  302    (   catch(shell(Command), E,
  303              (print_message(warning, E),
  304               fail))
  305    ->  print_message(informational, edit(make)),
  306        make
  307    ;   print_message(informational, edit(canceled))
  308    ).
  309
  310external_edit_command(Location, Command) :-
  311    memberchk(file(File), Location),
  312    memberchk(line(Line), Location),
  313    editor(Editor),
  314    file_base_name(Editor, EditorFile),
  315    file_name_extension(Base, _, EditorFile),
  316    edit_command(Base, Cmd),
  317    prolog_to_os_filename(File, OsFile),
  318    atom_codes(Cmd, S0),
  319    substitute('%e', Editor, S0, S1),
  320    substitute('%f', OsFile, S1, S2),
  321    substitute('%d', Line,   S2, S),
  322    !,
  323    atom_codes(Command, S).
  324external_edit_command(Location, Command) :-
  325    memberchk(file(File), Location),
  326    editor(Editor),
  327    file_base_name(Editor, EditorFile),
  328    file_name_extension(Base, _, EditorFile),
  329    edit_command(Base, Cmd),
  330    prolog_to_os_filename(File, OsFile),
  331    atom_codes(Cmd, S0),
  332    substitute('%e', Editor, S0, S1),
  333    substitute('%f', OsFile, S1, S),
  334    \+ substitute('%d', 1, S, _),
  335    !,
  336    atom_codes(Command, S).
  337external_edit_command(Location, Command) :-
  338    memberchk(file(File), Location),
  339    editor(Editor),
  340    atomic_list_concat(['"', Editor, '" "', File, '"'], Command).
  341
  342pceemacs(pce_emacs).
  343pceemacs(built_in).
 editor(-Editor)
Determine the external editor to run.
  349editor(Editor) :-                       % $EDITOR
  350    current_prolog_flag(editor, Editor),
  351    (   sub_atom(Editor, 0, _, _, $)
  352    ->  sub_atom(Editor, 1, _, 0, Var),
  353        catch(getenv(Var, Editor), _, fail), !
  354    ;   Editor == default
  355    ->  catch(getenv('EDITOR', Editor), _, fail), !
  356    ;   \+ pceemacs(Editor)
  357    ->  !
  358    ).
  359editor(Editor) :-                       % User defaults
  360    getenv('EDITOR', Editor),
  361    !.
  362editor(vi) :-                           % Platform defaults
  363    current_prolog_flag(unix, true),
  364    !.
  365editor(notepad) :-
  366    current_prolog_flag(windows, true),
  367    !.
  368editor(_) :-                            % No luck
  369    throw(error(existence_error(editor), _)).
 edit_command(+Editor, -Command)
This predicate should specify the shell-command called to invoke the user's editor. The following substitutions will be made:
%ePath name of the editor
%fPath name of the file to be edited
%dLine number of the target
  381edit_command(vi,          '%e +%d \'%f\'').
  382edit_command(vi,          '%e \'%f\'').
  383edit_command(emacs,       '%e +%d \'%f\'').
  384edit_command(emacs,       '%e \'%f\'').
  385edit_command(notepad,     '"%e" "%f"').
  386edit_command(wordpad,     '"%e" "%f"').
  387edit_command(uedit32,     '%e "%f/%d/0"').      % ultraedit (www.ultraedit.com)
  388edit_command(jedit,       '%e -wait \'%f\' +line:%d').
  389edit_command(jedit,       '%e -wait \'%f\'').
  390edit_command(edit,        '%e %f:%d').          % PceEmacs client script
  391edit_command(edit,        '%e %f').
  392
  393edit_command(emacsclient, Command) :- edit_command(emacs, Command).
  394edit_command(vim,         Command) :- edit_command(vi,    Command).
  395edit_command(nvim,        Command) :- edit_command(vi,    Command).
  396
  397substitute(FromAtom, ToAtom, Old, New) :-
  398    atom_codes(FromAtom, From),
  399    (   atom(ToAtom)
  400    ->  atom_codes(ToAtom, To)
  401    ;   number_codes(ToAtom, To)
  402    ),
  403    append(Pre, S0, Old),
  404    append(From, Post, S0) ->
  405    append(Pre, To, S1),
  406    append(S1, Post, New),
  407    !.
  408substitute(_, _, Old, Old).
  409
  410
  411                 /*******************************
  412                 *            SELECT            *
  413                 *******************************/
  414
  415merge_locations(Pairs0, Pairs) :-
  416    keysort(Pairs0, Pairs1),
  417    merge_locations2(Pairs1, Pairs).
  418
  419merge_locations2([], []).
  420merge_locations2([H0|T0], [H|T]) :-
  421    remove_same_location(H0, H, T0, T1),
  422    merge_locations2(T1, T).
  423
  424remove_same_location(Pair0, H, [Pair1|T0], L) :-
  425    merge_locations(Pair0, Pair1, Pair2),
  426    !,
  427    remove_same_location(Pair2, H, T0, L).
  428remove_same_location(H, H, L, L).
  429
  430merge_locations(Loc1-Spec1, Loc2-Spec2, Loc-Spec) :-
  431    same_location(Loc1, Loc2, Loc),
  432    !,
  433    (   merge_specs(Spec1, Spec2, Spec)
  434    ;   merge_specs(Spec2, Spec1, Spec)
  435    ;   Spec = Spec1
  436    ),
  437    !.
  438merge_locations([file(X)]-_, Loc-Spec, Loc-Spec) :-
  439    memberchk(file(X), Loc),
  440    memberchk(line(_), Loc).
  441
  442same_location(L, L, L).
  443same_location([file(F1)], [file(F2)], [file(F)]) :-
  444    best_same_file(F1, F2, F).
  445same_location([file(F1),line(L)], [file(F2)], [file(F),line(L)]) :-
  446    best_same_file(F1, F2, F).
  447same_location([file(F1)], [file(F2),line(L)], [file(F),line(L)]) :-
  448    best_same_file(F1, F2, F).
  449
  450best_same_file(F1, F2, F) :-
  451    catch(same_file(F1, F2), _, fail),
  452    !,
  453    atom_length(F1, L1),
  454    atom_length(F2, L2),
  455    (   L1 < L2
  456    ->  F = F1
  457    ;   F = F2
  458    ).
  459
  460merge_specs(source_file(Path), _, source_file(Path)).
 select_location(+Pairs, +UserSpec, -Location)
  464do_select_location(Pairs, Spec, Location) :-
  465    select_location(Pairs, Spec, Location),                % HOOK
  466    !,
  467    Location \== [].
  468do_select_location([], Spec, _) :-
  469    !,
  470    print_message(warning, edit(not_found(Spec))),
  471    fail.
  472do_select_location([Location-_Spec], _, Location) :- !.
  473do_select_location(Pairs, _, Location) :-
  474    print_message(help, edit(select)),
  475    list_pairs(Pairs, 0, N),
  476    print_message(help, edit(prompt_select)),
  477    read_number(N, I),
  478    nth1(I, Pairs, Location-_Spec),
  479    !.
  480
  481list_pairs([], N, N).
  482list_pairs([H|T], N0, N) :-
  483    NN is N0 + 1,
  484    list_pair(H, NN),
  485    list_pairs(T, NN, N).
  486
  487list_pair(Pair, N) :-
  488    print_message(help, edit(target(Pair, N))).
  489
  490
  491read_number(Max, X) :-
  492    Max < 10,
  493    !,
  494    get_single_char(C),
  495    between(0'0, 0'9, C),
  496    X is C - 0'0.
  497read_number(_, X) :-
  498    read_line(Chars),
  499    name(X, Chars),
  500    integer(X).
  501
  502read_line(Chars) :-
  503    get0(user_input, C0),
  504    read_line(C0, Chars).
  505
  506read_line(10, []) :- !.
  507read_line(-1, []) :- !.
  508read_line(C, [C|T]) :-
  509    get0(user_input, C1),
  510    read_line(C1, T).
  511
  512
  513                 /*******************************
  514                 *             MESSAGES         *
  515                 *******************************/
  516
  517:- multifile
  518    prolog:message/3.  519
  520prolog:message(edit(not_found(Spec))) -->
  521    [ 'Cannot find anything to edit from "~p"'-[Spec] ],
  522    (   { atom(Spec) }
  523    ->  [ nl, '    Use edit(file(~q)) to create a new file'-[Spec] ]
  524    ;   []
  525    ).
  526prolog:message(edit(select)) -->
  527    [ 'Please select item to edit:', nl, nl ].
  528prolog:message(edit(prompt_select)) -->
  529    [ nl, 'Your choice? ', flush ].
  530prolog:message(edit(target(Location-Spec, N))) -->
  531    [ '~t~d~3| '-[N]],
  532    edit_specifier(Spec),
  533    [ '~t~32|' ],
  534    edit_location(Location).
  535prolog:message(edit(waiting_for_editor)) -->
  536    [ 'Waiting for editor ... ', flush ].
  537prolog:message(edit(make)) -->
  538    [ 'Running make to reload modified files' ].
  539prolog:message(edit(canceled)) -->
  540    [ 'Editor returned failure; skipped make/0 to reload files' ].
  541
  542edit_specifier(Module:Name/Arity) -->
  543    !,
  544    [ '~w:~w/~w'-[Module, Name, Arity] ].
  545edit_specifier(file(_Path)) -->
  546    !,
  547    [ '<file>' ].
  548edit_specifier(source_file(_Path)) -->
  549    !,
  550    [ '<loaded file>' ].
  551edit_specifier(include_file(_Path)) -->
  552    !,
  553    [ '<included file>' ].
  554edit_specifier(Term) -->
  555    [ '~p'-[Term] ].
  556
  557edit_location(Location) -->
  558    { memberchk(file(File), Location),
  559      memberchk(line(Line), Location),
  560      short_filename(File, Spec)
  561    },
  562    !,
  563    [ '~q:~d'-[Spec, Line] ].
  564edit_location(Location) -->
  565    { memberchk(file(File), Location),
  566      short_filename(File, Spec)
  567    },
  568    !,
  569    [ '~q'-[Spec] ].
  570
  571short_filename(Path, Spec) :-
  572    absolute_file_name('', Here),
  573    atom_concat(Here, Local0, Path),
  574    !,
  575    remove_leading_slash(Local0, Spec).
  576short_filename(Path, Spec) :-
  577    findall(LenAlias, aliased_path(Path, LenAlias), Keyed),
  578    keysort(Keyed, [_-Spec|_]).
  579short_filename(Path, Path).
  580
  581aliased_path(Path, Len-Spec) :-
  582    setof(Alias, file_alias_path(Alias), Aliases),
  583    member(Alias, Aliases),
  584    Alias \== autoload,             % confusing and covered by something else
  585    Term =.. [Alias, '.'],
  586    absolute_file_name(Term,
  587                       [ file_type(directory),
  588                         file_errors(fail),
  589                         solutions(all)
  590                       ], Prefix),
  591    atom_concat(Prefix, Local0, Path),
  592    remove_leading_slash(Local0, Local),
  593    atom_length(Local, Len),
  594    Spec =.. [Alias, Local].
  595
  596file_alias_path(Alias) :-
  597    user:file_search_path(Alias, _).
  598
  599remove_leading_slash(Path, Local) :-
  600    atom_concat(/, Local, Path),
  601    !.
  602remove_leading_slash(Path, Path).
  603
  604
  605                 /*******************************
  606                 *        LOAD EXTENSIONS       *
  607                 *******************************/
  608
  609load_extensions :-
  610    load,
  611    fail.
  612load_extensions.
  613
  614:- load_extensions.