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)  2020-2025, VU University Amsterdam
    7                              CWI, 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_deps,
   38          [ file_autoload_directives/3,      % +File, -Directives, +Options
   39            file_auto_import/2               % +File, +Options
   40          ]).   41:- use_module(library(apply), [convlist/3, maplist/3, exclude/3]).   42:- use_module(library(filesex), [copy_file/2]).   43:- use_module(library(lists), [select/3, append/3, member/2]).   44:- use_module(library(option), [option/2, option/3]).   45:- use_module(library(pairs), [group_pairs_by_key/2]).   46:- use_module(library(pprint), [print_term/2]).   47:- use_module(library(prolog_code), [pi_head/2]).   48:- use_module(library(prolog_source),
   49              [ file_name_on_path/2,
   50                path_segments_atom/2,
   51                prolog_open_source/2,
   52                prolog_read_source_term/4,
   53                prolog_close_source/1
   54              ]).   55:- use_module(library(prolog_xref),
   56              [ xref_source/1,
   57                xref_module/2,
   58                xref_called/4,
   59                xref_defined/3,
   60                xref_built_in/1,
   61                xref_public_list/3
   62              ]).   63:- use_module(library(readutil), [read_file_to_string/3]).   64:- use_module(library(solution_sequences), [distinct/2]).   65
   66/** <module> Compute file dependencies
   67
   68This module computes  file  dependencies  for   _modules_  as  a  set of
   69directives.
   70*/
   71
   72:- multifile user:file_search_path/2.   73
   74user:file_search_path(noautoload, library(.)).
   75user:file_search_path(noautoload, library(semweb)).
   76user:file_search_path(noautoload, library(lynx)).
   77user:file_search_path(noautoload, library(tipc)).
   78user:file_search_path(noautoload, library(cql)).
   79user:file_search_path(noautoload, library(http)).
   80user:file_search_path(noautoload, library(dcg)).
   81user:file_search_path(noautoload, library(unicode)).
   82user:file_search_path(noautoload, library(clp)).
   83user:file_search_path(noautoload, library(pce(prolog/lib))).
   84
   85
   86%!  file_autoload_directives(+File, -Directives, +Options) is det.
   87%
   88%   Compute the dependencies as autoload/2 directives.  Options
   89%
   90%     - missing(+Bool)
   91%       If `true` (default `false`), only generate directives
   92%       for called predicates that are not already imported.
   93%
   94%     - directive(+Directive)
   95%       Directive to use for adding dependencies.  Defined
   96%	options are:
   97%
   98%       - use_autoload/2
   99%         (Default).  This uses use_module/2 for files that
  100%         cannot be imported using use_autoload/2.
  101%       - use_autoload/1
  102%         This uses use_module/1 for files that cannot be
  103%	  imported using use_autoload/1.
  104%       - use_module/2
  105%       - use_module/1
  106%
  107%     - update(Old)
  108%       Updated an existing set of directives.  The returned
  109%       set of Directive starts with copies of Old.  If a
  110%       member of Old is autoload/2 or use_module/2, new
  111%       dependencies are added at the end of this list.
  112%       New dependent files are added after the modified
  113%       copies of Old.  Declared dependencies are never
  114%       removed, even if no proof of usage is found.
  115%
  116%       If no directive(+Directive) option is provided a
  117%       default is determined from the given directives.
  118
  119file_autoload_directives(File, Directives, Options) :-
  120    xref_source(File),
  121    findall(Head, distinct(Head, undefined(File, Head, Options)), Missing0),
  122    clean_missing(Missing0, Missing),
  123    option(update(Old), Options, []),
  124    convlist(missing_autoload(File, Old), Missing, Pairs),
  125    keysort(Pairs, Pairs1),
  126    group_pairs_by_key(Pairs1, Grouped),
  127    directives(File, Grouped, Directives, Options).
  128
  129%!  undefined(+File, -Callable, +Options)
  130%
  131%   Callable is called in File, but no   definition can be found. If
  132%   File is not a module file we   consider other files that are not
  133%   module files.
  134
  135undefined(File, Undef, Options) :-
  136    xref_module(File, _),
  137    !,
  138    xref_called_cond(File, Undef, Cond),
  139    \+ (   available(File, Undef, How, Options),
  140           How \== plain_file
  141       ),
  142    included_if_defined(Cond, Undef),
  143    Undef \= (_:_).
  144undefined(File, Undef, Options) :-
  145    xref_called_cond(File, Undef, Cond),
  146    \+ available(File, Undef, _, Options),
  147    included_if_defined(Cond, Undef),
  148    Undef \= (_:_).
  149
  150%!  included_if_defined(+Condition, +Callable) is semidet.
  151
  152included_if_defined(true, _)  :- !.
  153included_if_defined(false, _) :- !, fail.
  154included_if_defined(fail, _)  :- !, fail.
  155included_if_defined(current_predicate(Name/Arity), Callable) :-
  156    \+ functor(Callable, Name, Arity),
  157    !.
  158included_if_defined(\+ Cond, Callable) :-
  159    !,
  160    \+ included_if_defined(Cond, Callable).
  161included_if_defined((A,B), Callable) :-
  162    !,
  163    included_if_defined(A, Callable),
  164    included_if_defined(B, Callable).
  165included_if_defined((A;B), Callable) :-
  166    !,
  167    (   included_if_defined(A, Callable)
  168    ;   included_if_defined(B, Callable)
  169    ).
  170
  171xref_called_cond(Source, Callable, Cond) :-
  172    xref_called(Source, Callable, By, Cond),
  173    By \= Callable.                 % recursive calls
  174
  175%!  available(+File, +Callable, -HowDefined, +Options)
  176%
  177%   True if Callable is available in File.
  178
  179available(File, Called, How, Options) :-
  180    xref_defined(File, Called, How0),
  181    (   How0 = imported(_)
  182    ->  option(missing(true), Options)
  183    ;   true
  184    ),
  185    !,
  186    How = How0.
  187available(_, Called, How, _) :-
  188    built_in_predicate(Called),
  189    !,
  190    How = builtin.
  191available(_, Called, How, _) :-
  192    Called = _:_,
  193    defined(_, Called),
  194    !,
  195    How = module_qualified.
  196available(_, M:G, How, _) :-
  197    defined(ExportFile, G),
  198    xref_module(ExportFile, M),
  199    !,
  200    How = module_overruled.
  201available(_, Called, How, _) :-
  202    defined(ExportFile, Called),
  203    \+ xref_module(ExportFile, _),
  204    !,
  205    How == plain_file.
  206
  207%!  built_in_predicate(+Callable)
  208%
  209%   True if Callable is a built-in
  210
  211built_in_predicate(Goal) :-
  212    strip_module(Goal, _, Plain),
  213    xref_built_in(Plain).
  214
  215%!  defined(?File, ?Callable)
  216%
  217%   True if Callable is defined in File and not imported.
  218
  219defined(File, Callable) :-
  220    xref_defined(File, Callable, How),
  221    How \= imported(_).
  222
  223%!  clean_missing(+Missing0, -Missing) is det.
  224%
  225%   Hack to deal with library(main) and library(optparse) issues.
  226%
  227%   @tbd Needs a more fundamental solution.
  228
  229clean_missing(Missing0, Missing) :-
  230    memberchk(main, Missing0),
  231    memberchk(argv_options(_,_,_), Missing0),
  232    !,
  233    exclude(argv_option_hook, Missing0, Missing).
  234clean_missing(Missing, Missing).
  235
  236argv_option_hook(opt_type(_,_,_)).
  237argv_option_hook(opt_help(_,_)).
  238argv_option_hook(opt_meta(_,_)).
  239
  240
  241		 /*******************************
  242		 *       GENERATE OUTPUT	*
  243		 *******************************/
  244
  245missing_autoload(Src, _, Head, From-Head) :-
  246    xref_defined(Src, Head, imported(From)),
  247    !.
  248missing_autoload(Src, Directives, Head, File-Head) :-
  249    src_file(Src, SrcFile),
  250    member(:-(Dir), Directives),
  251    directive_file(Dir, FileSpec),
  252    absolute_file_name(FileSpec, File,
  253                       [ file_type(prolog),
  254                         file_errors(fail),
  255                         relative_to(SrcFile),
  256                         access(read)
  257                       ]),
  258    xref_public_list(File, SrcFile, [exports(Exports)]),
  259    member(PI, Exports),
  260    is_pi(PI),
  261    pi_head(PI, Head),
  262    !.
  263missing_autoload(_Src, _, Head, File-Head) :-
  264    predicate_property(Head, autoload(File0)),
  265    !,
  266    (   absolute_file_name(File0, File1,
  267                           [ access(read),
  268                             file_type(prolog),
  269                             file_errors(fail)
  270                           ])
  271    ->  qlf_pl_file(File1, File)
  272    ;   File = File0
  273    ).
  274missing_autoload(_Src, _, Head, File-Head) :-
  275    noautoload(Head, File),
  276    !.
  277missing_autoload(_Src, _, Head, _) :-
  278    pi_head(PI, Head),
  279    print_message(warning,
  280                  error(existence_error(procedure, PI), _)),
  281    fail.
  282
  283:- if(exists_source(library(pce))).  284:- autoload(library(pce), [get/3]).  285src_file(@(Ref), File) =>
  286    get(?(@(Ref), file), absolute_path, File).
  287:- endif.  288src_file(File0, File) =>
  289    File = File0.
  290
  291%!  directives(+File, +FileAndHeads, -Directives, +Options) is det.
  292%
  293%   Assemble the final set of directives. Uses the option update(Old).
  294
  295directives(File, FileAndHeads, Directives, Options) :-
  296    option(update(Old), Options, []),
  297    phrase(update_directives(Old, FileAndHeads, RestDeps, File),
  298           Directives, Rest),
  299    update_style(Old, Options, Options1),
  300    maplist(directive(Options1), RestDeps, Rest0),
  301    sort(Rest0, Rest).
  302
  303update_directives([], Deps, Deps, _) -->
  304    [].
  305update_directives([:-(H)|T], Deps0, Deps, File) -->
  306    { update_directive(File, H, Deps0, Deps1, Directive) },
  307    !,
  308    [ :-(Directive) ],
  309    update_directives(T, Deps1, Deps, File).
  310update_directives([H|T], Deps0, Deps, File) -->
  311    [ H ],
  312    update_directives(T, Deps0, Deps, File).
  313
  314update_directive(Src, Dir0, Deps0, Deps, Dir) :-
  315    src_file(Src, SrcFile),
  316    directive_file(Dir0, FileSpec),
  317    absolute_file_name(FileSpec, File,
  318                       [ file_type(prolog),
  319                         file_errors(fail),
  320                         relative_to(SrcFile),
  321                         access(read)
  322                       ]),
  323    qlf_pl_file(File, PlFile),
  324    select(DepFile-Heads, Deps0, Deps),
  325    same_dep_file(DepFile, PlFile),
  326    !,
  327    (   Dir0 =.. [Pred,File0,Imports]
  328    ->  xref_public_list(PlFile, SrcFile, [exports(Exports)]),
  329        maplist(head_pi(Exports), Heads, PIs),
  330        subtract_pis(PIs, Imports, New),
  331        append(Imports, New, NewImports),
  332        Dir =.. [Pred,File0,NewImports]
  333    ;   Dir = Dir0
  334    ).
  335
  336directive_file(use_module(File),   File).
  337directive_file(use_module(File,_), File).
  338directive_file(autoload(File),     File).
  339directive_file(autoload(File,_),   File).
  340
  341qlf_pl_file(File, PlFile) :-
  342    file_name_extension(_Base, Ext, File),
  343    user:prolog_file_type(Ext, qlf),
  344    !,
  345    '$qlf_module'(File, Info),
  346    PlFile = Info.get(file).
  347qlf_pl_file(File, File).
  348
  349same_dep_file(File, File) :-
  350    !.
  351same_dep_file(Dep, _File) :-
  352    exists_file(Dep),
  353    !,
  354    fail.
  355same_dep_file(Dep, File) :-
  356    user:prolog_file_type(Ext, prolog),
  357    file_name_extension(Dep, Ext, DepFile),
  358    same_file(DepFile, File),
  359    !.
  360
  361is_pi(Name/Arity), atom(Name), integer(Arity) => true.
  362is_pi(Name//Arity), atom(Name), integer(Arity) => true.
  363is_pi(_) => fail.
  364
  365%!  head_pi(+Exports, +Head, -PI) is det.
  366
  367head_pi(PIs, Head, PI) :-
  368    head_pi(Head, PI),
  369    memberchk(PI, PIs),
  370    !.
  371head_pi(_PIs, Head, PI) :-
  372    pi_head(PI, Head).
  373
  374head_pi(Head, PI) :-
  375    pi_head(PI0, Head),
  376    (   PI = PI0
  377    ;   dcg_pi(PI0, PI)
  378    ).
  379
  380dcg_pi(Module:Name/Arity, PI), integer(Arity), Arity >= 2 =>
  381    DCGArity is Arity - 2,
  382    PI = Module:Name//DCGArity.
  383dcg_pi(Name/Arity, PI), integer(Arity), Arity >= 2 =>
  384    DCGArity is Arity - 2,
  385    PI = Name//DCGArity.
  386dcg_pi(_/Arity, _), integer(Arity) =>
  387    fail.
  388
  389%!  subtract_pis(+Set, +Delete, -Result) is det.
  390
  391subtract_pis([], _, R) =>
  392    R = [].
  393subtract_pis([H|T], D, R) =>
  394    (   member(E, D),
  395        same_pi(H, E)
  396    ->  subtract_pis(T, D, R)
  397    ;   R = [H|R1],
  398        subtract_pis(T, D, R1)
  399    ).
  400
  401same_pi(PI, PI) => true.
  402same_pi(Name/A1, Name//A2) => A1 =:= A2+2.
  403same_pi(Name//A1, Name/A2) => A1 =:= A2-2.
  404same_pi(_,_) => fail.
  405
  406
  407%!  update_style(+OldDirectives, +Options0, -Options)
  408%
  409%   Determine  the  directive  to  use    for   new  dependencies.  This
  410%   establishes a default based on existing dependencies.
  411
  412update_style(_Old, Options, Options) :-
  413    option(directive(_), Options),
  414    !.
  415update_style(Old, Options, [directive(autoload/2)|Options]) :-
  416    memberchk((:- autoload(_,_)), Old),
  417    !.
  418update_style(Old, Options, [directive(autoload/1)|Options]) :-
  419    memberchk((:- autoload(_)), Old),
  420    !.
  421update_style(Old, Options, [directive(use_module/2)|Options]) :-
  422    memberchk((:- use_module(_,_)), Old),
  423    !.
  424update_style(Old, Options, [directive(use_module/1)|Options]) :-
  425    memberchk((:- use_module(_)), Old),
  426    !.
  427update_style(_, Options, Options).
  428
  429
  430%!  directive(+Options, +FileAndHeads, -Directive)
  431%
  432%   Create a directive to import Heads from File.
  433
  434directive(Options, File-Heads, Directive) :-
  435    file_name_extension(File, pl, LibFile),
  436    file_name_on_path(LibFile, Lib0),
  437    segments(Lib0, Lib),
  438    maplist(pi_head, PIs, Heads),
  439    make_directive(Lib, PIs, Directive, Options).
  440
  441segments(Term0, Term) :-
  442    Term0 =.. [Alias,Atom],
  443    path_segments_atom(Segments, Atom),
  444    format(atom(Atom), '~q', [Segments]),
  445    !,
  446    Term =.. [Alias,Segments].
  447segments(FilePL, File) :-
  448    atom(FilePL),
  449    file_name_extension(File, pl, FilePL),
  450    !.
  451segments(Term, Term).
  452
  453:- multifile
  454    prolog:no_autoload_module/1.  455
  456make_directive(Lib, Import, (:- use_module(Lib, Import)), Options) :-
  457    option(directive(use_module/2), Options, use_autoload/2),
  458    !.
  459make_directive(Lib, _Import, (:- use_module(Lib)), Options) :-
  460    option(directive(use_module/1), Options, use_autoload/2),
  461    !.
  462make_directive(Lib, _Import, (:- use_module(Lib)), Options) :-
  463    option(directive(use_autoload/1), Options, use_autoload/2),
  464    prolog:no_autoload_module(Lib),
  465    !.
  466make_directive(Lib, Import, (:- use_module(Lib, Import)), _) :-
  467    prolog:no_autoload_module(Lib),
  468    !.
  469make_directive(Lib, _Import, (:- autoload(Lib)), Options) :-
  470    option(directive(use_autoload/1), Options, use_autoload/2),
  471    !.
  472make_directive(Lib, Import, (:- autoload(Lib, Import)), _).
  473
  474
  475		 /*******************************
  476		 *          NO AUTOLOAD		*
  477		 *******************************/
  478
  479:- dynamic
  480    library_index/3,                % Head x Module x Path
  481    autoload_directories/1,         % List
  482    index_checked_at/1.             % Time
  483:- volatile
  484    library_index/3,
  485    autoload_directories/1,
  486    index_checked_at/1.  487
  488%!  noautoload(+Head, -File) is semidet.
  489%
  490%   True when Head can be loaded from   File.  Where the autoload system
  491%   only considers the autoload directories,   this version searches all
  492%   indexed directories.
  493
  494noautoload(Head, File) :-
  495    functor(Head, Name, Arity),
  496    functor(GenHead, Name, Arity),
  497    context_module(Here),
  498    '$autoload':load_library_index(Here:Name, Arity, Here:noautoload('INDEX')),
  499    library_index(GenHead, _, File),
  500    !.
  501
  502
  503		 /*******************************
  504		 *           REPLACE		*
  505		 *******************************/
  506
  507%!  file_auto_import(+File, +Options)
  508%
  509%   Update the autoload/2 directives for File. This predicate __modifies
  510%   the file in place__. Defined options are:
  511%
  512%     - backup(+Extension)
  513%       Create a backup of File using Extension.
  514
  515file_auto_import(File, Options) :-
  516    absolute_file_name(File, Path,
  517                       [ file_type(prolog),
  518                         access(read)
  519                       ]),
  520    file_autoload_directives(Path, Directives, Options),
  521    (   option(backup(Ext), Options)
  522    ->  file_name_extension(Path, Ext, Old),
  523        copy_file(Path, Old)
  524    ;   true
  525    ),
  526    Edit = _{import:Directives, done:_},
  527    (   has_import(Path)
  528    ->  edit_file(Old, Path, Edit.put(replace,true))
  529    ;   edit_file(Old, Path, Edit.put(new,true))
  530    ).
  531
  532has_import(InFile) :-
  533    setup_call_cleanup(
  534        prolog_open_source(InFile, In),
  535        (   repeat,
  536            prolog_read_source_term(In, Term, _Expanded, []),
  537            (   Term == end_of_file
  538            ->  !
  539            ;    true
  540            )
  541        ),
  542        prolog_close_source(In)),
  543    nonvar(Term),
  544    import_directive(Term),
  545    !.
  546
  547import_directive((:- use_module(_))).
  548import_directive((:- use_module(_, _))).
  549
  550%!  rewrite_term(+In, -Keep, -OutList, +Options) is semidet.
  551
  552rewrite_term(Never,_,_,_) :-
  553    never_rewrite(Never),
  554    !,
  555    fail.
  556rewrite_term(Import,false,[],Options) :-
  557    Options.done == true,
  558    !,
  559    import_directive(Import).
  560rewrite_term(In,false,Directives,Options) :-
  561    import_directive(In),
  562    !,
  563    append(Options.import, [nl], Directives),
  564    Options.done = true.
  565rewrite_term(In,true,Directives,Options) :-
  566    In = (:- module(_,_)),
  567    Options.get(new) == true,
  568    !,
  569    append(Options.import, [nl], Directives),
  570    Options.done = true.
  571
  572never_rewrite((:- use_module(_, []))).
  573
  574edit_file(InFile, OutFile, Options) :-
  575    read_file_to_string(InFile, String, []),
  576    setup_call_cleanup(
  577        prolog_open_source(InFile, In),
  578        setup_call_cleanup(
  579            open(OutFile, write, Out),
  580            rewrite(In, Out, String, Options),
  581            close(Out)),
  582        prolog_close_source(In)).
  583
  584rewrite(In, Out, String, Options) :-
  585    prolog_read_source_term(
  586        In, Term, _Expanded,
  587        [ term_position(StartPos),
  588          subterm_positions(TermPos),
  589          comments(Comments)
  590        ]),
  591    stream_position_data(char_count, StartPos, StartChar),
  592    copy_comments(Comments, StartChar, String, Out),
  593    (   Term == end_of_file
  594    ->  true
  595    ;   (   nonvar(Term),
  596            rewrite_term(Term, Keep, List, Options)
  597        ->  (   Keep == true
  598            ->  copy_term_string(TermPos, String, Out)
  599            ;   true
  600            ),
  601            forall(member(T, List),
  602                   output_term(Out, T)),
  603            (   append(_, [nl], List)
  604            ->  skip_blanks(In)
  605            ;   true
  606            )
  607        ;   copy_term_string(TermPos, String, Out)
  608        ),
  609        rewrite(In, Out, String, Options)
  610    ).
  611
  612output_term(Out, nl) :-
  613    !,
  614    nl(Out).
  615output_term(Out, Term) :-
  616    print_term(Term, [output(Out)]),
  617    format(Out, '.~n', []).
  618
  619copy_comments([Pos-H|T], StartChar, String, Out) :-
  620    stream_position_data(char_count, Pos, Start),
  621    Start < StartChar,
  622    !,
  623    string_length(H, Len),
  624    sub_string(String, Start, Len, _, Comment),
  625    End is Start+Len+1,
  626    layout_after(End, String, Layout),
  627    format(Out, '~s~s', [Comment, Layout]),
  628    copy_comments(T, StartChar, String, Out).
  629copy_comments(_, _, _, _).
  630
  631copy_term_string(TermPos, String, Out) :-
  632    arg(1, TermPos, Start),
  633    arg(2, TermPos, End),
  634    Len is End - Start,
  635    sub_string(String, Start, Len, _, TermString),
  636    End1 is End + 1,
  637    full_stop_after(End1, String, Layout),
  638    format(Out, '~s~s', [TermString, Layout]).
  639
  640layout_after(Index, String, [H|T]) :-
  641    string_code(Index, String, H),
  642    code_type(H, space),
  643    !,
  644    Index2 is Index+1,
  645    layout_after(Index2, String, T).
  646layout_after(_, _, []).
  647
  648full_stop_after(Index, String, [H|T]) :-
  649    string_code(Index, String, H),
  650    Index2 is Index+1,
  651    (   code_type(H, space)
  652    ->  !, full_stop_after(Index2, String, T)
  653    ;   H == 0'.
  654    ->  !, layout_after(Index2, String, T)
  655    ).
  656full_stop_after(_, _, []).
  657
  658skip_blanks(In) :-
  659    peek_code(In, C),
  660    code_type(C, space),
  661    !,
  662    get_code(In, _),
  663    skip_blanks(In).
  664skip_blanks(_)