1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%% parseProblemVerb.pl
    3%%   Simple parser of PDDL domain file into prolog syntax.
    4%% Author: Robert Sasak, Charles University in Prague
    5%%
    6%% Example: 
    7%% ?-parseProblemVerb('problem.pddl', O).
    8%%   O = problem('blocks-4-0',							%name
    9%%              blocks,										%domain name
   10%%              _G1443,                            %require definition
   11%%              [block(d, b, a, c)],					%object declaration
   12%%              [ clear(c), clear(a), clear(b), clear(d), ontable(c), %initial state
   13%%                ontable(a), ontable(b), ontable(d), handempty,
   14%%                set('total-cost', 0)	],
   15%%              [on(d, c), on(c, b), on(b, a)],		%goal
   16%%              _G1447,										%constraints-not implemented
   17%%              metric(minimize, 'total-cost'),		%metric
   18%%              _G1449										%length_specification-not implemented
   19%%              )
   20%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   21
   22
   23% Support for reading file as a list.
   24
   25:- ensure_loaded('readFileI').   26:- ensure_loaded('sharedPDDL2.2').   27
   28% parseProblemVerb(+File, -Output).
   29% Parse PDDL problem File and return rewritten prolog syntax. 
   30parseProblemVerb(F, O):-
   31	view([problemFile,F]),
   32	parseProblemVerb(F, O, _).
   33
   34% parseProblemVerb(+File, -Output, -RestOfFile).
   35% The same as above and also return rest of file. Can be useful when domain and problem are in one file.
   36parseProblemVerb(F, O, R) :-
   37	read_file(F, L),
   38	view([problemVerb,L]),
   39	problemVerb(O, L, R).
   40
   41% List of DCG rules describing structure of problem file in language PDDL.
   42% BNF description was obtain from http://www.cs.yale.edu/homes/dvm/papers/pddl-bnf.pdf
   43% This parser do not fully NOT support PDDL 3.0
   44% However you will find comment out lines ready for futher development.
   45% Some of the rules are already implemented in parseDomain.pl
   50problemVerb(problem(Name, Domain, OD, I, G, MS))   
   51				--> ['(',define,'(',problem,Name,')',
   52				     '(',':',domain, Domain,')',
   53				     '(',':',includes],zeroOrMore(token,Includes),[')',
   54				     '(',':',timing,
   55				     '(','start-date'],dateTimeZone(StartDate),[')',
   56				     '(',units],duration(Duration),[')',
   57				     ')'
   58				     ],
   61				(p_object_declaration(OD)	; []),
   62				p_init(I),
   63				p_goal(G),
   65				(p_metric_spec(MS)	; []),
   67				[')'],
   68				{Units = units(Duration)}
   68.
   69
   70:- ensure_loaded('sharedPDDL2.2Problem').