1thingsToFix('generate_glosses.pl',
    2	    [
    3	     ['the andy should ...','Andy should ...']
    4	    ]).
   14preconditionNLGTemplates([
   16			  
   17			  
   18			 ]
   18)
   18.
   19
   21getDeterminerAndGloss(A,DT,AG) :-
   22	(   (	isa(A,person)) ->
   23	    (	DT = '') ;
   24	    (	DT = the )),
   25	hasEnglishGlosses(A,Tmp),
   26	Tmp =.. [_,AG|_].
   27
   28formatSentence(Template,Sentence) :-
   29	findall(Item,(member(Item,Template),not(Item = '')),[First|Rest]),
   30	capitalize(First,FirstCapitalized),
   31	Sentence = [FirstCapitalized|Rest].
   32
   33get_sentence_for_precondition_predicate(PTmp,ObjectNames,Condition,Sentence) :-
   34	(   (	PTmp = location) ->
   35	    (	P = at) ;
   36	    (	P = PTmp)),
   37	view([get_sentence_for_precondition_predicate(P,ObjectNames,Condition,Sentence)]),
   38	preconditionNLGTemplates(List),
   39	kmax_get_index_of_first_item_in_list(Condition,['at start','at end','over all'],Index),
   40	view([index,Index]),
   41	(   member([P,Templates],List) ->
   42	    (	nth1(Index,Templates,Template)) ; 
   43	    (	view([condition,Condition,index,Index,templates,Templates,objectnames,ObjectNames]), 
   44		(   
   45		    ObjectNames = [A] ->
   46		    (	
   47			getDeterminerAndGloss(A,DT1,AG),
   48			nth1(Index,[[DT1,AG,must,be,P],
   49				    [DT1,AG,will,be,P],
   50				    [DT1,AG,must,be,P,for,the,duration,of,the,action]],
   51			     Template)) ;
   52		    (	ObjectNames = [A,B] ->
   53			(   
   54			    getDeterminerAndGloss(A,DT1,AG),
   55			    getDeterminerAndGloss(B,DT2,BG),
   56			    nth1(Index,[[DT1,AG,must,be,P,DT2,BG],
   57					[DT1,AG,will,be,P,DT2,BG],
   58					[DT1,AG,must,be,P,DT2,BG,for,the,duration,of,the,action]],
   59				 Template)) ;
   60			(   ObjectNames = [A,B,C] ->
   61			    (	
   62				getDeterminerAndGloss(A,DT1,AG),
   63				nth1(Index,[[DT1,AG,must,be,P,B,C],
   64					    [DT1,AG,will,be,P,B,C],
   65					    [DT1,AG,must,be,P,B,C,for,the,duration,of,the,action]],
   66				     Template)) ;
   67			    (	ObjectNames = [A,B,C,D] ->
   68				(   
   69				    getDeterminerAndGloss(A,DT1,AG),
   70				    nth1(Index,[[DT1,AG,must,be,P,B,C,D],
   71						[DT1,AG,will,be,P,B,C,D],
   72						[DT1,AG,must,be,P,B,C,D,for,the,duration,of,the,action]],
   73					 Template)) ;
   74				(   ObjectNames = [A,B,C,D,E] ->
   75				    (	
   76					getDeterminerAndGloss(A,DT1,AG),
   77					nth1(Index,[[DT1,AG,must,be,P,B,C,D,E],
   78						    [DT1,AG,will,be,P,B,C,D,E],
   79						    [DT1,AG,must,be,P,B,C,D,E,for,the,duration,of,the,action]],
   80					     Template)) ; fail) ; fail) ; fail) ; fail) ; fail))),
   81	formatSentence(Template,Sentence).
   82
   83get_sentence_for_precondition_predicate(P,ObjectNames,Condition,Sentence) :-
   84	view([get_sentence_for_precondition_predicate(P,ObjectNames,Condition,Sentence)]),
   85	preconditionNLGTemplates(List),
   86	kmax_get_index_of_first_item_in_list(Condition,['at start','at end','over all'],Index),
   87	view([index,Index]),
   88	(   member([P,Templates],List) ->
   89	    (	nth1(Index,Templates,Template)) ; 
   90	    (	view([condition,Condition,index,Index,templates,Templates,objectnames,ObjectNames]), 
   91		(   
   92		    ObjectNames = [A] ->
   93		    (	
   94			getDeterminerAndGloss(A,DT1,AG),
   95			nth1(Index,[[DT1,AG,must,be,P],
   96				    [DT1,AG,will,be,P],
   97				    [DT1,AG,must,be,P,for,the,duration,of,the,action]],
   98			     Template)) ;
   99		    (	ObjectNames = [A,B] ->
  100			(   
  101			    getDeterminerAndGloss(A,DT1,AG),
  102			    getDeterminerAndGloss(B,DT2,BG),
  103			    nth1(Index,[[DT1,AG,must,be,P,DT2,BG],
  104					[DT1,AG,will,be,P,DT2,BG],
  105					[DT1,AG,must,be,P,DT2,BG,for,the,duration,of,the,action]],
  106				 Template)) ;
  107			(   ObjectNames = [A,B,C] ->
  108			    (	
  109				getDeterminerAndGloss(A,DT1,AG),
  110				nth1(Index,[[DT1,AG,must,be,P,B,C],
  111					    [DT1,AG,will,be,P,B,C],
  112					    [DT1,AG,must,be,P,B,C,for,the,duration,of,the,action]],
  113				     Template)) ;
  114			    (	ObjectNames = [A,B,C,D] ->
  115				(   
  116				    getDeterminerAndGloss(A,DT1,AG),
  117				    nth1(Index,[[DT1,AG,must,be,P,B,C,D],
  118						[DT1,AG,will,be,P,B,C,D],
  119						[DT1,AG,must,be,P,B,C,D,for,the,duration,of,the,action]],
  120					 Template)) ;
  121				(   ObjectNames = [A,B,C,D,E] ->
  122				    (	
  123					getDeterminerAndGloss(A,DT1,AG),
  124					nth1(Index,[[DT1,AG,must,be,P,B,C,D,E],
  125						    [DT1,AG,will,be,P,B,C,D,E],
  126						    [DT1,AG,must,be,P,B,C,D,E,for,the,duration,of,the,action]],
  127					     Template)) ; fail) ; fail) ; fail) ; fail) ; fail))),
  128	formatSentence(Template,Sentence).
  129
  130get_sentence_for_precondition_predicate(P,ObjectNames,Condition,Sentence).
  131
  132
  133convert_pregd(Item,Pairs,Gloss) :-
  134	nl,
  135	length(Pairs,Length),
  136	view([pairs,Pairs]),
  137	(   Item =.. [Condition,not(PreGD)] -> (Concat = '*not* ') ;
  138	    (	Item =.. [Condition,PreGD] -> (Concat = '') ; true )),
  139	view([preGd,PreGD]),
  140	PreGD =.. [P|A],
  141	view([p,P,a,A]),
  142	findall(ObjectName,(member(Pair,Pairs),member('$VAR'(VarName),A),Pair = [['$VAR'(VarName),_],ObjectName]),ObjectNames),
  143	get_sentence_for_precondition_predicate(P,ObjectNames,Condition,Sentence),
  144	view([sentence,Sentence]),
  145	(   nonvar(Sentence) -> atomic_list_concat(Sentence,' ',Gloss) ; (print_to_atom(PreGD,Gloss),view([glossBaby,Gloss]))),
  146	!.
  188convert_pregd(Statement,Pairs,Gloss) :-
  189	with_output_to(atom(Gloss),write_term(Statement,[quoted(true)])),!.