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(source_files, [pdt_source_files/1, pdt_source_file/2, pdt_source_file/3]).   15
   16:- use_module(library(lists), [
   17	member/2
   18]).
 pdt_source_files(String) is nondet
TRHO: obsolete once improved parser is available (PDT-412)
   23pdt_source_files(String) :-
   24	findall(File,
   25		source_file(File),
   26		Files),
   27	ctc_lists:list_2_comma_separated_list(Files, String).
   28
   29pdt_source_file(File, State) :-
   30	pdt_source_file(File, State, _).
   31
   32pdt_source_file(File, State, loaded) :-
   33	source_file(File),
   34	(	exists_file(File)
   35	->	source_file_property(File, 	modified(ModifiedAtConsult)),
   36		time_file(File, ModifiedNow),
   37		(	ModifiedNow > ModifiedAtConsult + 0.001
   38		->	State = old
   39		;	State = current
   40		)
   41	;	State = current
   42	).
   43
   44pdt_source_file(File, State, included) :-
   45	setof(
   46		F,
   47		P^L^(
   48			source_file_property(F, included_in(P, L)),
   49			\+ source_file(F)
   50		),
   51		Fs
   52	),
   53	member(File, Fs),
   54	(	exists_file(File)
   55	->	setof(
   56			Time,
   57			F^source_file_property(F, includes(File, Time)),
   58			Times
   59		),
   60		Times = [ModifiedAtConsult|_],
   61		time_file(File, ModifiedNow),
   62		(	ModifiedNow > ModifiedAtConsult + 0.001
   63		->	State = old
   64		;	State = current
   65		)
   66	;	State = current
   67	)