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)  2008-2013, 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_hotfix,
   37          [ load_hotfixes/1             % +Directory
   38          ]).   39:- autoload(library(apply),[maplist/2]).   40:- autoload(library(lists),[member/2,nth1/3]).   41:- autoload(library(option),[merge_options/3,option/2]).   42:- autoload(library(prolog_source),
   43	    [ prolog_open_source/2,
   44	      prolog_read_source_term/4,
   45	      prolog_close_source/1
   46	    ]).   47:- autoload(library(readutil),[read_line_to_codes/2]).   48
   49
   50/** <module> Load hotfixes into executables
   51
   52This library was developed to  deal   with  hotfixing  products that are
   53distributed as a Prolog saved state. It assumes the vendor is willing to
   54distribute hotfixes as Prolog source files.  These files are placed into
   55a directory. The  predicate  load_hotfixes/1   replaces  files  that are
   56loaded into the saved state.
   57
   58Resolution of the file to load is based on the module if the hotfix file
   59provides a module. If the hotfix file is not a module file and there are
   60multiple  loaded  source  files  with  the   same  name  from  different
   61directories, the hotfix directory  must   create  the  minimal directory
   62structure to make the paths unique. If omitted, this library will prompt
   63the user for the file that must be replaced.
   64
   65@tbd    This could be extended in several ways:
   66
   67            * Load hotfixes from a (encrypted) zip file
   68            * Use digital signatures and load over HTTP
   69            * Replace individual predicates
   70
   71@author Jan Wielemaker
   72*/
   73
   74%!  load_hotfixes(+Dir) is det.
   75%
   76%   Load all hotfixes that  have  not   yet  been  applied  into the
   77%   current state.
   78
   79load_hotfixes(Dir) :-
   80    absolute_file_name(Dir, DirPath,
   81                       [ file_type(directory),
   82                         access(read)
   83                       ]),
   84    phrase(prolog_source_files([DirPath]), Files),
   85    ensure_dirsep(DirPath, Common),
   86    maplist(apply_hotfix(Common), Files).
   87
   88
   89%!  prolog_source_files(+Dirs)// is det.
   90%
   91%   Find all Prolog source files in the given directory.
   92
   93prolog_source_files([]) --> !.
   94prolog_source_files([H|T]) -->
   95    !,
   96    prolog_source_files(H),
   97    prolog_source_files(T).
   98prolog_source_files(F) -->
   99    { exists_file(F),
  100      file_name_extension(_, Ext, F),
  101      user:prolog_file_type(Ext, prolog)
  102    },
  103    !,
  104    [F].
  105prolog_source_files(Dir) -->
  106    { exists_directory(Dir),
  107      !,
  108      atom_concat(Dir, '/*', Pattern),
  109      expand_file_name(Pattern, Members)
  110    },
  111    prolog_source_files(Members).
  112prolog_source_files(_) -->
  113    [].
  114
  115
  116%!  apply_hotfix(+HotfixDir, +File) is det.
  117%
  118%   Locate the hotfix and load it if it is newer. First step to find
  119%   the file we must replace is using  the module name, as these are
  120%   guaranteed to be unique in the Prolog process. If that fails, we
  121%   use the filename, but now we  can   get  multiple files with the
  122%   same name loaded  from  different   directories  as  candidates.
  123%   Finally, if no file matches, we load   the  file into the =user=
  124%   module.
  125
  126apply_hotfix(_HotfixDir, File) :-
  127    file_module(File, Module),
  128    module_property(Module, file(Loaded)),
  129    '$time_source_file'(Loaded, Time, _Type),
  130    !,
  131    time_file(File, HotfixTime),
  132    (   HotfixTime =\= Time
  133    ->  load_hotfix(File, Loaded)
  134    ;   true
  135    ).
  136apply_hotfix(HotfixDir, File) :-
  137    atom_concat(HotfixDir, Local, File),
  138    atom_concat(/, Local, SlashLocal),
  139    findall(Loaded-Time,
  140            (   '$time_source_file'(Loaded, Time, user),
  141                sub_atom(Loaded, _, _, 0, SlashLocal)
  142            ),
  143            Pairs),
  144    Pairs \== [],
  145    !,
  146    (   Pairs = [Loaded-Time]
  147    ->  true
  148    ;   select_file_to_reload(Pairs, Local, Loaded-Time)
  149    ),
  150    time_file(File, HotfixTime),
  151    (   HotfixTime =\= Time
  152    ->  load_hotfix(File, Loaded)
  153    ;   true
  154    ).
  155apply_hotfix(_HotfixDir, File) :-
  156    user:consult(File).
  157
  158
  159%!  ensure_dirsep(+Dir, -DirSlash) is det.
  160
  161ensure_dirsep(Dir0, Dir) :-
  162    (   sub_atom(Dir0, _, _, 0, /)
  163    ->  Dir = Dir0
  164    ;   atom_concat(Dir0, /, Dir)
  165    ).
  166
  167
  168%!  load_hotfix(+HotfixFile, +Loaded) is det.
  169%
  170%   Reload the HotfixFile, pretending we are reloading Loaded.
  171%
  172%   @see    make:reload_file/1
  173
  174load_hotfix(File, Loaded) :-
  175    time_file(File, Modified),
  176    setup_call_cleanup(
  177        open(File, read, In),
  178        load_hotfix_from_stream(Loaded, In, Modified),
  179        close(In)).
  180
  181load_hotfix_from_stream(Loaded, In, Modified) :-
  182    FixOptions = [ stream(In),
  183                   modified(Modified),
  184                   register(false)
  185                 ],
  186    set_stream(In, file_name(Loaded)),
  187    findall(M-Opts,
  188            source_file_property(Loaded, load_context(M, _, Opts)),
  189            Modules),
  190    (   Modules = [First-OptsFirst|Rest]
  191    ->  merge_options(FixOptions, OptsFirst, FirstOptions),
  192        load_stream(First:Loaded, FirstOptions),
  193        forall(member(Context-Opts, Rest),
  194               ( merge_options([if(not_loaded)|FirstOptions], Opts, ORest),
  195                 load_stream(Context:Loaded, ORest)
  196               ))
  197    ;   load_stream(user:Loaded, FixOptions)
  198    ).
  199
  200load_stream(Source, Options) :-
  201    option(stream(In), Options),
  202    setup_call_cleanup(
  203        stream_property(In, position(Pos)),
  204        load_files(Source, Options),
  205        set_stream_position(In, Pos)).
  206
  207%!  select_file_to_reload(+Pairs, +Local, -Pair) is det.
  208
  209select_file_to_reload(Pairs, Local, Pair) :-
  210    format(user_error,
  211           'Hotfix ~w matches multiple loaded files.~n~n',
  212           [Local]),
  213    forall(nth1(I, Pairs, File-_),
  214           format(user_error, '~t~d~6| ~w~n', [I, File])),
  215    repeat,
  216       format(user_error, '~nPlease select (\'s\' skips hotfix)? ', []),
  217       read_line_to_codes(user_input, Line),
  218       (   Line == end_of_file
  219       ->  halt(1)
  220       ;   atom_codes(s, Line)
  221       ->  !, fail
  222       ;   catch(number_codes(N, Line), _, fail)
  223       ),
  224       nth1(N, Pairs, Pair),
  225    !.
  226
  227%!  file_module(+File, -Module) is semidet.
  228%
  229%   True if Module is the module defined in File.
  230
  231file_module(File, Module) :-
  232    catch(file_module_guarded(File, Module), _, fail).
  233
  234file_module_guarded(File, Module) :-
  235    setup_call_cleanup(
  236        prolog_open_source(File, In),
  237        prolog_read_source_term(In, _, Expanded, []),
  238        prolog_close_source(In)),
  239    Expanded = (:- module(Module, _))