1/*****************************************************************************
    2 * This file is part of the Prolog Development Tool (PDT)
    3 * 
    4 * WWW: http://sewiki.iai.uni-bonn.de/research/pdt/start
    5 * Mail: pdt@lists.iai.uni-bonn.de
    6 * Copyright (C): 2004-2012, CS Dept. III, University of Bonn
    7 * 
    8 * All rights reserved. This program is  made available under the terms
    9 * of the Eclipse Public License v1.0 which accompanies this distribution,
   10 * and is available at http://www.eclipse.org/legal/epl-v10.html
   11 * 
   12 ****************************************************************************/
   13
   14:- module( ctc_util_files, [
   15     consult_if_not_yet/2,            % (File, Head)
   16     export_goal_output/2,            % (File,Goal)
   17                                        % <-- OBSOLETE, use with_output_to_file/2 instead
   18     with_output_to_file/2,           % (File,Goal)
   19     with_output_to_folder/2,         % (+Folder,+Call)           FileName=Functor+Time
   20     with_output_to_folder/3,         % (+Folder,-FileName,+Call) FileName=Functor+Time
   21     report_to_file_ctc/1,            % (CallLiteral) As above but in CTC_HOME directory 
   22                                        % <-- OBSOLETE, use with_output_to_file/2 instead
   23     report_to_file_in_ctchome/1,     % (CallLiteral) As above but in CTC_HOME directory
   24     report_to_file_in_ctchome/2,     % (CallLiteral,File) As above but tell which file
   25     create_timestamped_file_path/4,  % (Folder,Prefix,Suffix,File)
   26     create_timestamped_folder_path/2 % (Folder,Timestamped)
   27] ).   28
   29% Conditional loading:
   30
   31:- use_module(library(memfile)).   32:- use_module(logging).   33:- use_module(count).   34
   35:- module_transparent consult_if_not_yet/2.   36
   37consult_if_not_yet(File,Head) :-
   38    clause(Head,_),
   39    predicate_loaded_from(Head,F),
   40    !,
   41    (   current_prolog_flag(verbose_consult, false)
   42        ->  true
   43         ;  report_already_loaded(Head,F,File)
   44    ).
   45consult_if_not_yet(File,_) :-
   46    consult(File),
   47    !.
   48consult_if_not_yet(File,_) :-
   49    format(' *** ERROR loading ~k. ~n', [File]).   
   50
   51
   52/*
   53 * predicate_loaded_from(+Head,?File)
   54 *   Return in Arg2 
   55 *    - the File from which the predicate with head Arg1 was loaded 
   56 *      (if the predicate is not 'multifile') or
   57 *    - 'multifile(F)' if the predicate is multifile and F is a file
   58 *       from which a definition was loaded or
   59 *    - 'unknown' (if the predicate was created dynamically).
   60 */ 
   61predicate_loaded_from(Head,File) :- predicate_property(Head,file(F)),
   62                                    ( predicate_property(Head,multifile)
   63                                      -> File = multifile(F)
   64                                       ; File = F
   65                                    ).
   66predicate_loaded_from(Head,File) :- predicate_property(Head,_),
   67                                    File = unknown.
   68
   69/*
   70 * Report that predicate Arg1 has already been loaded from 
   71 * file Arg2 instead of file Arg3.
   72 */
   73report_already_loaded(Head,F1,F2) :-
   74    functor(Head,Fkt,N),
   75    format(' *** Definition of ~a/~a  *not* loaded from ~k~n        because it is already loaded from ~k~n', [Fkt,N,F2,F1]).
   76
   77/*
   78 * ctc_home_dir(CTCHomeOrPWD)
   79 *   Get the value of CTC home directory in an 
   80 *   operating system independent syntax. If it
   81 *   is undefined, return the current working directory. 
   82 */
   83ctc_home_dir(Dir) :- 
   84    (  file_search_path(ctcore,HomeOS)
   85    -> prolog_to_os_filename(Dir, HomeOS)
   86    ;  pwd(Dir)
   87    ).
   88
   89% Strange but works. Copied from SWI-Prolog library predicate shell:pwd/0.
   90pwd(Path) :-  
   91	absolute_file_name('', Path).
   92	
   93/*
   94 * report_to_file_in_ctchome(+Call : a single literal)
   95 * report_to_file_in_ctchome(+Call : a single literal, -File)
   96 *
   97 *   The same as with_output_to_folder but with Folder
   98 *   parameter set to CTC home direcory.
   99 */
  100 :- module_transparent report_to_file_in_ctchome/1,
  101                       report_to_file_in_ctchome/2,
  102                       report_to_file_ctc/1.  103 
  104report_to_file_in_ctchome(Call) :- 
  105   report_to_file_in_ctchome(Call,_).
  106   
  107report_to_file_in_ctchome(Call,File) :-
  108   ctc_home_dir(CTCHome),
  109   with_output_to_folder(CTCHome,File,Call).
  110
  111% OBSOLETE, use the above instead.
  112report_to_file_ctc(Call) :- report_to_file_in_ctchome(Call).
 with_input_from(+Source, :Goal) is semidet
Temporarily switch current input to object specified by Source while calling Goal as in once/1. Source is a term like that supplied to with_output_to/2 and can be any of:

Author: Samer Abdallah (published on SWI-Prolog mailing list, 10 Aug 2010).

  127with_input_from(atom(A),Goal) :- !,
  128   setup_call_cleanup(
  129      atom_to_memory_file(A,MF),
  130      setup_call_cleanup(
  131         open_memory_file(MF,read,S),
  132         with_input_from(S,Goal),
  133         close(S)
  134      ),
  135      free_memory_file(MF)    
  136   ).  
  137       
  138with_input_from(codes(Codes),G) :- !, atom_codes(A,Codes), with_input_from(atom(A),G).
  139with_input_from(chars(Chars),G) :- !, atom_chars(A,Chars), with_input_from(atom(A),G).
  140with_input_from(string(Str),G)  :- !, string_to_atom(Str,A), with_input_from(atom(A),G).
  141       
  142with_input_from(S,G) :- is_stream(S), !,
  143   current_input(S0),
  144   setup_call_cleanup( set_input(S), once(G), set_input(S0)).
  145
  146
  147/*
  148 * with_output_to_folder(+Directory: Path,        +Call : a single literal)
  149 * with_output_to_folder(+Directory: Path, -File, +Call : a single literal)
  150 *
  151 *   Find all solutions for Call, write them  followed by the number of 
  152 *   solutions to a file whose name is prefixed by the functor of the 
  153 *   call. Create the file in the directory Directory.
  154 *   
  155 *   Report the file name on stdout. In the 3-argument version
  156 *   return the file name in the second argument. 
  157 */ 
  158 :- module_transparent with_output_to_folder/2,
  159                       with_output_to_folder/3,
  160                       report_to_file/2.  161                       
  162with_output_to_folder(Folder,Call) :-
  163   with_output_to_folder(Folder,_,Call).
  164  
  165with_output_to_folder(Folder,File,Call) :-
  166   functor(Call,Functor,_),
  167   atomic_list_concat([Functor,'-'],Prefix),
  168   create_timestamped_file_path(Folder,Prefix,'.txt',File),
  169   export_all_results(File, Call),            
  170   log_on_stdout('Report written to file~n~a~n',[File]).
  171
  172% OBSOLETE, use the above instead.
  173report_to_file(Folder,Call) :- with_output_to_folder(Folder,Call).
  174
  175
  176/*
  177 * export_all_results(+File, +Goal)
  178 *   Open an output stream for File and redirect the  output
  179 *   of the goal to that stream. Find all solution for Goal,
  180 *   report the number of solutions and print each solution on 
  181 *   a separate line. Close the stream afterwards.
  182 *
  183 *   +File is a file in Unix notation (with slashes "/" as 
  184 *   separators). On Windows, the path may start with the 
  185 *   typical single letter followed by a colon, e.g. 
  186 *   'C:/folder/file.pl'
  187 */
  188:- module_transparent export_all_results/2.  189                       
  190export_all_results(File, Goal) :-
  191   with_output_to_file(File, 
  192       ( count(Goal,N),  % enforces calculating all results
  193         format('Found ~a results.~n',[N]),
  194         forall(Goal, writeln(Goal)),
  195         nl
  196       )
  197    ).
 with_output_to_file(+File, +Mode, +Goal)
Open an output stream for File in mode Mode (Mode = write | append), and redirect all output of the goal to that stream. Close it afterwards even if the Goal exited with an exception. CAUTION: If you choose Mode = write, the previous contents of the file will be overwritten!
  207:- module_transparent with_output_to_file/3.  208
  209with_output_to_file(File,Mode,Goal) :- 
  210   setup_call_cleanup( open(File, Mode, Stream),     % setup
  211                       with_output_to(Stream,Goal),  % call
  212                       close(Stream)                 % cleanup
  213   ).
  214
  215
  216% -- OBSOLETE, use with_output_to_file/3 instead:
  217:- module_transparent with_output_to_file/2, export_goal_output/2.  218with_output_to_file(File,Goal) :-  with_output_to_file(File,write,Goal).
  219export_goal_output(File,Goal)  :-  with_output_to_file(File,write,Goal).
  220
  221   
  222% Portable implementation of the above predicate
  223% (without SWI-specific "with_otput_to"):
  224%
  225%with_output_to_file(File,Goal) :- 
  226%    telling(CurrentOutput),
  227%    tell(File),
  228%      once(Goal),
  229%    told,
  230%    tell(CurrentOutput).
  231        
  232/*
  233 * Return in Arg4 the path to a unique file in folder Arg1.
  234 * The file name is created from the prefix passed
  235 * in Arg2 by appending the time of the invocation of this 
  236 * predicate and the sufix from Arg3.  
  237 */
  238create_timestamped_file_path(Directory,Prefix,Suffix,FilePath) :-
  239    create_timestamp(Timestamp),
  240    atomic_list_concat([Directory,'/',Prefix,Timestamp,Suffix],FilePath).
  241
  242create_timestamped_folder_path(Directory,Timestamped) :-
  243    create_timestamp(Timestamp),
  244    atomic_list_concat([Directory,Timestamp],Timestamped).    
  245/*
  246 * create_timestamp(?TimeStampAtom)
  247 *   Return in Arg1 an atom representing the time of the 
  248 *   invocation of this predicate in the form 
  249 *   Year-Month-Day-Hour-Minute-Second.Milliseconds  
  250 */
  251create_timestamp(TimeStampAtom) :-
  252    get_time(TimeStamp),
  253    stamp_date_time(TimeStamp, DateTimeTerm1, local),
  254    DateTimeTerm1 = date(Y,M,D,H,Mn,S,_,_,_),
  255    DateTimeTerm2 = Y-M-D-H-Mn-S,
  256    term_to_atom(DateTimeTerm2,TimeStampAtom).
  257
  258create_timestamp_2(TimeStampAtom) :-
  259    get_time(TimeStamp),
  260    stamp_date_time(TimeStamp, DateTimeTerm1, local),
  261    DateTimeTerm1 = date(Y,M,D,H,Mn,S,_,_,_),
  262    Seconds is truncate(S), 
  263    format(atom(TimeStampAtom), '~a.~a.~a ~a:~a:~d', [D,M,Y,H,Mn,Seconds]).
  264    
  265/*
  266 * Determine the absolute path to the root directory of the current 
  267 * workspace ASSUNIMG that this file is three levels deeper:
  268 *  --> WorkspaceDirPath/ProjectDir/FileDir/thisfile
  269 */                                    
  270workspace_root(WorkspaceDirPath) :-
  271    file_search_path('worspace_root', WorkspaceDirPath),
  272    !.
  273workspace_root(WorkspaceDirPath) :-
  274    source_file(workspace_root(_), CurrentFile),    % get absolute path of current file
  275    file_directory_name(CurrentFile, FileDirPath),  % get path to its containing directory
  276    file_base_name(FileDirPath, FileDir),           % get name of containing directory 
  277    concat(ProjectDirPath, FileDir, FileDirPath),   % get path to its containing project
  278    file_base_name(ProjectDirPath, ProjectDir),     % get name of containing project
  279    concat(WorkspaceDirPath, ProjectDir, ProjectDirPath), % get path of its containing worksapace
  280    assert(file_search_path('worspace_root', WorkspaceDirPath))