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