1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%% parseDomainVerb.pl
    3%%   Simple parser of Verb domain file into prolog syntax.
    4%% Author: Robert Sasak, Charles University in Prague
    5%%
    6%% Example: 
    7%% ?-parseDomainVerb('blocks_world.pddl', O).
    8%%   O = domainVerb(blocks,
    9%%        [strips, typing, 'action-costs'],
   10%%        [block],
   11%%        _G4108,
   12%%        [ on(block(?x), block(?y)),
   13%%	         ontable(block(?x)),
   14%%	         clear(block(?x)),
   15%%	         handempty,
   16%%	         holding(block(?x)) ],
   17%%        [number(f('total-cost', []))],
   18%%        _G4108,
   19%%        [ action('pick-up', [block(?x)],       %parameters
   20%%		      [clear(?x), ontable(?x), handempty], %preconditions
   21%%		      [holding(?x)],                       %positiv effects
   22%%          [ontable(?x), clear(?x), handempty], %negativ effects
   23%%          [increase('total-cost', 2)]),        %numeric effects
   24%%         ...],
   25%%       ...)
   26%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   27
   28% Support for reading file as a list.
   29
   30:- ensure_loaded('readFileI').   31
   32% parseDomainVerb(+File, -Output).
   33% Parse Verb domain File and return it rewritten prolog syntax.   
   34parseDomainVerb(F, O):-
   35	view([domainVerbFile,F]),
   36	parseDomainVerb(F, O, _).
   37
   38% parseDomainVerb(+File, -Output, -RestOfFile)
   39% The same as above and also return rest of file. Can be useful when domain and problem are in one file.
   40parseDomainVerb(File, Output, R) :-
   41		read_file(File, List),
   42		view([domainVerbList,List]),
   43		domainVerb(Output, List, R).
   44% List of DCG rules describing structure of domain file in language Verb.
   45% BNF description was obtain from http://www.cs.yale.edu/homes/dvm/papers/pddl-bnf.pdf
   46% This parser do not fully NOT support Verb 3.0
   47% However you will find comment out lines ready for futher development.
   50domainVerb(domain(N, R, T, P, F, S))
   51			--> ['(','define', '(','domain'], name(N), [')'],
   52                             (require_def(R)	; []),
   53                             (types_def(T)    	; []), %:typing
   54                             (timing_def(I) ; []), %:timing
   56                             (predicates_def(P)	; []),
   57                             (functions_def(F)	; []), %:fluents
   59                             zeroOrMore(structure_def, S),
   60			     [')']
   60.
   61
   62timing_def(Timing)		--> ['(',':',timing,'(',units],duration(Duration),[')',')'],{Timing = units(Duration)}.
   63
   64:- ensure_loaded('sharedPDDL2.2Domain').