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-2025, University of Amsterdam 7 VU University Amsterdam 8 SWI-Prolog Solutions b.v. 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(prolog_edit, 38 [ edit/1, % +Spec 39 edit/0 40 ]). 41:- autoload(library(lists), [member/2, append/3, select/3]). 42:- autoload(library(make), [make/0]). 43:- if(exists_source(library(pce))). 44:- autoload(library(pce), [in_pce_thread/1]). 45:- autoload(library(pce_emacs), [emacs/1]). 46:- endif. 47:- autoload(library(prolog_breakpoints), [breakpoint_property/2]). 48:- autoload(library(apply), [foldl/5, maplist/3, maplist/2]). 49:- use_module(library(dcg/high_order), [sequence/5]). 50:- autoload(library(readutil), [read_line_to_string/2]). 51 52 53% :- set_prolog_flag(generate_debug_info, false).
63:- multifile 64 locate/3, % +Partial, -FullSpec, -Location 65 locate/2, % +FullSpec, -Location 66 select_location/3, % +Pairs, +Spec, -Location 67 exists_location/1, % +Location 68 user_select/2, % +Max, -I 69 edit_source/1, % +Location 70 edit_command/2, % +Editor, -Command 71 load/0. % provides load-hooks
77edit(Spec) :- 78 notrace(edit_no_trace(Spec)). 79 80edit_no_trace(Spec) :- 81 var(Spec), 82 !, 83 throw(error(instantiation_error, _)). 84edit_no_trace(Spec) :- 85 load_extensions, 86 findall(Location-FullSpec, 87 locate(Spec, FullSpec, Location), 88 Pairs0), 89 sort(Pairs0, Pairs1), 90 merge_locations(Pairs1, Pairs), 91 do_select_location(Pairs, Spec, Location), 92 do_edit_source(Location).
% swipl [-s] file.pl
103edit :- 104 current_prolog_flag(associated_file, File), 105 !, 106 edit(file(File)). 107edit :- 108 '$cmd_option_val'(script_file, OsFiles), 109 OsFiles = [OsFile], 110 !, 111 prolog_to_os_filename(File, OsFile), 112 edit(file(File)). 113edit :- 114 throw(error(context_error(edit, no_default_file), _)). 115 116 117 /******************************* 118 * LOCATE * 119 *******************************/
123locate(FileSpec:Line, file(Path, line(Line)), #{file:Path, line:Line}) :- 124 integer(Line), Line >= 1, 125 ground(FileSpec), % so specific; do not try alts 126 !, 127 locate(FileSpec, _, #{file:Path}). 128locate(FileSpec:Line:LinePos, 129 file(Path, line(Line), linepos(LinePos)), 130 #{file:Path, line:Line, linepos:LinePos}) :- 131 integer(Line), Line >= 1, 132 integer(LinePos), LinePos >= 1, 133 ground(FileSpec), % so specific; do not try alts 134 !, 135 locate(FileSpec, _, #{file:Path}). 136locate(Path, file(Path), #{file:Path}) :- 137 atom(Path), 138 exists_file(Path). 139locate(Pattern, file(Path), #{file:Path}) :- 140 atom(Pattern), 141 catch(expand_file_name(Pattern, Files), error(_,_), fail), 142 member(Path, Files), 143 exists_file(Path). 144locate(FileBase, file(File), #{file:File}) :- 145 atom(FileBase), 146 find_source(FileBase, File). 147locate(FileSpec, file(File), #{file:File}) :- 148 is_file_search_spec(FileSpec), 149 find_source(FileSpec, File). 150locate(FileBase, source_file(Path), #{file:Path}) :- 151 atom(FileBase), 152 source_file(Path), 153 file_base_name(Path, File), 154 ( File == FileBase 155 -> true 156 ; file_name_extension(FileBase, _, File) 157 ). 158locate(FileBase, include_file(Path), #{file:Path}) :- 159 atom(FileBase), 160 setof(Path, include_file(Path), Paths), 161 member(Path, Paths), 162 file_base_name(Path, File), 163 ( File == FileBase 164 -> true 165 ; file_name_extension(FileBase, _, File) 166 ). 167locate(Name, FullSpec, Location) :- 168 atom(Name), 169 locate(Name/_, FullSpec, Location). 170locate(Name/Arity, Module:Name/Arity, Location) :- 171 locate(Module:Name/Arity, Location). 172locate(Name//DCGArity, FullSpec, Location) :- 173 ( integer(DCGArity) 174 -> Arity is DCGArity+2, 175 locate(Name/Arity, FullSpec, Location) 176 ; locate(Name/_, FullSpec, Location) % demand arity >= 2 177 ). 178locate(Name/Arity, library(File), #{file:PlPath}) :- 179 atom(Name), 180 '$in_library'(Name, Arity, Path), 181 ( absolute_file_name(library(.), Dir, 182 [ file_type(directory), 183 solutions(all) 184 ]), 185 atom_concat(Dir, File0, Path), 186 atom_concat(/, File, File0) 187 -> find_source(Path, PlPath) 188 ; fail 189 ). 190locate(Module:Name, Module:Name/Arity, Location) :- 191 locate(Module:Name/Arity, Location). 192locate(Module:Head, Module:Name/Arity, Location) :- 193 callable(Head), 194 \+ ( Head = (PName/_), 195 atom(PName) 196 ), 197 functor(Head, Name, Arity), 198 locate(Module:Name/Arity, Location). 199locate(Spec, module(Spec), Location) :- 200 locate(module(Spec), Location). 201locate(Spec, Spec, Location) :- 202 locate(Spec, Location). 203 204include_file(Path) :- 205 source_file_property(Path, included_in(_,_)).
211is_file_search_spec(Spec) :- 212 compound(Spec), 213 compound_name_arguments(Spec, Alias, [Arg]), 214 is_file_spec(Arg), 215 user:file_search_path(Alias, _), 216 !. 217 218is_file_spec(Name), atom(Name) => true. 219is_file_spec(Name), string(Name) => true. 220is_file_spec(Term), cyclic_term(Term) => fail. 221is_file_spec(A/B) => is_file_spec(A), is_file_spec(B).
228find_source(FileSpec, File) :- 229 catch(absolute_file_name(FileSpec, File0, 230 [ file_type(prolog), 231 access(read), 232 file_errors(fail) 233 ]), 234 error(_,_), fail), 235 prolog_source(File0, File). 236 237prolog_source(File0, File) :- 238 file_name_extension(_, Ext, File0), 239 user:prolog_file_type(Ext, qlf), 240 !, 241 '$qlf_module'(File0, Info), 242 File = Info.get(file). 243prolog_source(File, File).
250locate(file(File, line(Line)), #{file:File, line:Line}). 251locate(file(File), #{file:File}). 252locate(Module:Name/Arity, #{file:File, line:Line}) :- 253 ( atom(Name), integer(Arity) 254 -> functor(Head, Name, Arity) 255 ; Head = _ % leave unbound 256 ), 257 ( ( var(Module) 258 ; var(Name) 259 ) 260 -> NonImport = true 261 ; NonImport = false 262 ), 263 current_predicate(Name, Module:Head), 264 \+ ( NonImport == true, 265 Module \== system, 266 predicate_property(Module:Head, imported_from(_)) 267 ), 268 functor(Head, Name, Arity), % bind arity 269 predicate_property(Module:Head, file(File)), 270 predicate_property(Module:Head, line_count(Line)). 271locate(module(Module), Location) :- 272 atom(Module), 273 module_property(Module, file(Path)), 274 ( module_property(Module, line_count(Line)) 275 -> Location = #{file:Path, line:Line} 276 ; Location = #{file:Path} 277 ). 278locate(breakpoint(Id), Location) :- 279 integer(Id), 280 breakpoint_property(Id, clause(Ref)), 281 ( breakpoint_property(Id, file(File)), 282 breakpoint_property(Id, line_count(Line)) 283 -> Location = #{file:File, line:Line} 284 ; locate(clause(Ref), Location) 285 ). 286locate(clause(Ref), #{file:File, line:Line}) :- 287 clause_property(Ref, file(File)), 288 clause_property(Ref, line_count(Line)). 289locate(clause(Ref, _PC), #{file:File, line:Line}) :- % TBD: use clause 290 clause_property(Ref, file(File)), 291 clause_property(Ref, line_count(Line)). 292 293 294 /******************************* 295 * EDIT * 296 *******************************/
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.
310do_edit_source(Location) :- % hook 311 edit_source(Location), 312 !. 313:- if(current_predicate(emacs/1)). 314do_edit_source(Location) :- % PceEmacs 315 current_prolog_flag(editor, Editor), 316 pceemacs(Editor), 317 current_prolog_flag(gui, true), 318 !, 319 location_url(Location, URL), % File[:Line[:LinePos]] 320 in_pce_thread(emacs(URL)). 321:- endif. 322do_edit_source(Location) :- % External editor 323 external_edit_command(Location, Command), 324 print_message(informational, edit(waiting_for_editor)), 325 ( catch(shell(Command), E, 326 (print_message(warning, E), 327 fail)) 328 -> print_message(informational, edit(make)), 329 make 330 ; print_message(informational, edit(canceled)) 331 ). 332 333external_edit_command(Location, Command) :- 334 #{file:File, line:Line} :< Location, 335 editor(Editor), 336 file_base_name(Editor, EditorFile), 337 file_name_extension(Base, _, EditorFile), 338 edit_command(Base, Cmd), 339 prolog_to_os_filename(File, OsFile), 340 atom_codes(Cmd, S0), 341 substitute('%e', Editor, S0, S1), 342 substitute('%f', OsFile, S1, S2), 343 substitute('%d', Line, S2, S), 344 !, 345 atom_codes(Command, S). 346external_edit_command(Location, Command) :- 347 #{file:File} :< Location, 348 editor(Editor), 349 file_base_name(Editor, EditorFile), 350 file_name_extension(Base, _, EditorFile), 351 edit_command(Base, Cmd), 352 prolog_to_os_filename(File, OsFile), 353 atom_codes(Cmd, S0), 354 substitute('%e', Editor, S0, S1), 355 substitute('%f', OsFile, S1, S), 356 \+ substitute('%d', 1, S, _), 357 !, 358 atom_codes(Command, S). 359external_edit_command(Location, Command) :- 360 #{file:File} :< Location, 361 editor(Editor), 362 format(string(Command), '"~w" "~w"', [Editor, File]). 363 364pceemacs(pce_emacs). 365pceemacs(built_in).
371editor(Editor) :- % $EDITOR 372 current_prolog_flag(editor, Editor), 373 ( sub_atom(Editor, 0, _, _, $) 374 -> sub_atom(Editor, 1, _, 0, Var), 375 catch(getenv(Var, Editor), _, fail), ! 376 ; Editor == default 377 -> catch(getenv('EDITOR', Editor), _, fail), ! 378 ; \+ pceemacs(Editor) 379 -> ! 380 ). 381editor(Editor) :- % User defaults 382 getenv('EDITOR', Editor), 383 !. 384editor(vi) :- % Platform defaults 385 current_prolog_flag(unix, true), 386 !. 387editor(notepad) :- 388 current_prolog_flag(windows, true), 389 !. 390editor(_) :- % No luck 391 throw(error(existence_error(editor), _)).
%e | Path name of the editor |
%f | Path name of the file to be edited |
%d | Line number of the target |
403edit_command(vi, '%e +%d \'%f\''). 404edit_command(vi, '%e \'%f\''). 405edit_command(emacs, '%e +%d \'%f\''). 406edit_command(emacs, '%e \'%f\''). 407edit_command(notepad, '"%e" "%f"'). 408edit_command(wordpad, '"%e" "%f"'). 409edit_command(uedit32, '%e "%f/%d/0"'). % ultraedit (www.ultraedit.com) 410edit_command(jedit, '%e -wait \'%f\' +line:%d'). 411edit_command(jedit, '%e -wait \'%f\''). 412edit_command(edit, '%e %f:%d'). % PceEmacs client script 413edit_command(edit, '%e %f'). 414 415edit_command(emacsclient, Command) :- edit_command(emacs, Command). 416edit_command(vim, Command) :- edit_command(vi, Command). 417edit_command(nvim, Command) :- edit_command(vi, Command). 418 419substitute(FromAtom, ToAtom, Old, New) :- 420 atom_codes(FromAtom, From), 421 ( atom(ToAtom) 422 -> atom_codes(ToAtom, To) 423 ; number_codes(ToAtom, To) 424 ), 425 append(Pre, S0, Old), 426 append(From, Post, S0) -> 427 append(Pre, To, S1), 428 append(S1, Post, New), 429 !. 430substitute(_, _, Old, Old). 431 432 433 /******************************* 434 * SELECT * 435 *******************************/ 436 437merge_locations([L1|T1], Locations) :- 438 L1 = Loc1-Spec1, 439 select(L2, T1, T2), 440 L2 = Loc2-Spec2, 441 same_location(Loc1, Loc2, Loc), 442 merge_specs(Spec1, Spec2, Spec), 443 !, 444 merge_locations([Loc-Spec|T2], Locations). 445merge_locations(Locations, Locations). 446 447same_location(L, L, L). 448same_location(#{file:F1}, #{file:F2}, #{file:F}) :- 449 best_same_file(F1, F2, F). 450same_location(#{file:F1, line:Line}, #{file:F2}, #{file:F, line:Line}) :- 451 best_same_file(F1, F2, F). 452same_location(#{file:F1}, #{file:F2, line:Line}, #{file:F, line:Line}) :- 453 best_same_file(F1, F2, F). 454 455best_same_file(F1, F2, F) :- 456 catch(same_file(F1, F2), _, fail), 457 !, 458 atom_length(F1, L1), 459 atom_length(F2, L2), 460 ( L1 < L2 461 -> F = F1 462 ; F = F2 463 ). 464 465merge_specs(Spec, Spec, Spec) :- 466 !. 467merge_specs(file(F1), file(F2), file(F)) :- 468 best_same_file(F1, F2, F), 469 !. 470merge_specs(Spec1, Spec2, Spec) :- 471 merge_specs_(Spec1, Spec2, Spec), 472 !. 473merge_specs(Spec1, Spec2, Spec) :- 474 merge_specs_(Spec2, Spec1, Spec), 475 !. 476 477merge_specs_(FileSpec, Spec, Spec) :- 478 is_filespec(FileSpec). 479 480is_filespec(source_file(_)) => true. 481is_filespec(Term), 482 compound(Term), 483 compound_name_arguments(Term, Alias, [_Arg]), 484 user:file_search_path(Alias, _) => true. 485is_filespec(_) => 486 fail.
493do_select_location(Pairs, Spec, Location) :- 494 select_location(Pairs, Spec, Location), % HOOK 495 !, 496 Location \== []. 497do_select_location([], Spec, _) :- 498 !, 499 print_message(warning, edit(not_found(Spec))), 500 fail. 501do_select_location([#{file:File}-file(File)], _, Location) :- 502 !, 503 Location = #{file:File}. 504do_select_location([Location-_Spec], _, Location) :- 505 existing_location(Location), 506 !. 507do_select_location(Pairs, _, Location) :- 508 foldl(number_location, Pairs, NPairs, 1, End), 509 print_message(help, edit(select(NPairs))), 510 ( End == 1 511 -> fail 512 ; Max is End - 1, 513 user_selection(Max, I), 514 memberchk(I-(Location-_Spec), NPairs) 515 ).
523existing_location(Location) :- 524 exists_location(Location), 525 !. 526existing_location(Location) :- 527 #{file:File} :< Location, 528 access_file(File, read). 529 530number_location(Pair, N-Pair, N, N1) :- 531 Pair = Location-_Spec, 532 existing_location(Location), 533 !, 534 N1 is N+1. 535number_location(Pair, 0-Pair, N, N). 536 537user_selection(Max, I) :- 538 user_select(Max, I), 539 !. 540user_selection(Max, I) :- 541 print_message(help, edit(choose(Max))), 542 read_number(Max, I).
548read_number(Max, X) :- 549 Max < 10, 550 !, 551 get_single_char(C), 552 put_code(user_error, C), 553 between(0'0, 0'9, C), 554 X is C - 0'0. 555read_number(_, X) :- 556 read_line_to_string(user_input, String), 557 number_string(X, String). 558 559 560 /******************************* 561 * MESSAGES * 562 *******************************/ 563 564:- multifile 565 prolog:message/3. 566 567prologmessage(edit(Msg)) --> 568 message(Msg). 569 570message(not_found(Spec)) --> 571 [ 'Cannot find anything to edit from "~p"'-[Spec] ], 572 ( { atom(Spec) } 573 -> [ nl, ' Use edit(file(~q)) to create a new file'-[Spec] ] 574 ; [] 575 ). 576message(select(NPairs)) --> 577 { \+ (member(N-_, NPairs), N > 0) }, 578 !, 579 [ 'Found the following locations:', nl ], 580 sequence(target, [nl], NPairs). 581message(select(NPairs)) --> 582 [ 'Please select item to edit:', nl ], 583 sequence(target, [nl], NPairs). 584message(choose(_Max)) --> 585 [ nl, 'Your choice? ', flush ]. 586message(waiting_for_editor) --> 587 [ 'Waiting for editor ... ', flush ]. 588message(make) --> 589 [ 'Running make to reload modified files' ]. 590message(canceled) --> 591 [ 'Editor returned failure; skipped make/0 to reload files' ]. 592 593target(0-(Location-Spec)) ==> 594 [ ansi(warning, '~t*~3| ', [])], 595 edit_specifier(Spec), 596 [ '~t~32|' ], 597 edit_location(Location, false), 598 [ ansi(warning, ' (no source available)', [])]. 599target(N-(Location-Spec)) ==> 600 [ ansi(bold, '~t~d~3| ', [N])], 601 edit_specifier(Spec), 602 [ '~t~32|' ], 603 edit_location(Location, true). 604 605edit_specifier(Module:Name/Arity) ==> 606 [ '~w:'-[Module], 607 ansi(code, '~w/~w', [Name, Arity]) ]. 608edit_specifier(file(_Path)) ==> 609 [ '<file>' ]. 610edit_specifier(source_file(_Path)) ==> 611 [ '<loaded file>' ]. 612edit_specifier(include_file(_Path)) ==> 613 [ '<included file>' ]. 614edit_specifier(Term) ==> 615 [ '~p'-[Term] ]. 616 617edit_location(Location, false) ==> 618 { location_label(Location, Label) }, 619 [ ansi(warning, '~s', [Label]) ]. 620edit_location(Location, true) ==> 621 { location_label(Location, Label), 622 location_url(Location, URL) 623 }, 624 [ url(URL, Label) ]. 625 626location_label(Location, Label) :- 627 #{file:File, line:Line} :< Location, 628 !, 629 short_filename(File, ShortFile), 630 format(string(Label), '~w:~d', [ShortFile, Line]). 631location_label(Location, Label) :- 632 #{file:File} :< Location, 633 !, 634 short_filename(File, ShortFile), 635 format(string(Label), '~w', [ShortFile]). 636 637location_url(Location, File:Line:LinePos) :- 638 #{file:File, line:Line, linepos:LinePos} :< Location, 639 !. 640location_url(Location, File:Line) :- 641 #{file:File, line:Line} :< Location, 642 !. 643location_url(Location, File) :- 644 #{file:File} :< Location.
652short_filename(Path, Spec) :- 653 working_directory(Here, Here), 654 atom_concat(Here, Local0, Path), 655 !, 656 remove_leading_slash(Local0, Spec). 657short_filename(Path, Spec) :- 658 findall(LenAlias, aliased_path(Path, LenAlias), Keyed), 659 keysort(Keyed, [_-Spec|_]). 660short_filename(Path, Path). 661 662aliased_path(Path, Len-Spec) :- 663 setof(Alias, file_alias_path(Alias), Aliases), 664 member(Alias, Aliases), 665 Alias \== autoload, % confusing and covered by something else 666 Term =.. [Alias, '.'], 667 absolute_file_name(Term, Prefix, 668 [ file_type(directory), 669 file_errors(fail), 670 solutions(all) 671 ]), 672 atom_concat(Prefix, Local0, Path), 673 remove_leading_slash(Local0, Local1), 674 remove_extension(Local1, Local2), 675 unquote_segments(Local2, Local), 676 atom_length(Local2, Len), 677 Spec =.. [Alias, Local]. 678 679file_alias_path(Alias) :- 680 user:file_search_path(Alias, _). 681 682remove_leading_slash(Path, Local) :- 683 atom_concat(/, Local, Path), 684 !. 685remove_leading_slash(Path, Path). 686 687remove_extension(File0, File) :- 688 file_name_extension(File, Ext, File0), 689 user:prolog_file_type(Ext, source), 690 !. 691remove_extension(File, File). 692 693unquote_segments(File, Segments) :- 694 split_string(File, "/", "/", SegmentStrings), 695 maplist(atom_string, SegmentList, SegmentStrings), 696 maplist(no_quote_needed, SegmentList), 697 !, 698 segments(SegmentList, Segments). 699unquote_segments(File, File). 700 701 702no_quote_needed(A) :- 703 format(atom(Q), '~q', [A]), 704 Q == A. 705 706segments([Segment], Segment) :- 707 !. 708segments(List, A/Segment) :- 709 append(L1, [Segment], List), 710 !, 711 segments(L1, A). 712 713 714 /******************************* 715 * LOAD EXTENSIONS * 716 *******************************/ 717 718load_extensions :- 719 load, 720 fail. 721load_extensions. 722 723:- load_extensions.
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. */