9typed_list(W, [F|Ls])           --> oneOrMore(W, L), ['-'], !, type(T), typed_list(W, Ls), {F =.. [are,L,T]}.	%:typing
   10typed_list(W, L)                --> zeroOrMore(W, L).
   11
   12subsumptionList(T)              --> oneOrMore(subsumes,T).
   13
   14subsumes(A)                     --> oneOrMore(nonDashToken,SubTypes),['-'],token(SuperType),{A = genls(SubTypes,SuperType)}.
   15nonDashToken(T)                 --> token(T), {T \= '-'}.
   16
   17token(T)                        --> name(T).
   18
   19% BNF description include operator <term>+ to mark zero or more replacements.
   20% This DCG extension to overcome this. 
   21oneOrMore(W, [R|Rs], A, C) :- F =.. [W, R, A, B], F, (
   22					oneOrMore(W, Rs, B, C) ;
   23					(Rs = [] , C = B) 
   24				).
   25% BNF operator <term>*
   26zeroOrMore(W, R)		--> oneOrMore(W, R).
   27zeroOrMore(_, [])		--> [].
   28
   29
   30% Name is everything that is not number, bracket or question mark.
   31% Those rules are not necessary, but rapidly speed up parsing process.
   32name(N)				--> [N], {integer(N), !, fail}.
   33name(N)				--> [N], {float(N), !, fail}.
   34name(N)				--> [N], {N=')', !, fail}.
   35name(N)				--> [N], {N='(', !, fail}.
   38name(N)				--> [N], {N='?', !, fail}.
   39name(N)				--> [N].
   40
   41type(either(PT))		--> ['(',either], !, oneOrMore(primitive_type, PT), [')'].
   42type(PT)			--> primitive_type(PT).
   43
   44primitive_type(N)		--> name(N).
   45
   46
   47literal(T, F)			--> atomic_formula(T, F).
   48literal(T, not(F))		--> ['(',not], atomic_formula(T, F), [')'].
   49
   50atomic_formula(_, F)		--> ['('], predicate(P), zeroOrMore(term, T), [')'], {F =.. [P|T]}.		% cheating, maybe wrong
   51
   52predicate(P)			--> name(P).
   53
   54term(N)				--> name(N).
   55term(V)				--> variable(V).
   56
   57variable('$VAR'(V))             --> ['?'], name(N), {capitalize(N,V)}.
   58
   59number(N)			--> [N], {integer(N)}.
   60number(N)			--> mfloat(N).
   61
   62gd(F)				--> atomic_formula(term, F).	%: this option is covered by gd(L)
   63gd(L)				--> literal(term, L).								%:negative-preconditions
   64gd(P)				--> ['(',and],  zeroOrMore(gd, P), [')'].
   65gd(or(P))			--> ['(',or],   zeroOrMore(gd ,P), [')'].					%:disjuctive-preconditions
   66gd(not(P))			--> ['(',not],  gd(P), [')'].							%:disjuctive-preconditions
   67gd(imply(P1, P2))		--> ['(',imply], gd(P1), gd(P2), [')'].						%:disjuctive-preconditions
   68gd(exists(L, P))		--> ['(',exists,'('], typed_list(variable, L), [')'], gd(P), [')'].		%:existential-preconditions
   69gd(forall(L, P))		--> ['(',forall,'('], typed_list(variable, L), [')'], gd(P), [')'].		%:universal-preconditions
   70gd(F)				--> f_comp(F).	%:fluents
   71
   72f_head(F)			--> ['('], function_symbol(S), zeroOrMore(term, T), [')'], { F =.. [S|T] }.
   73f_head(S)			--> function_symbol(S).
   74
   75function_symbol(S)		--> name(S).
   76
   77mfloat(F)                       --> [N1,'.',N2], {number(N1), number(N2), atomic_list_concat([N1,'.',N2],'',Tmp),atom_number(Tmp,F)}.
   78
   79pre_GD(P)			--> pref_GD(P).
   80pre_GD(P)                       --> oneOrMore(assignment,P).
   81pre_GD(P)			--> ['(',and], pre_GD(P), [')'].
   82pre_GD(forall(L, P))		--> ['(',forall,'('], typed_list(variable, L), [')'], pre_GD(P), [')'].		%:universal-preconditions
   83
   84pref_GD(preference(N, P))	--> ['(',preference], (pref_name(N); []), gd(P), [')'].				%:preferences
   85pref_GD(P)			--> gd(P).
   86
   87f_comp(compare(C, E1, E2))	--> ['('], binary_comp(C), f_exp(E1), f_exp(E2), [')'].
   88
   89binary_comp('>')		--> ['>'].
   90binary_comp('<')		--> ['<'].
   91binary_comp('=')		--> ['='].
   92binary_comp('>=')		--> ['>','='].
   93binary_comp('<=')		--> ['<','='].
   94
   95assignment(A)                   --> ['('], assign_op(P), f_head(H), f_exp(E), [')'], {A =.. [P,H,E]}.
   96
   97assign_op(assign)		--> [assign].
   98assign_op(scale_up)		--> [scale_up].
   99assign_op(scale_down)		--> [scale_down].
  100assign_op(increase)		--> [increase].
  101assign_op(decrease)		--> [decrease].
  102
  103:- ensure_loaded('shared').