1:- use_module(library(lists)).    2
    3:- consult('pddl_wrapper').    4:- consult('args').    5:- consult('prolog-to-pddl-pretty-print-prolog').    6
    7flp_convert_pl_to_pddl(Arguments) :-
    8	argt(Arguments,[domain(Domain),problem(Problem),solution(Solution),results(Results)]),
    9	output(domain(Domain),DomainResults),
   10	output(problem(Problem),ProblemResults),
   11	output(solution(Solution),SolutionResults),
   12	Results = [domainResults(DomainResults),problemResults(ProblemResults),solution(Solution,SolutionResults)],
   13	Arguments = [domain(Domain),problem(Problem),solution(Solution),results(Results)].
   14
   15output(domain(Domain),DomainResults) :-
   16	Domain = domain(DomainName,TmpRequirements,TmpTypes,TmpPredicates,TmpFunctions,TmpActions),
   17	view([1]),
   18	Derived = [],
   19
   20	findall(Requirement,(member(TmpRequirement,TmpRequirements),atom_concat(':',TmpRequirement,Requirement)),Tmp2Requirements),
   21	append([[':requirements'],Tmp2Requirements],Requirements),
   22	view([requirements,Requirements]),
   23
   24	view([tmpTypes,TmpTypes]),
   25	setof([SubTypes,['-'],[SuperType]],member(genls(SubTypes,SuperType),TmpTypes),Tmp2Types),
   26	append(Tmp2Types,Tmp3Types),
   27	append(Tmp3Types,Tmp4Types),
   28	append([[':types'],Tmp4Types],Types),
   29	view([types,Types]),
   30
   31	fixPredicates(TmpPredicates,Tmp2Predicates),
   32	append([[':predicates'],Tmp2Predicates],Predicates),
   33	view([predicates,Predicates]),
   34
   35	view([tmpFunctions,TmpFunctions]),
   36	fixFunctions(TmpFunctions,Tmp2Functions),
   37	append([[':functions'],Tmp2Functions],Functions),
   38	view([functions,Functions]),
   39
   40	TmpArgumentList = [domain(DomainName),Requirements,Types,Predicates,Functions],
   41	fixActions(TmpActions,Actions),
   42	append([TmpArgumentList,Derived,Actions],ArgumentList),
   43	view([argumentList,ArgumentList]),
   44	
   45	append([[define],ArgumentList],PDDLDomain),
   46	Atom = pddl_domain(PDDLDomain),
   47
   48	convert_pl_to_pddl([input(PDDLDomain),inputType('Prolog'),outputType('KIF String'),results(DomainResults)]),
   49	displayResults(DomainResults), !.
   50
   51fixPredicates(TmpPredicates,Predicates) :-
   52	findall(Predicate,
   53		(   
   54		    member(TmpPredicate,TmpPredicates),
   55		    view([tmpPredicate,TmpPredicate]),
   56		    TmpPredicate =.. [PredicateName|AllTypeSpecs],
   57		    view([predicateName,PredicateName]),
   58		    view([allTypeSpecs,AllTypeSpecs]),
   59		    findall(Output,
   60			    (	
   61				member(are(Variables,Type),AllTypeSpecs),
   62				view([type,Type,typeSpecs,Variables]),
   63				findall(NewVariableName,
   64					(   
   65					    member('$VAR'(VariableName),Variables),
   66					    atom_concat('?',VariableName,NewVariableName)
   67					),
   68					NewVariableNames),
   69				append([NewVariableNames,[-],[Type]],Output)
   70			    ),
   71			    TmpOutputs),
   72		    append(TmpOutputs,Outputs),
   73		    append([[PredicateName],Outputs],Predicate)
   74		),
   75		Predicates),
   76	view([predicates,Predicates]).
   77
   78fixFunctions(TmpFunctions,Functions) :-
   79	findall(Function,
   80		(   
   81		    member(TmpFunction,TmpFunctions),
   82		    view([tmpFunction,TmpFunction]),
   83		    TmpFunction =.. [f|[FunctionName|[AllTypeSpecs]]],
   84		    view([functionName,FunctionName]),
   85		    view([allTypeSpecs,AllTypeSpecs]),
   86		    findall(Output,
   87			    (	
   88				member(are(Variables,Type),AllTypeSpecs),
   89				view([type,Type,typeSpecs,Variables]),
   90				findall(NewVariableName,
   91					(   
   92					    member('$VAR'(VariableName),Variables),
   93					    atom_concat('?',VariableName,NewVariableName)
   94					),
   95					NewVariableNames),
   96				append([NewVariableNames,[-],[Type]],Output)
   97			    ),
   98			    TmpOutputs),
   99		    view([tmpOutputs,TmpOutputs]),
  100		    append(TmpOutputs,Outputs),
  101		    view([outputs,Outputs]),
  102		    append([[FunctionName],Outputs],Function)
  103		),
  104		Functions),
  105	view([functions,Functions]).
  106
  107fixActions(TmpActions,Actions) :-
  108	findall(Action,
  109		(   
  110		    member(TmpAction,TmpActions),
  111		    view([tmpAction,TmpAction]),
  112		    TmpAction =.. [durativeAction|[ActionName|[AllTypeSpecs,TmpDuration,Tmp0Preconditions,Tmp0Effects]]],
  113		    fixPreconditions(Tmp0Preconditions,TmpPreconditions),
  114		    fixEffects(Tmp0Effects,TmpEffects),
  115		    view([actionName,ActionName,variables,AllTypeSpecs,duration,TmpDuration,preconditions,TmpPreconditions,effects,TmpEffects]),
  116		    findall(Parameter,
  117			    (	
  118				member(are(Variables,Type),AllTypeSpecs),
  119				view([type,Type,variables,Variables]),
  120				findall(NewVariableName,
  121					(   
  122					    member('$VAR'(VariableName),Variables),
  123					    atom_concat('?',VariableName,NewVariableName)
  124					),
  125					NewVariableNames),
  126				append([NewVariableNames,[-],[Type]],Parameter)
  127			    ),
  128			    TmpParameters),
  129		    append(TmpParameters,Parameters),
  130		    renderVariables(TmpDuration,Duration),
  131		    append([['and'],TmpPreconditions],Tmp2Preconditions),
  132		    renderVariables(Tmp2Preconditions,Preconditions),
  133		    append([['and'],TmpEffects],Tmp2Effects),
  134		    renderVariables(Tmp2Effects,Effects),
  135		    Action = ':durative-action'(ActionName,':parameters',Parameters,':duration',['=','?duration',Duration],':condition',Preconditions,':effect',Effects)
  136		),
  137		Actions),
  138	view([actions,Actions]).
  139
  140fixPreconditions(TmpPreconditions,Preconditions) :-
  141	findall(NewPrecondition,
  142		(   
  143		    member(Precondition,TmpPreconditions),
  144		    renderOpAndCompareConversion(Precondition,NewPrecondition0),
  145		    renderActionsConversion(NewPrecondition0,NewPrecondition),
  146		    view([newPrecondition|[NewPrecondition]])
  147		),
  148		Preconditions).
  149
  150fixEffects(TmpEffects,Effects) :-
  151	findall(NewEffect,
  152		(   
  153		    member(Effect,TmpEffects),
  154		    view([effect,Effect]),
  155		    Effect =.. [Op|Args],
  156		    view([op,Op,args,Args]),
  157		    (	(   (	Op = 'at start' ; Op = 'over all' ; Op = 'at end' ), is_list(Args), [TmpArgs] = Args, is_list(TmpArgs)) ->
  158			(   (	length(TmpArgs,1)) ->
  159			    [[NewArgs]] = Args ;
  160			    append([and],Args,NewArgs) ) ;
  161			(   [NewArgs] = Args)),
  162		    view([newargs,NewArgs]),
  163		    TmpNewEffect =.. [Op,NewArgs],
  164		    renderOpAndCompareConversion(TmpNewEffect,NewEffect0),
  165		    renderActionsConversion(NewEffect0,NewEffect),
  166		    view([neweffect|[NewEffect]])
  167		),
  168		Effects).
  169
  170output(problem(Problem),ProblemResults) :-
  171	Problem = problem(ProblemName,ProblemDomainName,TmpObjects,TmpInit,TmpGoal),
  172	view([problemItems,[ProblemName,ProblemDomainName,TmpObjects,TmpInit,TmpGoal]]),
  173
  174	view([tmpObjects,TmpObjects]),
  175	append([[':objects'],TmpObjects],Objects),
  176	view([objects,Objects]),
  177
  178	view([tmpInit,TmpInit]),
  180	
  181	append([[':init'],
  183		TmpInit]
  183,Init)
  183,
  184	view([init,Init]),
  185
  186	view([tmpGoal,TmpGoal]),
  187	append([[and],TmpGoal],Tmp2Goal),
  188	append([[':goal'],[Tmp2Goal]],Goal),
  189	view([goal,Goal]),
  190
  191	Metric = ':metric'(minimize,'total-time'()),
  192	view([metric,Metric]),
  193
  194	PDDLProblem = define(
  195			     problem(ProblemName),
  196			     ':domain'(ProblemDomainName),
  197			     Objects,
  198			     Init,
  199			     Goal,
  200			     Metric
  201			    ),
  202	Atom = pddl_problem(PDDLProblem),
  203	convert_pl_to_pddl([input(PDDLProblem),inputType('Prolog'),outputType('KIF String'),results(ProblemResults)]),
  204	displayResults(ProblemResults),!
  204.
  205
  206output(solution(Solution),SolutionResults) :-
  207	Atom = pddl_solution(Solution),
  208	view([input(Solution),inputType('Prolog'),outputType('KIF String'),results(SolutionResults)]),
  209	(   nonvar(Solution) -> convert_pl_to_pddl([input(Solution),inputType('Prolog'),outputType('KIF String'),results(SolutionResults)]) ; true),
  210	displayResults(SolutionResults),!.
  211
  212convert_pl_to_pddl(Arguments) :-
  214	prolog_to_pddl_pretty_print(Arguments),
  215	true
  215.
  216
  217prolog_to_pddl_pretty_print([input(Input),inputType(InputType),outputType(OutputType),results(Results)]) :-
  218	prolog_to_pddl_pretty_print_prolog([input(Input),inputType(InputType),outputType(OutputType),results(Results)]).
  219
  220prolog_to_pddl_pretty_print_prolog([input(Input),inputType(InputType),outputType(OutputType),results(Results)]) :-
  221	prolog_to_verb(Input,Results).
  222
  223prolog_to_pddl_pretty_print_perl([input(Input),inputType(InputType),outputType(OutputType),results(Results)]) :-
  225	
  226	InputFile = '/tmp/kbs2-import-export-input.txt',
  227	OutputFile = '/tmp/kbs2-import-export-output.txt',
  228	writeq_data_to_file(Input,InputFile),
  229	atomic_list_concat([
  230			    'prolog-to-pddl-pretty-print -i \'',
  231			    InputType,
  232			    '\' -o \'',
  233			    OutputType,
  234			    '\' -f \'',
  235			    InputFile,'\' > ',
  236			    OutputFile
  237			   ],'',Command),
  238	shell(Command),
  239	read_data_from_file(OutputFile,Results)
  239.
  240
  241displayResults(Results) :-
  242	view([displayingResult]),
  243	nl,nl,
  244	write(Results),
  245	nl,nl,
  246	!.
  247
  248renderVariables(Pre,Post) :-
  249	view([pre,Pre]),
  250	is_list(Pre) ->
  251	findall(Item,(member(SubPre,Pre),renderVariables(SubPre,Item)),Post) ;
  252	Pre =.. ['$VAR',VariableName] ->
  253	atom_concat('?',VariableName,Post) ;
  254	Pre =.. [PredicateName|Args] ->	
  255	(   
  256	    findall(Item,(member(SubArgs,Args),renderVariables(SubArgs,Item)),Items),
  257	    Post =.. [PredicateName|Items]
  258	) ;
  259	Post = Pre.
  260
  261renderOpAndCompareConversion(Pre,Post) :-
  262	view([pre,Pre]),
  263	is_list(Pre) ->
  264	findall(Item,(member(SubPre,Pre),renderOpAndCompareConversion(SubPre,Item)),Post) ;
  265	(   Pre =.. [op,Op|Rest] ; Pre =.. [compare,Op|Rest] ) ->
  266	Post =.. [Op|Rest] ;
  267	Pre =.. [PredicateName|Args] ->	
  268	(   
  269	    findall(Item,(member(SubArgs,Args),renderOpAndCompareConversion(SubArgs,Item)),Items),
  270	    Post =.. [PredicateName|Items]
  271	) ;
  272	Post = Pre.
  273
  274renderActionsConversion(Pre,Post) :-
  275	view([preA,Pre]),
  276	(   (	is_list(Pre)) ->
  277	    (	findall(Item,(member(SubPre,Pre),renderActionsConversion(SubPre,Item)),Post)) ;
  278	    (	(   nonvar(Pre)) ->
  279		(   (	Pre = actions ) ->
  280		    (	Post = [actions] ) ;
  281		    (	(   Pre = okay ) ->
  282			(   Post = [okay] ) ;
  283			(   Pre =.. [P|A],
  284			    (	A = [] ->
  285				Post = P ;
  286				(   renderActionsConversion(P,P2),
  287				    findall(Item,(member(SubA,A),renderActionsConversion(SubA,Item)),A2),
  288				    Post =.. [P2|A2]))))) ;	
  289		Post = Pre))