src/Tools/isac/Interpret/generate.sml
author Walther Neuper <neuper@ist.tugraz.at>
Tue, 22 May 2012 13:40:06 +0200
changeset 42432 7dc25d1526a5
parent 42394 977788dfed26
child 42434 9e9debbe1501
permissions -rw-r--r--
added "fun requestFillformula"

given a fillpatID propose a fillform to the learner on the worksheet;
the "ctree" is extended with fillpat and "ostate Inconsistent", the "istate" is NOT updated;
returns CalcChanged.
arg errpatID: required because there is no dialog-related state in the math-kernel.

ATTENTION: the handling of "Inconsistent" and pos will be tested with "fun inputFillformula".
     1 (* use"ME/generate.sml";
     2    use"generate.sml";
     3    *)
     4 
     5 (*.initialize istate for Detail_Set.*)
     6 (*
     7 fun init_istate (Rewrite_Set rls) = 
     8 (* val (Rewrite_Set rls) = (get_obj g_tac pt p);
     9    *)
    10     (case assoc_rls rls of
    11 	 Rrls {scr=sc as Rfuns {init_state=ii,...},...} => (RrlsState (ii t))
    12 (* val Rrls {scr=sc as Rfuns {init_state=ii,...},...} = assoc_rls rls;
    13    *)
    14        | Rls {scr=EmptyScr,...} => 
    15 	 error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    16 		      ^"use prep_rls for storing rule-sets !")
    17        | Rls {scr=Script s,...} =>
    18 (* val Rls {scr=Script s,...} = assoc_rls rls;
    19    *)
    20 	 (ScrState ([(one_scr_arg s, t)], [], NONE, e_term, Sundef, true))
    21        | Seq {scr=EmptyScr,...} => 
    22 	 error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    23 		      ^"use prep_rls for storing rule-sets !")
    24        | Seq {srls=srls,scr=Script s,...} =>
    25 	 (ScrState ([(one_scr_arg s, t)], [], NONE, e_term, Sundef, true)))
    26   | init_istate (Rewrite_Set_Inst (subs, rls)) =
    27 (* val (Rewrite_Set_Inst (subs, rls)) = (get_obj g_tac pt p);
    28    *)
    29     let val (_, v)::_ = subs2subst (assoc_thy "Isac") subs
    30     in case assoc_rls rls of
    31            Rls {scr=EmptyScr,...} => 
    32 	   error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    33 			^"use prep_rls for storing rule-sets !")
    34 	 | Rls {scr=Script s,...} =>
    35 	   let val (a1, a2) = two_scr_arg s
    36 	   in (ScrState ([(a1, v), (a2, t)],[], NONE, e_term, Sundef,true)) end
    37 	 | Seq {scr=EmptyScr,...} => 
    38 	   error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    39 			^"use prep_rls for storing rule-sets !")
    40 (* val Seq {scr=Script s,...} = assoc_rls rls;
    41    *)
    42 	 | Seq {scr=Script s,...} =>
    43 	   let val (a1, a2) = two_scr_arg s
    44 	   in (ScrState ([(a1, v), (a2, t)],[], NONE, e_term, Sundef,true)) end
    45     end;
    46 *)
    47 (*~~~~~~~~~~~~~~~~~~~~~~copy for dev. until del.~~~~~~~~~~~~~~~~~~~~~~~~~*)
    48 fun init_istate (Rewrite_Set rls) t =
    49 (* val (Rewrite_Set rls) = (get_obj g_tac pt p);
    50    *)
    51     (case assoc_rls rls of
    52 	 Rrls {scr=sc as Rfuns {init_state=ii,...},...} => (RrlsState (ii t))
    53 (* val Rrls {scr=sc as Rfuns {init_state=ii,...},...} = assoc_rls rls;
    54    *)
    55        | Rls {scr=EmptyScr,...} => 
    56 	 error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    57 		      ^"use prep_rls for storing rule-sets !")
    58        | Rls {scr=Script s,...} =>
    59 (* val Rls {scr=Script s,...} = assoc_rls rls;
    60    *)
    61 	 (ScrState ([(one_scr_arg s, t)], [], NONE, e_term, Sundef, true))
    62        | Seq {scr=EmptyScr,...} => 
    63 	 error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    64 		      ^"use prep_rls for storing rule-sets !")
    65        | Seq {srls=srls,scr=Script s,...} =>
    66 	 (ScrState ([(one_scr_arg s, t)], [], NONE, e_term, Sundef, true)))
    67 (* val ((Rewrite_Set_Inst (subs, rls)), t) = ((get_obj g_tac pt p), t);
    68    *)
    69   | init_istate (Rewrite_Set_Inst (subs, rls)) t =
    70     let val (_, v)::_ = subs2subst (assoc_thy "Isac") subs
    71     (*...we suppose the substitution of only _one_ bound variable*)
    72     in case assoc_rls rls of
    73            Rls {scr=EmptyScr,...} => 
    74 	   error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    75 			^"use prep_rls for storing rule-sets !")
    76 	 | Rls {scr=Script s,...} =>
    77 	   let val (form, bdv) = two_scr_arg s
    78 	   in (ScrState ([(form, t), (bdv, v)],[], NONE, e_term, Sundef,true))
    79 	   end
    80 	 | Seq {scr=EmptyScr,...} => 
    81 	   error ("interSteps>..>init_istate: \""^rls^"\" has EmptyScr."
    82 			^"use prep_rls for storing rule-sets !")
    83 (* val Seq {scr=Script s,...} = assoc_rls rls;
    84    *)
    85 	 | Seq {scr=Script s,...} =>
    86 	   let val (form, bdv) = two_scr_arg s
    87 	   in (ScrState ([(form, t), (bdv, v)],[], NONE, e_term, Sundef,true))
    88 	   end
    89     end;
    90 
    91 
    92 (*.a taci holds alle information required to build a node in the calc-tree;
    93    a taci is assumed to be used efficiently such that the calc-tree
    94    resulting from applying a taci need not be stored separately;
    95    see "type calcstate".*)
    96 (*TODO.WN0504 redesign ??? or redesign generate ?? see "fun generate"
    97   TODO.WN0512 ? redesign this _list_:
    98   # only used for [Apply_Method + (Take or Subproblem)], i.e. for initacs
    99   # the latter problem may be resolved automatically if "fun autocalc" is 
   100     not any more used for the specify-phase and for changing the phases*)
   101 type taci = 
   102      (tac *            (*for comparison with input tac*)      
   103       tac_ *           (*for ptree generation*)
   104       (pos' *          (*after applying tac_, for ptree generation*)
   105        (istate * Proof.context)));       (*after applying tac_, for ptree generation*)
   106 val e_taci = (Empty_Tac, Empty_Tac_, (e_pos', (e_istate, e_ctxt))): taci;
   107 (* val (tac, tac_, (pos', istate))::_ = tacis';
   108    *)
   109 fun taci2str ((tac, tac_, (pos', (istate, _))):taci) =
   110     "( "^tac2str tac^", "^tac_2str tac_^", ( "^pos'2str pos'
   111     ^", "^istate2str istate^" ))";
   112 fun tacis2str tacis = (strs2str o (map (linefeed o taci2str))) tacis;
   113 
   114 datatype pblmet =       (*%^%*)
   115     Upblmet             (*undefined*)
   116   | Problem of pblID    (*%^%*)
   117   | Method of metID;    (*%^%*)
   118 fun pblmet2str (Problem pblID) = "Problem "^(strs2str pblID)(*%^%*)
   119   | pblmet2str (Method metID) = "Method "^(metID2str metID);(*%^%*)
   120       (*%^%*)   (*26.6. moved to sequent.sml: fun ~~~~~~~~~; was here below*)
   121 
   122 
   123 (* copy from 03.60.usecases.sml 15.11.99 *)
   124 datatype user_cmd = 
   125   Accept   | NotAccept | Example
   126 | YourTurn | MyTurn (* internal use only 7.6.02 java-sml*)   
   127 | Rules
   128 | DontKnow  (*| HowComes | WhatFor       7.6.02 java-sml*)
   129 | Undo      (*| Back          | Forward  7.6.02 java-sml*)
   130 | EndProof | EndSession
   131 | ActivePlus | ActiveMinus | SpeedPlus | SpeedMinus
   132                            (*Stepwidth...7.6.02 java-sml*)
   133 | Auto | NotAuto | Details;
   134 (* for test-print-outs *)
   135 fun user_cmd2str Accept     ="Accept"
   136   | user_cmd2str NotAccept  ="NotAccept"
   137   | user_cmd2str Example    ="Example"
   138   | user_cmd2str MyTurn     ="MyTurn"
   139   | user_cmd2str YourTurn   ="YourTurn"
   140   | user_cmd2str Rules	    ="Rules"
   141 (*| user_cmd2str HowComes   ="HowComes"*)
   142   | user_cmd2str DontKnow   ="DontKnow"
   143 (*| user_cmd2str WhatFor    ="WhatFor"
   144   | user_cmd2str Back       ="Back"*)
   145   | user_cmd2str Undo       ="Undo"
   146 (*| user_cmd2str Forward    ="Forward"*)
   147   | user_cmd2str EndProof   ="EndProof"
   148   | user_cmd2str EndSession ="EndSession"
   149   | user_cmd2str ActivePlus = "ActivePlus"
   150   | user_cmd2str ActiveMinus = "ActiveMinus"
   151   | user_cmd2str SpeedPlus = "SpeedPlus"
   152   | user_cmd2str SpeedMinus = "SpeedMinus"
   153   | user_cmd2str Auto = "Auto"
   154   | user_cmd2str NotAuto = "NotAuto"
   155   | user_cmd2str Details = "Details";
   156 
   157 
   158 
   159 (*3.5.00: TODO: foppFK eliminated in interface FE-KE !!!*)
   160 datatype foppFK =                  (* in DG cases div 2 *)
   161   EmptyFoppFK         (*DG internal*)
   162 | FormFK of cterm'
   163 | PpcFK of cterm' ppc;
   164 fun foppFK2str (FormFK ct') ="FormFK "^ct'
   165   | foppFK2str (PpcFK  ppc) ="PpcFK "^(ppc2str ppc)
   166   | foppFK2str EmptyFoppFK  ="EmptyFoppFK";
   167 
   168 
   169 datatype nest = Open | Closed | Nundef;
   170 fun nest2str Open = "Open"
   171   | nest2str Closed = "Closed"
   172   | nest2str Nundef = "Nundef";
   173 
   174 type indent = int;
   175 datatype edit = EdUndef | Write | Protect;
   176                                    (* bridge --> kernel *)
   177                                    (* bridge <-> kernel *)
   178 (* needed in dialog.sml *)         (* bridge <-- kernel *)
   179 fun edit2str EdUndef = "EdUndef"
   180   | edit2str Write = "Write"
   181   | edit2str Protect = "Protect";
   182 
   183 
   184 datatype inout = (*FIXME.WN1105 drop this: was required for proto0 with dialog in sml*)
   185   New_User | End_User                                          (*<->*)
   186 | New_Proof | End_Proof                                        (*<->*)
   187 | Command of user_cmd                                          (*-->*)
   188 | Request of string | Message of string                        (*<--*) 
   189 | Error_ of string  | System of string                         (*<--*)
   190 | FoPpcFK of foppFK                                            (*-->*)
   191 | FormKF of cellID * edit * indent * nest * cterm'             (*<--*)
   192 | PpcKF of cellID * edit * indent * nest * (pblmet * item ppc) (*<--*)
   193 | RuleFK of tac                                              (*-->*)
   194 | RuleKF of edit * tac                                       (*<--*)
   195 | RefinedKF of (pblID * ((itm list) * ((bool * term) list))) (*<--*)
   196 | Select of tac list                                         (*<--*)
   197 | RefineKF of match list                                       (*<--*)
   198 | Speed of int                                                 (*<--*)
   199 | Active of int                                                (*<--*)
   200 | Domain of domID;                                             (*<--*)
   201 
   202 fun inout2str End_Proof = "End_Proof"
   203   | inout2str (Command user_cmd) = "Command "^(user_cmd2str user_cmd)
   204   | inout2str (Request s) = "Request "^s
   205   | inout2str (Message s) = "Message "^s
   206   | inout2str (Error_  s) = "Error_ "^s
   207   | inout2str (System  s) = "System "^s
   208   | inout2str (FoPpcFK foppFK) = "FoPpcFK "^(foppFK2str foppFK)
   209   | inout2str (FormKF (cellID, edit, indent, nest, ct')) =  
   210 	       "FormKF ("^(string_of_int cellID)^","
   211 	       ^(edit2str edit)^","^(string_of_int indent)^","
   212 	       ^(nest2str nest)^",("
   213 	       ^ct' ^")"
   214   | inout2str (PpcKF (cellID, edit, indent, nest, (pm,itemppc))) =
   215 	       "PpcKF ("^(string_of_int cellID)^","
   216 	       ^(edit2str edit)^","^(string_of_int indent)^","
   217 	       ^(nest2str nest)^",("
   218 	       ^(pblmet2str pm)^","^(itemppc2str itemppc)^"))"
   219   | inout2str (RuleKF (edit,tac)) = "RuleKF "^
   220 	       pair2str(edit2str edit,tac2str tac)
   221   | inout2str (RuleFK tac) = "RuleFK "^(tac2str tac)  
   222   | inout2str (Select tacs)= 
   223 	       "Select "^((strs2str' o (map tac2str)) tacs)
   224   | inout2str (RefineKF ms)  = "RefineKF "^(matchs2str ms)
   225   | inout2str (Speed i) = "Speed "^(string_of_int i)
   226   | inout2str (Active i) = "Active "^(string_of_int i)
   227   | inout2str (Domain dI) = "Domain "^dI;
   228 fun inouts2str ios = (strs2str' o (map inout2str)) ios; 
   229 
   230 datatype mout =
   231   Form' of inout         (* packing cterm' | cterm' ppc *)
   232 | Problems of inout      (* passes specify (and solve)  *)
   233 | Error' of inout
   234 | EmptyMout;
   235 
   236 fun mout2str (Form' inout) ="Form' "^(inout2str inout)
   237   | mout2str (Error'  inout) ="Error' "^(inout2str inout)
   238   | mout2str (EmptyMout    ) ="EmptyMout";
   239 
   240 (*fun Form'2str (Form' )*)
   241 
   242 
   243 
   244 
   245 
   246 (* init pbl with ...,dsc,empty | [] *)
   247 fun init_pbl pbt = 
   248   let 
   249       fun pbt2itm (f, (d, t)) = 
   250           ((0, [], false, f, Inc ((d, []), (e_term, []))) : itm);
   251   in map pbt2itm pbt end;
   252 (*take formal parameters from pbt, for transfer from pbl/met-hierarchy*)
   253 fun init_pbl' pbt = 
   254   let 
   255     fun pbt2itm (f,(d,t)) = 
   256       ((0,[],false,f,Inc((d,[t]),(e_term,[]))):itm);
   257   in map pbt2itm pbt end;
   258 
   259 
   260 (*generate 1 ppobj in ptree*)
   261 (*TODO.WN0501: take calcstate as an argument (see embed_derive etc.)?specify?*)
   262 fun generate1 thy (Add_Given' (_, itmlist)) _ (pos as (p,p_)) pt = 
   263       (pos:pos',[],Form' (PpcKF (0,EdUndef,0,Nundef,(Upblmet, itms2itemppc thy [][]))),
   264          case p_ of
   265            Pbl => update_pbl pt p itmlist
   266 	       | Met => update_met pt p itmlist)
   267     (*WN110515 probably declare_constraints with input item (without dsc) --
   268       -- important when specifying without formalisation*)
   269   | generate1 thy (Add_Find' (_, itmlist)) _ (pos as (p,p_)) pt = 
   270       (pos,[],Form' (PpcKF (0,EdUndef,0,Nundef,(Upblmet,itms2itemppc thy [][]))),
   271          case p_ of
   272            Pbl => update_pbl pt p itmlist
   273 	       | Met => update_met pt p itmlist)
   274     (*WN110515 probably declare_constraints with input item (without dsc)*)
   275   | generate1 thy (Add_Relation' (_, itmlist)) _ (pos as (p,p_)) pt = 
   276       (pos,[],Form' (PpcKF (0,EdUndef,0,Nundef,(Upblmet,itms2itemppc thy [][]))),
   277          case p_ of
   278            Pbl => update_pbl pt p itmlist
   279 	       | Met => update_met pt p itmlist)
   280 
   281   | generate1 thy (Specify_Theory' domID) _ (pos as (p,_)) pt = 
   282     (pos,[],Form' (PpcKF (0,EdUndef,0,Nundef,(Upblmet,itms2itemppc thy [][]))),
   283      update_domID pt p domID)
   284 
   285   | generate1 thy (Specify_Problem' (pI, (ok, (itms, pre)))) _
   286 	      (pos as (p,_)) pt = 
   287     let val pt = update_pbl pt p itms
   288 	val pt = update_pblID pt p pI
   289     in ((p,Pbl),[],
   290 	Form' (PpcKF (0,EdUndef,0,Nundef,(Upblmet,itms2itemppc thy [][]))), 
   291 	pt) end
   292 
   293   | generate1 thy (Specify_Method' (mID, oris, itms)) _ 
   294 	      (pos as (p,_)) pt = 
   295     let val pt = update_oris pt p oris
   296 	val pt = update_met pt p itms
   297 	val pt = update_metID pt p mID
   298     in ((p,Met),[],
   299 	Form' (PpcKF (0,EdUndef,0,Nundef,(Upblmet,itms2itemppc thy [][]))), 
   300 	pt) end
   301 
   302   | generate1 thy (Model_Problem' (_, itms, met)) _ (pos as (p,_)) pt =
   303       let 
   304         val pt = update_pbl pt p itms
   305 	      val pt = update_met pt p met
   306      in (pos,[],Form'(PpcKF(0,EdUndef,0,Nundef, (Upblmet, itms2itemppc thy [] []))), pt)
   307      end
   308 
   309   | generate1 thy (Refine_Tacitly' (pI,pIre,domID,metID,pbl)) 
   310 	      _ (pos as (p,_)) pt = 
   311     let val pt = update_pbl pt p pbl
   312 	val pt = update_orispec pt p (domID,pIre,metID)
   313     in (pos,[],
   314 	Form'(PpcKF(0,EdUndef,0,Nundef,(Upblmet,itms2itemppc thy [][]))),
   315 	pt) end
   316 
   317   | generate1 thy (Refine_Problem' (pI,_)) _ (pos as (p,_)) pt =
   318     let val (dI,_,mI) = get_obj g_spec pt p
   319 	val pt = update_spec pt p (dI, pI, mI)
   320     in (pos,[],
   321 	Form'(PpcKF(0,EdUndef,0,Nundef,(Upblmet,itms2itemppc thy [][]))),pt)
   322     end
   323 
   324   | generate1 thy (Apply_Method' (_,topt, is, ctxt)) _ (pos as (p,p_)) pt = 
   325     ((*tracing("###generate1 Apply_Method': pos = "^pos'2str (p,p_));
   326      tracing("###generate1 Apply_Method': topt= "^termopt2str topt);
   327      tracing("###generate1 Apply_Method': is  = "^istate2str is);*)
   328      case topt of 
   329 	 SOME t => 
   330 	 let val (pt,c) = cappend_form pt p (is, ctxt) t
   331 	     (*val _= tracing("###generate1 Apply_Method: after cappend")*)
   332 	 in (pos,c, EmptyMout,pt)
   333 	 end
   334        | NONE => 
   335 	 (pos,[],EmptyMout,update_env pt p (SOME (is, ctxt))))
   336 (* val (thy, (Take' t), l, (p,p_), pt) = 
   337        ((assoc_thy "Isac"), tac_, is, pos, pt);
   338    *)
   339   | generate1 thy (Take' t) l (p,p_) pt = (* val (Take' t) = m; *)
   340   let (*val _=tracing("### generate1: Take' pos="^pos'2str (p,p_));*)
   341       val p = let val (ps,p') = split_last p(*no connex to prev.ppobj*)
   342 	    in if p'=0 then ps@[1] else p end;
   343     val (pt,c) = cappend_form pt p l t;
   344   in ((p,Frm):pos', c, 
   345       Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str t)), pt) end
   346 
   347 (* val (l, (p,p_)) = (RrlsState is, p);
   348 
   349    val (thy, Begin_Trans' t, l, (p,Frm), pt) =
   350        (assoc_thy "Isac", tac_, is, p, pt);
   351    *)
   352   | generate1 thy (Begin_Trans' t) l (p,Frm) pt =
   353   let (* print_depth 99;
   354 	 map fst (get_interval ([],Pbl) ([],Res) 9999 pt);print_depth 3;
   355 	 *)
   356       val (pt,c) = cappend_form pt p l t
   357       (* print_depth 99;
   358 	 map fst (get_interval ([],Pbl) ([],Res) 9999 pt);print_depth 3;
   359 	 *)
   360       val pt = update_branch pt p TransitiveB (*040312*)
   361       (*replace the old PrfOjb ~~~~~*)
   362       val p = (lev_on o lev_dn(*starts with [...,0]*)) p; 
   363       val (pt,c') = cappend_form pt p l t(*FIXME.0402 same istate ???*);
   364   in ((p,Frm), c @ c', Form' (FormKF (~1,EdUndef,(length p), Nundef, 
   365 				 term2str t)), pt) end
   366 
   367   (* val (thy, Begin_Trans' t, l, (p,Res), pt) =
   368 	 (assoc_thy "Isac", tac_, is, p, pt);
   369       *)
   370   | generate1 thy (Begin_Trans' t) l (p       ,Res) pt =
   371     (*append after existing PrfObj    _________*)
   372     generate1 thy (Begin_Trans' t) l (lev_on p,Frm) pt
   373 
   374   | generate1 thy (End_Trans' tasm) l (p,p_) pt =
   375       let
   376         val p' = lev_up p
   377         val (pt,c) = append_result pt p' l tasm Complete;
   378       in ((p',Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str t)), pt) end
   379 
   380   | generate1 thy (Rewrite_Inst' (_,_,_,_,subs',thm',f,(f', asm))) (is, ctxt) (p,p_) pt =
   381       let
   382         val (pt,c) = cappend_atomic pt p (is, insert_assumptions asm ctxt) f
   383           (Rewrite_Inst (subst2subs subs',thm')) (f',asm) Complete;
   384         val pt = update_branch pt p TransitiveB
   385       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str f')), pt) end
   386 
   387   | generate1 thy (Rewrite' (thy',ord',rls',pa,thm',f,(f',asm))) (is, ctxt) (p,p_) pt =
   388       let
   389         val (pt,c) = cappend_atomic pt p (is, insert_assumptions asm ctxt) f
   390           (Rewrite thm') (f',asm) Complete
   391         val pt = update_branch pt p TransitiveB
   392       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str f')), pt) end
   393 
   394   | generate1 thy (Rewrite_Asm' all) l p pt = generate1 thy (Rewrite' all) l p pt
   395 
   396   | generate1 thy (Rewrite_Set_Inst' (_,_,subs',rls',f,(f',asm))) (is, ctxt) (p,p_) pt =
   397       let
   398         val (pt,c) = cappend_atomic pt p (is, insert_assumptions asm ctxt) f 
   399           (Rewrite_Set_Inst (subst2subs subs',id_rls rls')) (f',asm) Complete
   400         val pt = update_branch pt p TransitiveB
   401       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str f')), pt) end
   402 
   403   | generate1 thy (Detail_Set_Inst' (_,_,subs,rls,f,(f',asm))) (is, ctxt) (p,p_) pt =
   404       let
   405         val ctxt' = insert_assumptions asm ctxt
   406         val (pt,c) = cappend_form pt p (is, ctxt') f 
   407         val pt = update_branch pt p TransitiveB
   408  
   409        val is = init_istate (Rewrite_Set_Inst (subst2subs subs, id_rls rls)) f 
   410         val tac_ = Apply_Method' (e_metID, SOME t, is, ctxt')
   411         val pos' = ((lev_on o lev_dn) p, Frm)
   412       in (*implicit Take*) generate1 thy tac_ (is, ctxt') pos' pt end
   413 
   414   | generate1 thy (Rewrite_Set' (_,_,rls',f,(f',asm))) (is, ctxt) (p,p_) pt =
   415       let
   416         val (pt,c) = cappend_atomic pt p (is, insert_assumptions asm ctxt) f 
   417           (Rewrite_Set (id_rls rls')) (f',asm) Complete
   418         val pt = update_branch pt p TransitiveB
   419       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str f')), pt) end
   420 
   421   | generate1 thy (Detail_Set' (_,_,rls,f,(f',asm))) (is, ctxt) (p,p_) pt =
   422       let
   423         val ctxt' = insert_assumptions asm ctxt
   424         val (pt,c) = cappend_form pt p (is, ctxt') f 
   425         val pt = update_branch pt p TransitiveB
   426 
   427         val is = init_istate (Rewrite_Set (id_rls rls)) f
   428         val tac_ = Apply_Method' (e_metID, SOME t, is, ctxt')
   429         val pos' = ((lev_on o lev_dn) p, Frm)
   430       in (*implicit Take*) generate1 thy tac_ (is, ctxt') pos' pt end
   431 
   432   | generate1 thy (Check_Postcond' (pI, (scval, asm))) l (p,p_) pt =
   433       let val (pt,c) = append_result pt p l (scval, asm) Complete
   434       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str scval)), pt) end
   435 
   436   | generate1 thy (Calculate' (thy',op_,f,(f',thm'))) l (p,p_) pt =
   437       let val (pt,c) = cappend_atomic pt p l f (Calculate op_) (f',[]) Complete;
   438       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str f')), pt) end
   439 
   440   | generate1 thy (Check_elementwise' (consts,pred,(f',asm))) l (p,p_) pt =
   441       let
   442         val (pt,c) = cappend_atomic pt p l consts (Check_elementwise pred) (f',asm) Complete;
   443       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str f')), pt) end
   444 
   445   | generate1 thy (Or_to_List' (ors,list)) l (p,p_) pt =
   446       let val (pt,c) = cappend_atomic pt p l ors Or_to_List (list,[]) Complete;
   447       in ((p,Res), c, Form' (FormKF(~1,EdUndef,(length p), Nundef, term2str list)), pt) end
   448 
   449   | generate1 thy (Substitute' (_, _, subte, t, t')) l (p,p_) pt =
   450       let 
   451         val (pt,c) =
   452           cappend_atomic pt p l t (Substitute (subte2sube subte)) (t',[]) Complete;
   453         in ((p,Res), c, Form' (FormKF(~1,EdUndef,(length p), Nundef, term2str t')), pt) 
   454         end
   455 
   456   | generate1 thy (Tac_ (_,f,id,f')) l (p,p_) pt =
   457       let
   458         val (pt,c) =
   459           cappend_atomic pt p l (str2term f) (Tac id) (str2term f',[]) Complete;
   460       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, f')), pt)end
   461 
   462   | generate1 thy (Subproblem' ((domID, pblID, metID), oris, hdl, fmz_, ctxt, f)) l (p,p_) pt =
   463       let
   464 	      val (pt,c) =
   465           cappend_problem pt p l (fmz_, (domID, pblID, metID)) (oris, (domID, pblID, metID), hdl);
   466         val pt = update_ctxt pt p ctxt
   467 	      val f = Syntax.string_of_term (thy2ctxt thy) f;
   468       in ((p,Pbl), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, f)), pt) end
   469 
   470   | generate1 thy m' _ _ _ = 
   471       error ("generate1: not impl.for "^(tac_2str m'));
   472 
   473 fun generate_inconsistent _ (Rewrite' (_,_,_,_, thm', f, (f', asm))) (is, ctxt) (p,_) pt =
   474       let
   475         val (pt,c) = cappend_atomic pt p (is, insert_assumptions asm ctxt) f
   476           (Rewrite thm') (f', asm) Inconsistent
   477         val pt = update_branch pt p TransitiveB
   478       in ((p,Res), c, Form' (FormKF (~1,EdUndef,(length p), Nundef, term2str f')), pt)end
   479 
   480 fun generate_hard thy m' (p,p_) pt =
   481   let  
   482     val p =
   483       case p_ of
   484         Frm => p | Res => lev_on p
   485       | _ => error ("generate_hard: call by " ^ pos'2str (p,p_));
   486   in generate1 thy m' (e_istate, e_ctxt) (p,p_) pt end;
   487 
   488 (*tacis are in reverse order from nxt_solve_/specify_: last = fst to insert*)
   489 fun generate ([]: taci list) ptp = ptp
   490   | generate tacis (pt, c, _:pos'(*!dropped!WN0504redesign generate/tacis?*))= 
   491       let
   492         val (tacis', (_, tac_, (p, is))) = split_last tacis
   493 	      val (p',c',_,pt') = generate1 (assoc_thy "Isac") tac_ is p pt
   494       in generate tacis' (pt', c@c', p') end;
   495 
   496 (*. a '_deriv'ation is constructed during 'reverse rewring' by an Rrls       *
   497  *  of for connecting a user-input formula with the current calc-state.	     *
   498  *# It is somewhat incompatible with the rest of the math-engine:	     *
   499  *  (1) it is not created by a script					     *
   500  *  (2) thus there cannot be another user-input within a derivation	     *
   501  *# It suffers particularily from the not-well-foundedness of the math-engine*
   502  *  (1) FIXME other branchtyptes than Transitive will change 'embed_deriv'   *
   503  *  (2) FIXME and eventually 'compare_step' (ie. the script interpreter)     *
   504  *  (3) FIXME and eventually 'lev_back'                                      *
   505  *# SOME improvements are evident FIXME.040215 '_deriv'ation:	             *
   506  *  (1) FIXME nest Rls_ in 'make_deriv'					     *
   507  *  (2) FIXME do the not-reversed part in 'make_deriv' by scripts -- thus    *
   508  *	user-input will become possible in this part of a derivation	     *
   509  *  (3) FIXME do (2) only if a derivation has been found -- for efficiency,  *
   510  *	while a non-derivable inform requires to step until End_Proof'	     *
   511  *  (4) FIXME find criteria on when _not_ to step until End_Proof'           *
   512  *  (5) FIXME 
   513 .*)
   514 (*.update pos in tacis for embedding by generate.*)
   515 (* val 
   516    *)
   517 fun insert_pos _ [] = []
   518   | insert_pos (p:pos) (((tac,tac_,(_, ist))::tacis):taci list) = 
   519     ((tac,tac_,((p, Res), ist)):taci)
   520     ::((insert_pos (lev_on p) tacis):taci list);
   521 
   522 fun res_from_taci (_, Rewrite'(_,_,_,_,_,_,(res, asm)), _) = (res, asm)
   523   | res_from_taci (_, Rewrite_Set'(_,_,_,_,(res, asm)), _) = (res, asm)
   524   | res_from_taci (_, tac_, _) = 
   525     error ("res_from_taci: called with" ^ tac_2str tac_);
   526 
   527 (*.embed the tacis created by a '_deriv'ation; sys.form <> input.form
   528   tacis are in order, thus are reverted for generate.*)
   529 (* val (tacis, (pt, pos as (p, Frm))) =  (tacis', ptp);
   530    *)
   531 fun embed_deriv (tacis:taci list) (pt, pos as (p, Frm):pos') =
   532   (*inform at Frm: replace the whole PrfObj by a Transitive-ProfObj FIXME?0402
   533     and transfer the istate (from _after_ compare_deriv) from Frm to Res*)
   534     let val (res, asm) = (res_from_taci o last_elem) tacis
   535 	val (SOME (ist, ctxt),_) = get_obj g_loc pt p
   536 	val form = get_obj g_form pt p
   537       (*val p = lev_on p; ---------------only difference to (..,Res) below*)
   538 	val tacis = (Begin_Trans, Begin_Trans' form, (pos, (Uistate, ctxt)))
   539 		    ::(insert_pos ((lev_on o lev_dn) p) tacis)
   540 		    @ [(End_Trans, End_Trans' (res, asm),
   541 			(pos_plus (length tacis) (lev_dn p, Res), 
   542 			 (new_val res ist, ctxt)))]
   543 	val {nrls,...} = get_met (get_obj g_metID pt (par_pblobj pt p))
   544 	val (pt, c, pos as (p,_)) = generate (rev tacis) (pt, [], (p, Res))
   545 	val pt = update_tac pt p (Derive (id_rls nrls))
   546         (*FIXME.040216 struct.ctree*)
   547 	val pt = update_branch pt p TransitiveB
   548     in (c, (pt, pos:pos')) end
   549 
   550 (* val (tacis, (pt, (p, Res))) =  (tacis', ptp);
   551    *)
   552   | embed_deriv tacis (pt, (p, Res)) =
   553   (*inform at Res: append a Transitive-PrfObj FIXME?0402 other branch-types ?
   554     and transfer the istate (from _after_ compare_deriv) from Res to new Res*)
   555     let val (res, asm) = (res_from_taci o last_elem) tacis
   556 	val (_, SOME (ist, ctxt)) = get_obj g_loc pt p
   557 	val (f,a) = get_obj g_result pt p
   558 	val p = lev_on p(*---------------only difference to (..,Frm) above*);
   559 	val tacis = (Begin_Trans, Begin_Trans' f, ((p, Frm), (Uistate, ctxt)))
   560 		    ::(insert_pos ((lev_on o lev_dn) p) tacis)
   561 		    @ [(End_Trans, End_Trans' (res, asm), 
   562 			(pos_plus (length tacis) (lev_dn p, Res), 
   563 			 (new_val res ist, ctxt)))];
   564 	val {nrls,...} = get_met (get_obj g_metID pt (par_pblobj pt p))
   565 	val (pt, c, pos as (p,_)) = generate (rev tacis) (pt, [], (p, Res))
   566 	val pt = update_tac pt p (Derive (id_rls nrls))
   567         (*FIXME.040216 struct.ctree*)
   568 	val pt = update_branch pt p TransitiveB
   569     in (c, (pt, pos)) end;