1% Support for reading file as a list.
    2
    3:- ensure_loaded('readFileI').
    6% parseDomain(+File, -Output).
    7% Parse PDDL domain File and return it rewritten prolog syntax.   
    8parseSolution(F, O):-
    9	view([solutionFile,F]),
   10	atomic_concat(F,'.filtered',F2),
   11	currentPlanner(Planner),
   12	(   (	Planner = 'LPG') ->
   13	    (	atomic_list_concat(['trim.pl',F,'>',F2],' ',Command) ) ;
   14	    (	(   Planner = 'OPTIC_CLP') -> atomic_list_concat(['trim_optic_clp.pl',F,'>',F2],' ',Command) ; true)),
   15	view([command,Command]),
   16	shell(Command,_),
 parseSolution(F, O, _)
   18	parseSolution(F2, O, _)
   18.
   19
   20% The same as above and also return rest of file. Can be useful when domain and problem are in one file.
   21parseSolution(File, Output, R) :-
   22	read_file(File, List),
   23	view([parseSolutionList,List]),
   24	solution(Output, List, R),!.
   25
   26lower_case_list(A,B) :-
   27	findall(Y,(member(X,A),lower_case(X,Y)),B).
   28
   29capitalize(WordLC, WordUC) :-
   30	atom_chars(WordLC, [FirstChLow|LWordLC]),
   31	atom_chars(FirstLow, [FirstChLow]),
   32	upcase_atom(FirstLow, FirstUpp),
   33	atom_chars(FirstUpp, [FirstChUpp]),
   34	atom_chars(WordUC, [FirstChUpp|LWordLC]),!.
   35
   36% List of DCG rules describing structure of domain file in language PDDL.
   37% BNF description was obtain from http://www.cs.yale.edu/homes/dvm/papers/pddl-bnf.pdf
   38% This parser do not fully NOT support PDDL 3.0
   39% However you will find comment out lines ready for futher development.
   40%% solution(solution(N, CLI, P, T, ST, PT, MT, MV))
   41solution(solution(P))
   42                        -->
   44				
   45				
   46				
   47				
   48				
   49				
   50				
   51				
   52				generatedPlan(P)
   52.
   53
   57generatedPlan(P)                    --> ['<',no,solution,'>'],{P = none}.
   58generatedPlan(P)                    --> oneOrMore(plan_step, P).
   60plan_step(P)               --> mfloat(T), [:], ['('], action(A), oneOrMore(action_argument, Args), [')'], mfloat(D), {P = [T,A,Args,D]}.
   61
   62action(A)                  --> name(A).
   63action_argument(A)         --> name(A).
   67% BNF description include operator <term>+ to mark zero or more replacements.
   68% This DCG extension to overcome this. 
   69oneOrMore(W, [R|Rs], A, C) :- F =.. [W, R, A, B], F, (
   70						      oneOrMore(W, Rs, B, C) ;
   71						      (Rs = [] , C = B)
   72						     ).
   73
   74number(N)			--> [N], {integer(N)}.
   75number(N)			--> mfloat(N).
   76mfloat(F)                       --> [N1,'.',N2], {atom(N1), atom(N2), atomic_list_concat([N1,'.',N2],'',Tmp),atom_number(Tmp,F)}.
   78mfloat(F)                       --> [N], {atom(N),atom_number(N,F)}.
   79
   80name(N)				--> [N], {integer(N), !, fail}.
   81name(N)				--> [N], {float(N), !, fail}.
   82name(N)				--> [N], {N=')', !, fail}.
   83name(N)				--> [N], {N='(', !, fail}.
   84name(N)				--> [N], {N='?', !, fail}.
   85name(N)				--> [N]