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-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:- autoload(library(prolog_breakpoints), [breakpoint_property/2]).   44:- autoload(library(apply), [foldl/5, maplist/3, maplist/2]).   45:- use_module(library(dcg/high_order), [sequence/5]).   46:- autoload(library(readutil), [read_line_to_string/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    exists_location/1,              % +Location
   64    user_select/2,                  % +Max, -I
   65    edit_source/1,                  % +Location
   66    edit_command/2,                 % +Editor, -Command
   67    load/0.                         % provides load-hooks
   68
   69%!  edit(+Spec)
   70%
   71%   Edit indicated object.
   72
   73edit(Spec) :-
   74    notrace(edit_no_trace(Spec)).
   75
   76edit_no_trace(Spec) :-
   77    var(Spec),
   78    !,
   79    throw(error(instantiation_error, _)).
   80edit_no_trace(Spec) :-
   81    load_extensions,
   82    findall(Location-FullSpec,
   83            locate(Spec, FullSpec, Location),
   84            Pairs0),
   85    sort(Pairs0, Pairs1),
   86    merge_locations(Pairs1, Pairs),
   87    do_select_location(Pairs, Spec, Location),
   88    do_edit_source(Location).
   89
   90%!  edit
   91%
   92%   Edit associated or script file.  This is the Prolog file opened
   93%   by double-clicking or the file loaded using
   94%
   95%     ==
   96%     % swipl [-s] file.pl
   97%     ==
   98
   99edit :-
  100    current_prolog_flag(associated_file, File),
  101    !,
  102    edit(file(File)).
  103edit :-
  104    '$cmd_option_val'(script_file, OsFiles),
  105    OsFiles = [OsFile],
  106    !,
  107    prolog_to_os_filename(File, OsFile),
  108    edit(file(File)).
  109edit :-
  110    throw(error(context_error(edit, no_default_file), _)).
  111
  112
  113                 /*******************************
  114                 *            LOCATE            *
  115                 *******************************/
  116
  117%!  locate(+Spec, -FullSpec, -Location:dict)
  118
  119locate(FileSpec:Line, file(Path, line(Line)), #{file:Path, line:Line}) :-
  120    integer(Line), Line >= 1,
  121    ground(FileSpec),                      % so specific; do not try alts
  122    !,
  123    locate(FileSpec, _, #{file:Path}).
  124locate(FileSpec:Line:LinePos,
  125       file(Path, line(Line), linepos(LinePos)),
  126       #{file:Path, line:Line, linepos:LinePos}) :-
  127    integer(Line), Line >= 1,
  128    integer(LinePos), LinePos >= 1,
  129    ground(FileSpec),                      % so specific; do not try alts
  130    !,
  131    locate(FileSpec, _, #{file:Path}).
  132locate(Path, file(Path), #{file:Path}) :-
  133    atom(Path),
  134    exists_file(Path).
  135locate(Pattern, file(Path), #{file:Path}) :-
  136    atom(Pattern),
  137    catch(expand_file_name(Pattern, Files), error(_,_), fail),
  138    member(Path, Files),
  139    exists_file(Path).
  140locate(FileBase, file(File), #{file:File}) :-
  141    atom(FileBase),
  142    find_source(FileBase, File).
  143locate(FileSpec, file(File), #{file:File}) :-
  144    is_file_search_spec(FileSpec),
  145    find_source(FileSpec, File).
  146locate(FileBase, source_file(Path),  #{file:Path}) :-
  147    atom(FileBase),
  148    source_file(Path),
  149    file_base_name(Path, File),
  150    (   File == FileBase
  151    ->  true
  152    ;   file_name_extension(FileBase, _, File)
  153    ).
  154locate(FileBase, include_file(Path),  #{file:Path}) :-
  155    atom(FileBase),
  156    setof(Path, include_file(Path), Paths),
  157    member(Path, Paths),
  158    file_base_name(Path, File),
  159    (   File == FileBase
  160    ->  true
  161    ;   file_name_extension(FileBase, _, File)
  162    ).
  163locate(Name, FullSpec, Location) :-
  164    atom(Name),
  165    locate(Name/_, FullSpec, Location).
  166locate(Name/Arity, Module:Name/Arity, Location) :-
  167    locate(Module:Name/Arity, Location).
  168locate(Name//DCGArity, FullSpec, Location) :-
  169    (   integer(DCGArity)
  170    ->  Arity is DCGArity+2,
  171        locate(Name/Arity, FullSpec, Location)
  172    ;   locate(Name/_, FullSpec, Location) % demand arity >= 2
  173    ).
  174locate(Name/Arity, library(File),  #{file:PlPath}) :-
  175    atom(Name),
  176    '$in_library'(Name, Arity, Path),
  177    (   absolute_file_name(library(.), Dir,
  178                           [ file_type(directory),
  179                             solutions(all)
  180                           ]),
  181        atom_concat(Dir, File0, Path),
  182        atom_concat(/, File, File0)
  183    ->  find_source(Path, PlPath)
  184    ;   fail
  185    ).
  186locate(Module:Name, Module:Name/Arity, Location) :-
  187    locate(Module:Name/Arity, Location).
  188locate(Module:Head, Module:Name/Arity, Location) :-
  189    callable(Head),
  190    \+ ( Head = (PName/_),
  191         atom(PName)
  192       ),
  193    functor(Head, Name, Arity),
  194    locate(Module:Name/Arity, Location).
  195locate(Spec, module(Spec), Location) :-
  196    locate(module(Spec), Location).
  197locate(Spec, Spec, Location) :-
  198    locate(Spec, Location).
  199
  200include_file(Path) :-
  201    source_file_property(Path, included_in(_,_)).
  202
  203%!  is_file_search_spec(@Spec) is semidet.
  204%
  205%   True if Spec is valid pattern for absolute_file_name/3.
  206
  207is_file_search_spec(Spec) :-
  208    compound(Spec),
  209    compound_name_arguments(Spec, Alias, [Arg]),
  210    is_file_spec(Arg),
  211    user:file_search_path(Alias, _),
  212    !.
  213
  214is_file_spec(Name), atom(Name) => true.
  215is_file_spec(Name), string(Name) => true.
  216is_file_spec(Term), cyclic_term(Term) => fail.
  217is_file_spec(A/B) => is_file_spec(A), is_file_spec(B).
  218is_file_spec(_) => fail.
  219
  220%!  find_source(++FileSpec, =File) is semidet.
  221%
  222%   Find a source file from FileSpec.  If FileSpec resolves to a .qlf
  223%   file, File is the embedded `.pl` file (which may not exist).
  224
  225find_source(FileSpec, File) :-
  226    catch(absolute_file_name(FileSpec, File0,
  227                             [ file_type(prolog),
  228                               access(read),
  229                               file_errors(fail)
  230                             ]),
  231          error(_,_), fail),
  232    prolog_source(File0, File).
  233
  234prolog_source(File0, File) :-
  235    file_name_extension(_, Ext, File0),
  236    user:prolog_file_type(Ext, qlf),
  237    !,
  238    '$qlf_module'(File0, Info),
  239    File = Info.get(file).
  240prolog_source(File, File).
  241
  242
  243%!  locate(+Spec, -Location)
  244%
  245%   Locate object from the specified location.
  246
  247locate(file(File, line(Line)), #{file:File, line:Line}).
  248locate(file(File), #{file:File}).
  249locate(Module:Name/Arity, #{file:File, line:Line}) :-
  250    (   atom(Name), integer(Arity)
  251    ->  functor(Head, Name, Arity)
  252    ;   Head = _                    % leave unbound
  253    ),
  254    (   (   var(Module)
  255        ;   var(Name)
  256        )
  257    ->  NonImport = true
  258    ;   NonImport = false
  259    ),
  260    current_predicate(Name, Module:Head),
  261    \+ (   NonImport == true,
  262           Module \== system,
  263           predicate_property(Module:Head, imported_from(_))
  264       ),
  265    functor(Head, Name, Arity),     % bind arity
  266    predicate_property(Module:Head, file(File)),
  267    predicate_property(Module:Head, line_count(Line)).
  268locate(module(Module), Location) :-
  269    atom(Module),
  270    module_property(Module, file(Path)),
  271    (   module_property(Module, line_count(Line))
  272    ->  Location = #{file:Path, line:Line}
  273    ;   Location = #{file:Path}
  274    ).
  275locate(breakpoint(Id), Location) :-
  276    integer(Id),
  277    breakpoint_property(Id, clause(Ref)),
  278    (   breakpoint_property(Id, file(File)),
  279        breakpoint_property(Id, line_count(Line))
  280    ->  Location =  #{file:File, line:Line}
  281    ;   locate(clause(Ref), Location)
  282    ).
  283locate(clause(Ref), #{file:File, line:Line}) :-
  284    clause_property(Ref, file(File)),
  285    clause_property(Ref, line_count(Line)).
  286locate(clause(Ref, _PC), #{file:File, line:Line}) :- % TBD: use clause
  287    clause_property(Ref, file(File)),
  288    clause_property(Ref, line_count(Line)).
  289
  290
  291                 /*******************************
  292                 *             EDIT             *
  293                 *******************************/
  294
  295%!  do_edit_source(+Location)
  296%
  297%   Actually call the editor to edit Location, a list of Name(Value)
  298%   that contains file(File) and may contain line(Line). First the
  299%   multifile hook edit_source/1 is called. If this fails the system
  300%   checks for XPCE and the prolog-flag editor. If the latter is
  301%   built_in or pce_emacs, it will start PceEmacs.
  302%
  303%   Finally, it will get the editor to use from the prolog-flag
  304%   editor and use edit_command/2 to determine how this editor
  305%   should be called.
  306
  307do_edit_source(Location) :-             % hook
  308    edit_source(Location),
  309    !.
  310do_edit_source(Location) :-             % PceEmacs
  311    current_prolog_flag(editor, Editor),
  312    is_pceemacs(Editor),
  313    current_prolog_flag(gui, true),
  314    !,
  315    location_url(Location, URL),        % File[:Line[:LinePos]]
  316    run_pce_emacs(URL).
  317do_edit_source(Location) :-             % External editor
  318    external_edit_command(Location, Command),
  319    print_message(informational, edit(waiting_for_editor)),
  320    (   catch(shell(Command), E,
  321              (print_message(warning, E),
  322               fail))
  323    ->  print_message(informational, edit(make)),
  324        make
  325    ;   print_message(informational, edit(canceled))
  326    ).
  327
  328external_edit_command(Location, Command) :-
  329    #{file:File, line:Line} :< 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, S2),
  338    substitute('%d', Line,   S2, S),
  339    !,
  340    atom_codes(Command, S).
  341external_edit_command(Location, Command) :-
  342    #{file:File} :< Location,
  343    editor(Editor),
  344    file_base_name(Editor, EditorFile),
  345    file_name_extension(Base, _, EditorFile),
  346    edit_command(Base, Cmd),
  347    prolog_to_os_filename(File, OsFile),
  348    atom_codes(Cmd, S0),
  349    substitute('%e', Editor, S0, S1),
  350    substitute('%f', OsFile, S1, S),
  351    \+ substitute('%d', 1, S, _),
  352    !,
  353    atom_codes(Command, S).
  354external_edit_command(Location, Command) :-
  355    #{file:File} :< Location,
  356    editor(Editor),
  357    format(string(Command), '"~w" "~w"', [Editor, File]).
  358
  359is_pceemacs(pce_emacs).
  360is_pceemacs(built_in).
  361
  362%!  run_pce_emacs(+URL) is semidet.
  363%
  364%   Dynamically load and run emacs/1.
  365
  366run_pce_emacs(URL) :-
  367    autoload_call(in_pce_thread(autoload_call(emacs(URL)))).
  368
  369%!  editor(-Editor)
  370%
  371%   Determine the external editor to run.
  372
  373editor(Editor) :-                       % $EDITOR
  374    current_prolog_flag(editor, Editor),
  375    (   sub_atom(Editor, 0, _, _, $)
  376    ->  sub_atom(Editor, 1, _, 0, Var),
  377        catch(getenv(Var, Editor), _, fail), !
  378    ;   Editor == default
  379    ->  catch(getenv('EDITOR', Editor), _, fail), !
  380    ;   \+ is_pceemacs(Editor)
  381    ->  !
  382    ).
  383editor(Editor) :-                       % User defaults
  384    getenv('EDITOR', Editor),
  385    !.
  386editor(vi) :-                           % Platform defaults
  387    current_prolog_flag(unix, true),
  388    !.
  389editor(notepad) :-
  390    current_prolog_flag(windows, true),
  391    !.
  392editor(_) :-                            % No luck
  393    throw(error(existence_error(editor), _)).
  394
  395%!  edit_command(+Editor, -Command)
  396%
  397%   This predicate should specify the shell-command called to invoke
  398%   the user's editor. The following substitutions will be made:
  399%
  400%           | %e | Path name of the editor            |
  401%           | %f | Path name of the file to be edited |
  402%           | %d | Line number of the target          |
  403
  404
  405edit_command(vi,          '%e +%d \'%f\'').
  406edit_command(vi,          '%e \'%f\'').
  407edit_command(emacs,       '%e +%d \'%f\'').
  408edit_command(emacs,       '%e \'%f\'').
  409edit_command(notepad,     '"%e" "%f"').
  410edit_command(wordpad,     '"%e" "%f"').
  411edit_command(uedit32,     '%e "%f/%d/0"').      % ultraedit (www.ultraedit.com)
  412edit_command(jedit,       '%e -wait \'%f\' +line:%d').
  413edit_command(jedit,       '%e -wait \'%f\'').
  414edit_command(edit,        '%e %f:%d').          % PceEmacs client script
  415edit_command(edit,        '%e %f').
  416
  417edit_command(emacsclient, Command) :- edit_command(emacs, Command).
  418edit_command(vim,         Command) :- edit_command(vi,    Command).
  419edit_command(nvim,        Command) :- edit_command(vi,    Command).
  420
  421substitute(FromAtom, ToAtom, Old, New) :-
  422    atom_codes(FromAtom, From),
  423    (   atom(ToAtom)
  424    ->  atom_codes(ToAtom, To)
  425    ;   number_codes(ToAtom, To)
  426    ),
  427    append(Pre, S0, Old),
  428    append(From, Post, S0) ->
  429    append(Pre, To, S1),
  430    append(S1, Post, New),
  431    !.
  432substitute(_, _, Old, Old).
  433
  434
  435                 /*******************************
  436                 *            SELECT            *
  437                 *******************************/
  438
  439merge_locations(Locations0, Locations) :-
  440    append(Before, [L1|Rest], Locations0),
  441    L1 = Loc1-Spec1,
  442    select(L2, Rest, Rest1),
  443    L2 = Loc2-Spec2,
  444    same_location(Loc1, Loc2, Loc),
  445    merge_specs(Spec1, Spec2, Spec),
  446    !,
  447    append([Before, [Loc-Spec], Rest1], Locations1),
  448    merge_locations(Locations1, Locations).
  449merge_locations(Locations, Locations).
  450
  451same_location(L, L, L).
  452same_location(#{file:F1}, #{file:F2}, #{file:F}) :-
  453    best_same_file(F1, F2, F).
  454same_location(#{file:F1, line:Line}, #{file:F2}, #{file:F, line:Line}) :-
  455    best_same_file(F1, F2, F).
  456same_location(#{file:F1}, #{file:F2, line:Line}, #{file:F, line:Line}) :-
  457    best_same_file(F1, F2, F).
  458
  459best_same_file(F1, F2, F) :-
  460    catch(same_file(F1, F2), _, fail),
  461    !,
  462    atom_length(F1, L1),
  463    atom_length(F2, L2),
  464    (   L1 < L2
  465    ->  F = F1
  466    ;   F = F2
  467    ).
  468
  469merge_specs(Spec, Spec, Spec) :-
  470    !.
  471merge_specs(file(F1), file(F2), file(F)) :-
  472    best_same_file(F1, F2, F),
  473    !.
  474merge_specs(Spec1, Spec2, Spec) :-
  475    merge_specs_(Spec1, Spec2, Spec),
  476    !.
  477merge_specs(Spec1, Spec2, Spec) :-
  478    merge_specs_(Spec2, Spec1, Spec),
  479    !.
  480
  481merge_specs_(FileSpec, Spec, Spec) :-
  482    is_filespec(FileSpec).
  483
  484is_filespec(source_file(_)) => true.
  485is_filespec(Term),
  486    compound(Term),
  487    compound_name_arguments(Term, Alias, [_Arg]),
  488    user:file_search_path(Alias, _) => true.
  489is_filespec(_) =>
  490    fail.
  491
  492%!  select_location(+Pairs, +UserSpec, -Location) is semidet.
  493%
  494%   @arg Pairs is a list of `Location-Spec` pairs
  495%   @arg Location is a list of properties
  496
  497do_select_location(Pairs, Spec, Location) :-
  498    select_location(Pairs, Spec, Location),                % HOOK
  499    !,
  500    Location \== [].
  501do_select_location([], Spec, _) :-
  502    !,
  503    print_message(warning, edit(not_found(Spec))),
  504    fail.
  505do_select_location([#{file:File}-file(File)], _, Location) :-
  506    !,
  507    Location = #{file:File}.
  508do_select_location([Location-_Spec], _, Location) :-
  509    existing_location(Location),
  510    !.
  511do_select_location(Pairs, _, Location) :-
  512    foldl(number_location, Pairs, NPairs, 1, End),
  513    print_message(help, edit(select(NPairs))),
  514    (   End == 1
  515    ->  fail
  516    ;   Max is End - 1,
  517        user_selection(Max, I),
  518        memberchk(I-(Location-_Spec), NPairs)
  519    ).
  520
  521%!  existing_location(+Location) is semidet.
  522%
  523%   True when Location can be edited.  By   default  that means that the
  524%   file exists. This facility is hooked   to allow for alternative ways
  525%   to reach the source, e.g., by lazily downloading it.
  526
  527existing_location(Location) :-
  528    exists_location(Location),
  529    !.
  530existing_location(Location) :-
  531    #{file:File} :< Location,
  532    access_file(File, read).
  533
  534number_location(Pair, N-Pair, N, N1) :-
  535    Pair = Location-_Spec,
  536    existing_location(Location),
  537    !,
  538    N1 is N+1.
  539number_location(Pair, 0-Pair, N, N).
  540
  541user_selection(Max, I) :-
  542    user_select(Max, I),
  543    !.
  544user_selection(Max, I) :-
  545    print_message(help, edit(choose(Max))),
  546    read_number(Max, I).
  547
  548%!  read_number(+Max, -X) is semidet.
  549%
  550%   Read a number between 1 and Max. If Max < 10, use get_single_char/1.
  551
  552read_number(Max, X) :-
  553    Max < 10,
  554    !,
  555    get_single_char(C),
  556    put_code(user_error, C),
  557    between(0'0, 0'9, C),
  558    X is C - 0'0.
  559read_number(_, X) :-
  560    read_line_to_string(user_input, String),
  561    number_string(X, String).
  562
  563
  564                 /*******************************
  565                 *             MESSAGES         *
  566                 *******************************/
  567
  568:- multifile
  569    prolog:message/3.  570
  571prolog:message(edit(Msg)) -->
  572    message(Msg).
  573
  574message(not_found(Spec)) -->
  575    [ 'Cannot find anything to edit from "~p"'-[Spec] ],
  576    (   { atom(Spec) }
  577    ->  [ nl, '    Use edit(file(~q)) to create a new file'-[Spec] ]
  578    ;   []
  579    ).
  580message(select(NPairs)) -->
  581    { \+ (member(N-_, NPairs), N > 0) },
  582    !,
  583    [ 'Found the following locations:', nl ],
  584    sequence(target, [nl], NPairs).
  585message(select(NPairs)) -->
  586    [ 'Please select item to edit:', nl ],
  587    sequence(target, [nl], NPairs).
  588message(choose(_Max)) -->
  589    [ nl, 'Your choice? ', flush ].
  590message(waiting_for_editor) -->
  591    [ 'Waiting for editor ... ', flush ].
  592message(make) -->
  593    [ 'Running make to reload modified files' ].
  594message(canceled) -->
  595    [ 'Editor returned failure; skipped make/0 to reload files' ].
  596
  597target(0-(Location-Spec)) ==>
  598    [ ansi(warning, '~t*~3| ', [])],
  599    edit_specifier(Spec),
  600    [ '~t~32|' ],
  601    edit_location(Location, false),
  602    [ ansi(warning, ' (no source available)', [])].
  603target(N-(Location-Spec)) ==>
  604    [ ansi(bold, '~t~d~3| ', [N])],
  605    edit_specifier(Spec),
  606    [ '~t~32|' ],
  607    edit_location(Location, true).
  608
  609edit_specifier(Module:Name/Arity) ==>
  610    [ '~w:'-[Module],
  611      ansi(code, '~w/~w', [Name, Arity]) ].
  612edit_specifier(file(_Path)) ==>
  613    [ '<file>' ].
  614edit_specifier(source_file(_Path)) ==>
  615    [ '<loaded file>' ].
  616edit_specifier(include_file(_Path)) ==>
  617    [ '<included file>' ].
  618edit_specifier(Term) ==>
  619    [ '~p'-[Term] ].
  620
  621edit_location(Location, false) ==>
  622    { location_label(Location, Label) },
  623    [ ansi(warning, '~s', [Label]) ].
  624edit_location(Location, true) ==>
  625    { location_label(Location, Label),
  626      location_url(Location, URL)
  627    },
  628    [ url(URL, Label) ].
  629
  630location_label(Location, Label) :-
  631    #{file:File, line:Line} :< Location,
  632    !,
  633    short_filename(File, ShortFile),
  634    format(string(Label), '~w:~d', [ShortFile, Line]).
  635location_label(Location, Label) :-
  636    #{file:File} :< Location,
  637    !,
  638    short_filename(File, ShortFile),
  639    format(string(Label), '~w', [ShortFile]).
  640
  641location_url(Location, File:Line:LinePos) :-
  642    #{file:File, line:Line, linepos:LinePos} :< Location,
  643    !.
  644location_url(Location, File:Line) :-
  645    #{file:File, line:Line} :< Location,
  646    !.
  647location_url(Location, File) :-
  648    #{file:File} :< Location.
  649
  650%!  short_filename(+Path, -Spec) is det.
  651%
  652%   Spec is a way to refer to the file Path that is shorter. The path is
  653%   shortened by either taking  it  relative   to  the  current  working
  654%   directory or use one of the Prolog path aliases.
  655
  656short_filename(Path, Spec) :-
  657    working_directory(Here, Here),
  658    atom_concat(Here, Local0, Path),
  659    !,
  660    remove_leading_slash(Local0, Spec).
  661short_filename(Path, Spec) :-
  662    findall(LenAlias, aliased_path(Path, LenAlias), Keyed),
  663    keysort(Keyed, [_-Spec|_]).
  664short_filename(Path, Path).
  665
  666aliased_path(Path, Len-Spec) :-
  667    setof(Alias, file_alias_path(Alias), Aliases),
  668    member(Alias, Aliases),
  669    Alias \== autoload,             % confusing and covered by something else
  670    Term =.. [Alias, '.'],
  671    absolute_file_name(Term, Prefix,
  672                       [ file_type(directory),
  673                         file_errors(fail),
  674                         solutions(all)
  675                       ]),
  676    atom_concat(Prefix, Local0, Path),
  677    remove_leading_slash(Local0, Local1),
  678    remove_extension(Local1, Local2),
  679    unquote_segments(Local2, Local),
  680    atom_length(Local2, Len),
  681    Spec =.. [Alias, Local].
  682
  683file_alias_path(Alias) :-
  684    user:file_search_path(Alias, _).
  685
  686remove_leading_slash(Path, Local) :-
  687    atom_concat(/, Local, Path),
  688    !.
  689remove_leading_slash(Path, Path).
  690
  691remove_extension(File0, File) :-
  692    file_name_extension(File, Ext, File0),
  693    user:prolog_file_type(Ext, source),
  694    !.
  695remove_extension(File, File).
  696
  697unquote_segments(File, Segments) :-
  698    split_string(File, "/", "/", SegmentStrings),
  699    maplist(atom_string, SegmentList, SegmentStrings),
  700    maplist(no_quote_needed, SegmentList),
  701    !,
  702    segments(SegmentList, Segments).
  703unquote_segments(File, File).
  704
  705
  706no_quote_needed(A) :-
  707    format(atom(Q), '~q', [A]),
  708    Q == A.
  709
  710segments([Segment], Segment) :-
  711    !.
  712segments(List, A/Segment) :-
  713    append(L1, [Segment], List),
  714    !,
  715    segments(L1, A).
  716
  717
  718                 /*******************************
  719                 *        LOAD EXTENSIONS       *
  720                 *******************************/
  721
  722load_extensions :-
  723    load,
  724    fail.
  725load_extensions.
  726
  727:- load_extensions.