src/Tools/isac/Interpret/solve.sml
author Mathias Lehnfeld <e0726734@student.tuwien.ac.at>
Mon, 18 Apr 2011 15:24:57 +0200
branchdecompose-isar
changeset 41960 3048fe25fe67
parent 41959 a0d6a7c3e1df
child 41968 3228aa46fd30
permissions -rw-r--r--
ctxt intro finished (no environments)
     1 (* solve an example by interpreting a method's script
     2    (c) Walther Neuper 1999
     3 
     4 use"ME/solve.sml";
     5 use"solve.sml";
     6 *)
     7 
     8 fun safe (ScrState (_,_,_,_,s,_)) = s
     9   | safe (RrlsState _) = Safe;
    10 
    11 type mstID = string;
    12 type tac'_ = mstID * tac; (*DG <-> ME*)
    13 val e_tac'_ = ("Empty_Tac", Empty_Tac):tac'_;
    14 
    15 fun mk_tac'_   m = case m of
    16   Init_Proof (ppc, spec)    => ("Init_Proof", Init_Proof (ppc, spec )) 
    17 | Model_Problem             => ("Model_Problem", Model_Problem)
    18 | Refine_Tacitly pblID      => ("Refine_Tacitly", Refine_Tacitly pblID)
    19 | Refine_Problem pblID      => ("Refine_Problem", Refine_Problem pblID)
    20 | Add_Given cterm'          => ("Add_Given", Add_Given cterm') 
    21 | Del_Given cterm'          => ("Del_Given", Del_Given cterm') 
    22 | Add_Find cterm'           => ("Add_Find", Add_Find cterm') 
    23 | Del_Find cterm'           => ("Del_Find", Del_Find cterm') 
    24 | Add_Relation cterm'       => ("Add_Relation", Add_Relation cterm') 
    25 | Del_Relation cterm'       => ("Del_Relation", Del_Relation cterm') 
    26 
    27 | Specify_Theory domID	    => ("Specify_Theory", Specify_Theory domID) 
    28 | Specify_Problem pblID     => ("Specify_Problem", Specify_Problem pblID)
    29 | Specify_Method metID	    => ("Specify_Method", Specify_Method metID) 
    30 | Apply_Method metID	    => ("Apply_Method", Apply_Method metID) 
    31 | Check_Postcond pblID	    => ("Check_Postcond", Check_Postcond pblID)
    32 | Free_Solve                => ("Free_Solve",Free_Solve)
    33 		    
    34 | Rewrite_Inst (subs, thm') => ("Rewrite_Inst", Rewrite_Inst (subs, thm')) 
    35 | Rewrite thm'		    => ("Rewrite", Rewrite thm') 
    36 | Rewrite_Asm thm'	    => ("Rewrite_Asm", Rewrite_Asm thm') 
    37 | Rewrite_Set_Inst (subs, rls')
    38                => ("Rewrite_Set_Inst", Rewrite_Set_Inst (subs, rls')) 
    39 | Rewrite_Set rls'          => ("Rewrite_Set", Rewrite_Set rls') 
    40 | End_Ruleset		    => ("End_Ruleset", End_Ruleset)
    41 
    42 | End_Detail                => ("End_Detail", End_Detail)
    43 | Detail_Set rls'           => ("Detail_Set", Detail_Set rls')
    44 | Detail_Set_Inst (s, rls') => ("Detail_Set_Inst", Detail_Set_Inst (s, rls'))
    45 
    46 | Calculate op_             => ("Calculate", Calculate op_)
    47 | Substitute sube           => ("Substitute", Substitute sube) 
    48 | Apply_Assumption cts'	    => ("Apply_Assumption", Apply_Assumption cts')
    49 
    50 | Take cterm'               => ("Take", Take cterm') 
    51 | Take_Inst cterm'          => ("Take_Inst", Take_Inst cterm') 
    52 | Group (con, ints) 	    => ("Group", Group (con, ints)) 
    53 | Subproblem (domID, pblID) => ("Subproblem", Subproblem (domID, pblID)) 
    54 (*
    55 | Subproblem_Full(spec,cts')=> ("Subproblem_Full", Subproblem_Full(spec,cts')) 
    56 *)
    57 | End_Subproblem            => ("End_Subproblem",End_Subproblem)
    58 | CAScmd cterm'		    => ("CAScmd", CAScmd cterm')
    59 			    
    60 | Split_And                 => ("Split_And", Split_And) 
    61 | Conclude_And		    => ("Conclude_And", Conclude_And) 
    62 | Split_Or                  => ("Split_Or", Split_Or) 
    63 | Conclude_Or		    => ("Conclude_Or", Conclude_Or) 
    64 | Begin_Trans               => ("Begin_Trans", Begin_Trans) 
    65 | End_Trans		    => ("End_Trans", End_Trans) 
    66 | Begin_Sequ                => ("Begin_Sequ", Begin_Sequ) 
    67 | End_Sequ                  => ("End_Sequ", Begin_Sequ) 
    68 | Split_Intersect           => ("Split_Intersect", Split_Intersect) 
    69 | End_Intersect		    => ("End_Intersect", End_Intersect) 
    70 | Check_elementwise cterm'  => ("Check_elementwise", Check_elementwise cterm')
    71 | Or_to_List                => ("Or_to_List", Or_to_List) 
    72 | Collect_Trues	            => ("Collect_Results", Collect_Trues) 
    73 			    
    74 | Empty_Tac               => ("Empty_Tac",Empty_Tac)
    75 | Tac string              => ("Tac",Tac string)
    76 | User                      => ("User",User)
    77 | End_Proof'                => ("End_Proof'",End_Proof'); 
    78 
    79 (*Detail*)
    80 val empty_tac'_ = (mk_tac'_ Empty_Tac):tac'_;
    81 
    82 fun mk_tac ((_,m):tac'_) = m; 
    83 fun mk_mstID ((mI,_):tac'_) = mI;
    84 
    85 fun tac'_2str ((ID,ms):tac'_) = ID ^ (tac2str ms);
    86 (* TODO: tac2str, tac'_2str NOT tested *)
    87 
    88 
    89 
    90 type squ = ptree; (* TODO: safe etc. *)
    91 
    92 (*13.9.02--------------
    93 type ctr = (loc * pos) list;
    94 val ops = [("PLUS","Groups.plus_class.plus"),("MINUS","Groups.minus_class.minus"),("TIMES","Groups.times_class.times"),
    95 	   ("cancel","cancel"),("pow","pow"),("sqrt","sqrt")];
    96 ML {* 
    97 @{term "PLUS"};   (*Free ("PLUS", "'a") : term*)
    98 @{term "plus"};   (*Const ("Groups.plus_class.plus", "'a => 'a => 'a")*)
    99 @{term "MINUS"};  (*Free ("MINUS", "'a")*)
   100 @{term "minus"};  (*Const ("Groups.minus_class.minus", "'a => 'a => 'a")*)
   101 @{term "TIMES"};  (*Free ("TIMES", "'a")*)
   102 @{term "times"};  (*Const ("Groups.times_class.times", "'a => 'a => 'a")*)
   103 @{term "CANCEL"}; (*Free ("CANCEL", "'a")*)
   104 @{term "cancel"}; (*Free ("cancel", "'a")*)
   105 @{term "POWER"};  (*Free ("POWER", "'a")*)
   106 @{term "pow"};    (*Free ("pow", "'a")*)
   107 @{term "SQRT"};   (*Free ("SQRT", "'a")*)
   108 @{term "sqrt"};   (*Const ("NthRoot.sqrt", "RealDef.real => RealDef.real")*)
   109 *}
   110 fun op_intern op_ =
   111   case assoc (ops, op_) of
   112     SOME op' => op' | NONE => error ("op_intern: no op= "^op_);
   113 -----------------------*)
   114 
   115 
   116 
   117 (* use"ME/solve.sml";
   118    use"solve.sml";
   119 
   120 val ttt = (term_of o the o (parse thy))"Substitute [(bdv,x)] g";
   121 val ttt = (term_of o the o (parse thy))"Rewrite thmid True g";
   122 
   123   Const ("Script.Rewrite'_Inst",_) $ sub $ Free (thm',_) $ Const (pa,_) $ f'
   124    *)
   125 
   126 
   127 
   128 val specsteps = ["Init_Proof","Refine_Tacitly","Refine_Problem",
   129 		 "Model_Problem",(*"Match_Problem",*)
   130 		 "Add_Given","Del_Given","Add_Find","Del_Find",
   131 		 "Add_Relation","Del_Relation",
   132 		 "Specify_Theory","Specify_Problem","Specify_Method"];
   133 
   134 "-----------------------------------------------------------------------";
   135 
   136 
   137 fun step2taci ((tac_, _, pt, p, _):step) = (*FIXXME.040312: redesign step*)
   138     (tac_2tac tac_, tac_, (p, get_loc pt p)):taci;
   139 
   140 
   141 (*FIXME.WN050821 compare solve ... nxt_solv*)
   142 (* val ("Apply_Method",Apply_Method' (mI,_))=(mI,m);
   143    val (("Apply_Method",Apply_Method' (mI,_,_)),pt, pos as (p,_))=(m,pt, pos);
   144    *)
   145 fun solve ("Apply_Method", m as Apply_Method' (mI, _, _, _)) 
   146 	  (pt:ptree, (pos as (p,_))) =
   147   let val {srls,...} = get_met mI;
   148     val PblObj{meth=itms,...} = get_obj I pt p;
   149     val thy' = get_obj g_domID pt p;
   150     val thy = assoc_thy thy';
   151     val (is as ScrState (env,_,_,_,_,_), ctxt, sc) = init_scrstate thy itms mI;
   152     val ini = init_form thy sc env;
   153     val p = lev_dn p;
   154   in 
   155       case ini of
   156 	  SOME t => (* val SOME t = ini; 
   157 	             *)
   158 	  let val (pos,c,_,pt) = 
   159 		  generate1 thy (Apply_Method' (mI, SOME t, is, ctxt))
   160 			    (is, ctxt) (lev_on p, Frm)(*implicit Take*) pt;
   161 	  in ("ok",([(Apply_Method mI, Apply_Method' (mI, SOME t, is, ctxt), 
   162 		      ((lev_on p, Frm), (is, ctxt)))], c, (pt,pos)):calcstate') 
   163 	  end	      
   164 	| NONE => (*execute the first tac in the Script, compare solve m*)
   165 	  let val (m', (is', ctxt'), _) = next_tac (thy', srls) (pt, (p, Res)) sc (is, ctxt);
   166 	      val d = e_rls (*FIXME: get simplifier from domID*);
   167 	  in 
   168 	      case locate_gen (thy',srls) m' (pt,(p, Res))(sc,d) (is', ctxt') of 
   169 		  Steps (is'', ss as (m'',f',pt',p',c')::_) =>
   170 (* val Steps (is'', ss as (m'',f',pt',p',c')::_) =
   171        locate_gen (thy',srls) m'  (pt,(p,Res)) (sc,d) is';
   172  *)
   173 		  ("ok", (map step2taci ss, c', (pt',p')))
   174 		| NotLocatable =>  
   175 		  let val (p,ps,f,pt) = 
   176 			  generate_hard (assoc_thy "Isac") m (p,Frm) pt;
   177 		  in ("not-found-in-script",
   178 		      ([(tac_2tac m, m, (pos, (is, ctxt)))], ps, (pt,p))) end
   179     (*just-before------------------------------------------------------
   180 	      ("ok",([(Apply_Method mI,Apply_Method'(mI,NONE,e_istate),
   181 		       (pos, is))],
   182 		     [], (update_env pt (fst pos) (SOME is),pos)))
   183      -----------------------------------------------------------------*)
   184 	  end
   185   end
   186 
   187   | solve ("Free_Solve", Free_Solve')  (pt,po as (p,_)) =
   188   let (*val _=tracing"###solve Free_Solve";*)
   189     val p' = lev_dn_ (p,Res);
   190     val pt = update_metID pt (par_pblobj pt p) e_metID;
   191   in ("ok", ((*(p',Uistate,Empty_Tac_), EmptyMout, Empty_Tac, Unsafe,*)
   192       [(Empty_Tac, Empty_Tac_, (po, (Uistate, e_ctxt)))], [], (pt,p'))) end
   193 
   194 (* val (("Check_Postcond",Check_Postcond' (pI,_)), (pt,(pos as (p,p_)))) =
   195        (  m,                                       (pt, pos));
   196    *)
   197   | solve ("Check_Postcond",Check_Postcond' (pI,_)) (pt,(pos as (p,p_))) =
   198     let (*val _=tracing"###solve Check_Postcond";*)
   199       val pp = par_pblobj pt p
   200       val asm = (case get_obj g_tac pt p of
   201 		    Check_elementwise _ => (*collects and instantiates asms*)
   202 		    (snd o (get_obj g_result pt)) p
   203 		  | _ => get_assumptions_ pt (p,p_))
   204 	  handle _ => [] (*WN.27.5.03 asms in subpbls not completely clear*)
   205       val metID = get_obj g_metID pt pp;
   206       val {srls=srls,scr=sc,...} = get_met metID;
   207       val loc as (ScrState (E,l,a,_,_,b), ctxt) = get_loc pt (p,p_); 
   208      (*val _= tracing("### solve Check_postc, subpbl pos= "^(pos'2str (p,p_)));
   209       val _= tracing("### solve Check_postc, is= "^(istate2str is));*)
   210       val thy' = get_obj g_domID pt pp;
   211       val thy = assoc_thy thy';
   212       val (_,_,(scval,scsaf)) = next_tac (thy',srls) (pt,(p,p_)) sc loc;
   213       (*val _= tracing("### solve Check_postc, scval= "^(term2str scval));*)
   214 
   215     in if pp = [] then
   216 	   let val is = ScrState (E,l,a,scval,scsaf,b)
   217 	       val tac_ = Check_Postcond'(pI,(scval, map term2str asm))
   218 	       val (pos,ps,f,pt) = generate1 thy tac_ (is, ctxt) (pp,Res) pt;
   219 	   in ("ok", ((*(([],Res),is,End_Proof''), f, End_Proof', scsaf,*)
   220 	       [(Check_Postcond pI, tac_, ((pp,Res),(is, ctxt)))], ps,(pt,pos))) end
   221        else
   222         let
   223 	  (*resume script of parpbl, transfer value of subpbl-script*)
   224         val ppp = par_pblobj pt (lev_up p);
   225 	val thy' = get_obj g_domID pt ppp;
   226         val thy = assoc_thy thy';
   227 	val metID = get_obj g_metID pt ppp;
   228         val sc = (#scr o get_met) metID;
   229         val (ScrState (E,l,a,_,_,b), ctxt') = get_loc pt (pp(*!/p/*),Frm); 
   230 	      val ctxt'' = transfer_from_subproblem ctxt ctxt'
   231         val ((p,p_),ps,f,pt) = 
   232 	    generate1 thy (Check_Postcond' (pI, (scval, map term2str asm)))
   233 		(ScrState (E,l,a,scval,scsaf,b), ctxt'') (pp,Res) pt;
   234        in ("ok",(*((pp,Res),is',nx), f, tac_2tac nx, scsaf,*)
   235 	   ([(Check_Postcond pI, Check_Postcond'(pI,(scval, map term2str asm)),
   236 	      ((pp,Res), (ScrState (E,l,a,scval,scsaf,b), ctxt'')))],ps,(pt,(p,p_))))
   237 	end
   238     end
   239 (* val (msg, cs') = 
   240     ("ok",([(Check_Postcond pI,Check_Postcond'(pI, (scval, map term2str asm))),
   241 	    ((pp,Res),(ScrState (E,l,a,scval,scsaf,b)))], (pt,(p,p_))));
   242     val (_,(pt',p')) = cs';
   243    (tracing o istate2str) (get_istate pt' p');
   244    (term2str o fst) (get_obj g_result pt' (fst p'));
   245    *)
   246 
   247 (* tracing(istate2str(get_istate pt (p,p_)));
   248    *)
   249   | solve (_,End_Proof'') (pt, (p,p_)) =
   250       ("end-proof",
   251        ((*(([],Res),Uistate,Empty_Tac_), EmptyMout, Empty_Tac, Safe,*)
   252        [(Empty_Tac,Empty_Tac_,(([],Res),(Uistate, e_ctxt)))],[],(pt,(p,p_))))
   253 
   254 (*-----------vvvvvvvvvvv could be done by generate1 ?!?*)
   255   | solve (_,End_Detail' t) (pt,(p,p_)) =
   256     let val pr as (p',_) = (lev_up p, Res)
   257 	val pp = par_pblobj pt p
   258 	val r = (fst o (get_obj g_result pt)) p' 
   259 	(*Rewrite_Set* done at Detail_Set*: this result is already in ptree*)
   260 	val thy' = get_obj g_domID pt pp
   261 	val (srls, is, sc) = from_pblobj' thy' pr pt
   262 	val (tac_,is',_) = next_tac (thy',srls) (pt,pr) sc is
   263     in ("ok", ((*((pp,Frm(*???*)),is,tac_), 
   264 	Form' (FormKF (~1, EdUndef, length p', Nundef, term2str r)),
   265 	tac_2tac tac_, Sundef,*)
   266 	[(End_Detail, End_Detail' t , 
   267 	  ((p,p_), get_loc pt (p,p_)))], [], (pt,pr))) end
   268 
   269   | solve (mI,m) (pt, po as (p,p_)) =
   270 (* val ((mI,m), (pt, po as (p,p_))) = (m, (pt, pos));
   271    *)
   272     if e_metID = get_obj g_metID pt (par_pblobj pt p)(*29.8.02:
   273 						      could be detail, too !!*)
   274     then let val ((p,p_),ps,f,pt) = 
   275 		 generate1 (assoc_thy (get_obj g_domID pt (par_pblobj pt p))) 
   276 			   m (e_istate, e_ctxt) (p,p_) pt;
   277 	 in ("no-method-specified", (*Free_Solve*)
   278 	     ((*((p,p_),Uistate,Empty_Tac_),f, Empty_Tac, Unsafe,*)
   279 	     [(Empty_Tac,Empty_Tac_, ((p,p_),(Uistate, e_ctxt)))], ps, (pt,(p,p_)))) end
   280     else
   281 	let 
   282 	    val thy' = get_obj g_domID pt (par_pblobj pt p);
   283 	    val (srls, is, sc) = from_pblobj_or_detail' thy' (p,p_) pt;
   284 (*val _= tracing("### solve, before locate_gen p="^(pos'2str(p,p_)));*)
   285 		val d = e_rls; (*FIXME: canon.simplifier for domain is missing
   286 				8.01: generate from domID?*)
   287 	in case locate_gen (thy',srls) m  (pt,(p,p_)) (sc,d) is of 
   288 	       Steps (is', ss as (m',f',pt',p',c')::_) =>
   289 (* val Steps (is', ss as (m',f',pt',p',c')::_) =
   290        locate_gen (thy',srls) m  (pt,(p,p_)) (sc,d) is;
   291  *)
   292 	       let (*val _= tracing("### solve, after locate_gen: is= ")
   293 		       val _= tracing(istate2str is')*)
   294 		   (*val nxt_ = 
   295 		       case p' of (*change from solve to model subpbl*)
   296 			   (_,Pbl) => nxt_model_pbl m' (pt',p')
   297 			 | _ => fst3 (next_tac (thy',srls) (pt',p') sc is');*) 
   298 	       (*27.8.02:next_tac may change to other branches in pt FIXXXXME*)
   299 	       in ("ok", ((*(p',is',nxt_), f', tac_2tac nxt_, safe is',*)
   300 		   map step2taci ss, c', (pt',p'))) end
   301 	     | NotLocatable =>  
   302 	       let val (p,ps,f,pt) = 
   303 		       generate_hard (assoc_thy "Isac") m (p,p_) pt;
   304 	       in ("not-found-in-script",
   305 		   ((*(p,Uistate,Empty_Tac_),f, Empty_Tac, Unsafe,*) 
   306 		   [(tac_2tac m, m, (po,is))], ps, (pt,p))) end
   307 	end;
   308 
   309 
   310 (*FIXME.WN050821 compare solve ... nxt_solv*)
   311 (* nxt_solv (Apply_Method'     vvv FIXME: get args in applicable_in *)
   312 fun nxt_solv (Apply_Method' (mI,_,_,_)) _ (pt:ptree, pos as (p,_)) =
   313 (* val ((Apply_Method' (mI,_,_)),             _,    (pt:ptree, pos as (p,_))) =
   314        ((Apply_Method' (mI, NONE, e_istate)), e_istate, ptp);
   315    *)
   316   let val {srls,ppc,...} = get_met mI;
   317     val PblObj{meth=itms,origin=(oris,_,_),probl,...} = get_obj I pt p;
   318     val itms = if itms <> [] then itms
   319 	       else complete_metitms oris probl [] ppc
   320     val thy' = get_obj g_domID pt p;
   321     val thy = assoc_thy thy';
   322     val (is as ScrState (env,_,_,_,_,_), ctxt, scr) = init_scrstate thy itms mI;
   323     val ini = init_form thy scr env;
   324   in 
   325     case ini of
   326     SOME t => (* val SOME t = ini; 
   327 	         *)
   328     let val pos = ((lev_on o lev_dn) p, Frm)
   329 	val tac_ = Apply_Method' (mI, SOME t, is, ctxt);
   330 	val (pos,c,_,pt) = (*implicit Take*)
   331 	    generate1 thy tac_ (is, ctxt) pos pt
   332       (*val _= ("### nxt_solv Apply_Method, pos= "^pos'2str (lev_on p,Frm));*)
   333     in ([(Apply_Method mI, tac_, (pos, (is, ctxt)))], c, (pt, pos)):calcstate' end
   334   | NONE =>
   335     let val pt = update_env pt (fst pos) (SOME (is, ctxt))
   336 	val (tacis, c, ptp) = nxt_solve_ (pt, pos)
   337     in (tacis @ 
   338 	[(Apply_Method mI, Apply_Method' (mI, NONE, e_istate, e_ctxt), (pos, (is, ctxt)))],
   339 	c, ptp) end
   340   end
   341 (* val ("Check_Postcond",Check_Postcond' (pI,_)) = (mI,m);
   342    val (Check_Postcond' (pI,_), _, (pt, pos as (p,p_))) = 
   343        (tac_,                  is,  ptp);
   344    *)
   345   (*TODO.WN050913 remove unnecessary code below*)
   346   | nxt_solv (Check_Postcond' (pI,_)) _ (pt, pos as (p,p_))  =
   347     let (*val _=tracing"###solve Check_Postcond";*)
   348       val pp = par_pblobj pt p
   349       val asm = (case get_obj g_tac pt p of
   350 		    Check_elementwise _ => (*collects and instantiates asms*)
   351 		    (snd o (get_obj g_result pt)) p
   352 		  | _ => get_assumptions_ pt (p,p_))
   353 	  handle _ => [] (*WN.27.5.03 asms in subpbls not completely clear*)
   354       val metID = get_obj g_metID pt pp;
   355       val {srls=srls,scr=sc,...} = get_met metID;
   356       val loc as (ScrState (E,l,a,_,_,b), ctxt) = get_loc pt (p,p_); 
   357      (*val _= tracing("### solve Check_postc, subpbl pos= "^(pos'2str (p,p_)));
   358       val _= tracing("### solve Check_postc, is= "^(istate2str is));*)
   359       val thy' = get_obj g_domID pt pp;
   360       val thy = assoc_thy thy';
   361       val (_,_,(scval,scsaf)) = next_tac (thy',srls) (pt,(p,p_)) sc loc;
   362       (*val _= tracing("### solve Check_postc, scval= "^(term2str scval));*)
   363     in if pp = [] then 
   364 	   let val is = ScrState (E,l,a,scval,scsaf,b)
   365 	       val tac_ = Check_Postcond'(pI,(scval, map term2str asm))
   366 	       val ((p,p_),ps,f,pt) = 
   367 		   generate1 thy tac_ (is, ctxt) (pp,Res) pt;
   368 	   in ([(Check_Postcond pI, tac_, ((pp,Res), (is, ctxt)))],ps,(pt, (p,p_))) end
   369        else
   370         let
   371 	  (*resume script of parpbl, transfer value of subpbl-script*)
   372         val ppp = par_pblobj pt (lev_up p);
   373 	val thy' = get_obj g_domID pt ppp;
   374         val thy = assoc_thy thy';
   375 	val metID = get_obj g_metID pt ppp;
   376 	val {scr,...} = get_met metID;
   377         val (ScrState (E,l,a,_,_,b), ctxt') = get_loc pt (pp(*!/p/*),Frm)
   378 	      val ctxt'' = transfer_from_subproblem ctxt ctxt'
   379         val tac_ = Check_Postcond' (pI, (scval, map term2str asm))
   380 	val is = ScrState (E,l,a,scval,scsaf,b)
   381         val ((p,p_),ps,f,pt) = generate1 thy tac_ (is, ctxt'') (pp, Res) pt;
   382 	(*val (nx,is',_) = next_tac (thy',srls) (pt,(p,p_)) scr is;WN050913*)
   383        in ([(Check_Postcond pI, tac_, ((pp, Res), (is, ctxt'')))], ps, (pt, (p,p_))) end
   384     end
   385 
   386   | nxt_solv (End_Proof'') _ ptp = ([], [], ptp)
   387 
   388   | nxt_solv tac_ is (pt, pos as (p,p_)) =
   389 (* val (pt, pos as (p,p_)) = ptp;
   390    *)
   391     let val pos = case pos of
   392 		      (p, Met) => ((lev_on o lev_dn) p, Frm)(*begin script*)
   393 		    | (p, Res) => (lev_on p,Res) (*somewhere in script*)
   394 		    | _ => pos  (*somewhere in script*)
   395     (*val _= tracing"### nxt_solv4 Apply_Method: stored is =";
   396         val _= tracing(istate2str is);*)
   397 	val (pos',c,_,pt) = generate1 (assoc_thy "Isac") tac_ is pos pt;
   398     in ([(tac_2tac tac_, tac_, (pos,is))], c, (pt, pos')) end
   399 
   400 
   401   (*(p,p_), (([],Res),Uistate,Empty_Tac_), EmptyMout, Empty_Tac, Safe, pt*)
   402 
   403 
   404 (*.find the next tac from the script, nxt_solv will update the ptree.*)
   405 (* val (ptp as (pt,pos as (p,p_))) = ptp';
   406    val (ptp as (pt, pos as (p,p_))) = ptp'';
   407    val (ptp as (pt, pos as (p,p_))) = ptp;
   408    val (ptp as (pt, pos as (p,p_))) = (pt,ip);
   409    val (ptp as (pt, pos as (p,p_))) = (pt, pos);
   410    *)
   411 and nxt_solve_ (ptp as (pt, pos as (p,p_))) =
   412     if e_metID = get_obj g_metID pt (par_pblobj pt p)
   413     then ([], [], (pt,(p,p_))):calcstate'
   414     else let val thy' = get_obj g_domID pt (par_pblobj pt p);
   415 	     val (srls, is, sc) = from_pblobj_or_detail' thy' (p,p_) pt;
   416 	     val (tac_,is,(t,_)) = next_tac (thy',srls) (pt,pos) sc is;
   417 	 (*TODO here ^^^  return finished/helpless/ok !*)
   418 	 (* val (tac_',is',(t',_)) = next_tac (thy',srls) (pt,pos) sc is;
   419 	    *)
   420 	 in case tac_ of
   421 		End_Detail' _ => ([(End_Detail, 
   422 				    End_Detail' (t,[(*FIXME.040215*)]), 
   423 				    (pos, is))], [], (pt, pos))
   424 	      | _ => nxt_solv tac_ is ptp end;
   425 
   426 (*.says how may steps of a calculation should be done by "fun autocalc".*)
   427 (*TODO.WN0512 redesign togehter with autocalc ?*)
   428 datatype auto = 
   429   Step of int      (*1 do #int steps; may stop in model/specify:
   430 		     IS VERY INEFFICIENT IN MODEL/SPECIY*)
   431 | CompleteModel    (*2 complete modeling
   432                      if model complete, finish specifying + start solving*)
   433 | CompleteCalcHead (*3 complete model/specify in one go + start solving*)
   434 | CompleteToSubpbl (*4 stop at the next begin of a subproblem,
   435                      if none, complete the actual (sub)problem*)
   436 | CompleteSubpbl   (*5 complete the actual (sub)problem (incl.ev.subproblems)*)
   437 | CompleteCalc;    (*6 complete the calculation as a whole*)	
   438 fun autoord (Step _ ) = 1
   439   | autoord CompleteModel = 2
   440   | autoord CompleteCalcHead = 3
   441   | autoord CompleteToSubpbl = 4
   442   | autoord CompleteSubpbl = 5
   443   | autoord CompleteCalc = 6;
   444 
   445 (* val (auto, c, (ptp as (_, p))) = (auto, (c@c'), ptp);
   446    *)
   447 fun complete_solve auto c (ptp as (_, p): ptree * pos') =
   448     if p = ([], Res) then ("end-of-calculation", [], ptp) else
   449     case nxt_solve_ ptp of
   450 	((Subproblem _, tac_, (_, is))::_, c', ptp') =>
   451 (* val ptp' = ptp''';
   452    *)
   453 	if autoord auto < 5 then ("ok", c@c', ptp)
   454 	else let val ptp = all_modspec ptp';
   455 	         val (_, c'', ptp) = all_solve auto (c@c') ptp;
   456 	     in complete_solve auto (c@c'@c'') ptp end
   457       | ((Check_Postcond _, tac_, (_, is))::_, c', ptp' as (_, p')) =>
   458 	if autoord auto < 6 orelse p' = ([],Res) then ("ok", c@c', ptp')
   459 	else complete_solve auto (c@c') ptp'
   460       | ((End_Detail, _, _)::_, c', ptp') => 
   461 	if autoord auto < 6 then ("ok", c@c', ptp')
   462 	else complete_solve auto (c@c') ptp'
   463       | (_, c', ptp') => complete_solve auto (c@c') ptp'
   464 (* val (tacis, c', ptp') = nxt_solve_ ptp;
   465    val (tacis, c', ptp'') = nxt_solve_ ptp';
   466    val (tacis, c', ptp''') = nxt_solve_ ptp'';
   467    val (tacis, c', ptp'''') = nxt_solve_ ptp''';
   468    val (tacis, c', ptp''''') = nxt_solve_ ptp'''';
   469    *)
   470 and all_solve auto c (ptp as (pt, (p,_)): ptree * pos') = 
   471 (* val (ptp as (pt, (p,_))) = ptp;
   472    val (ptp as (pt, (p,_))) = ptp';
   473    val (ptp as (pt, (p,_))) = (pt, pos);
   474    *)
   475     let val (_,_,mI) = get_obj g_spec pt p;
   476         val (_, c', ptp) = nxt_solv (Apply_Method' (mI, NONE, e_istate, e_ctxt))
   477 				(e_istate, e_ctxt) ptp;
   478     in complete_solve auto (c@c') ptp end;
   479 (*@@@ vvv @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@*)
   480 fun complete_solve auto c (ptp as (_, p as (_,p_)): ptree * pos') =
   481     if p = ([], Res) then ("end-of-calculation", [], ptp) else
   482     if member op = [Pbl,Met] p_
   483     then let val ptp = all_modspec ptp
   484 	     val (_, c', ptp) = all_solve auto c ptp
   485 	 in complete_solve auto (c@c') ptp end
   486     else case nxt_solve_ ptp of
   487 	     ((Subproblem _, tac_, (_, is))::_, c', ptp') =>
   488 	     if autoord auto < 5 then ("ok", c@c', ptp)
   489 	     else let val ptp = all_modspec ptp'
   490 		      val (_, c'', ptp) = all_solve auto (c@c') ptp
   491 		  in complete_solve auto (c@c'@c'') ptp end
   492 	   | ((Check_Postcond _, tac_, (_, is))::_, c', ptp' as (_, p')) =>
   493 	     if autoord auto < 6 orelse p' = ([],Res) then ("ok", c@c', ptp')
   494 	     else complete_solve auto (c@c') ptp'
   495 	   | ((End_Detail, _, _)::_, c', ptp') => 
   496 	     if autoord auto < 6 then ("ok", c@c', ptp')
   497 	     else complete_solve auto (c@c') ptp'
   498 	   | (_, c', ptp') => complete_solve auto (c@c') ptp'
   499 and all_solve auto c (ptp as (pt, (p,_)): ptree * pos') = 
   500     let val (_,_,mI) = get_obj g_spec pt p
   501         val (_, c', ptp) = nxt_solv (Apply_Method' (mI, NONE, e_istate, e_ctxt))
   502 				    (e_istate, e_ctxt) ptp
   503     in complete_solve auto (c@c') ptp end;
   504 
   505 (*.aux.fun for detailrls with Rrls, reverse rewriting.*)
   506 (* val (nds, t, ((rule, (t', asm)) :: rts)) = ([], t, rul_terms);
   507    *)
   508 fun rul_terms_2nds nds t [] = nds
   509   | rul_terms_2nds nds t ((rule, res as (t', _)) :: rts) =
   510     (append_atomic [] (e_istate, e_ctxt) t (rule2tac [] rule) res Complete EmptyPtree) ::
   511     (rul_terms_2nds nds t' rts);
   512 
   513 
   514 (*. detail steps done internally by Rewrite_Set* 
   515     into ctree by use of a script .*)
   516 (* val (pt, (p,p_)) = (pt, pos);
   517    *)
   518 fun detailrls pt ((p,p_):pos') = 
   519     let val t = get_obj g_form pt p
   520 	val tac = get_obj g_tac pt p
   521 	val rls = (assoc_rls o rls_of) tac
   522     in case rls of
   523 (* val Rrls {scr = Rfuns {init_state,...},...} = rls;
   524    *)
   525 	   Rrls {scr = Rfuns {init_state,...},...} => 
   526 	   let val (_,_,_,rul_terms) = init_state t
   527 	       val newnds = rul_terms_2nds [] t rul_terms
   528 	       val pt''' = ins_chn newnds pt p 
   529 	   in ("detailrls", pt''', (p @ [length newnds], Res):pos') end
   530 	 | _ =>
   531 	   let val is = init_istate tac t
   532 	(*TODO.WN060602 ScrState (["(t_, Problem (Isac,[equation,univar]))"]
   533 				      is wrong for simpl, but working ?!? *)
   534 	       val tac_ = Apply_Method' (e_metID(*WN0402: see generate1 !?!*), 
   535 					 SOME t, is, e_ctxt)
   536 	       val pos' = ((lev_on o lev_dn) p, Frm)
   537 	       val thy = assoc_thy "Isac"
   538 	       val (_,_,_,pt') = (*implicit Take*)generate1 thy tac_ (is, e_ctxt) pos' pt
   539 	       val (_,_,(pt'',_)) = complete_solve CompleteSubpbl [] (pt',pos')
   540 	       val newnds = children (get_nd pt'' p)
   541 	       val pt''' = ins_chn newnds pt p 
   542 	   (*complete_solve cuts branches after*)
   543 	   in ("detailrls", pt'''(*, get_formress [] ((lev_on o lev_dn) p)cn*),
   544 	       (p @ [length newnds], Res):pos') end
   545     end;
   546 
   547 
   548 
   549 (* val(mI,m)=m;val ppp=p;(*!!!*)val(p,p_)=pos;val(_,pt,_)=ppp(*!!!*);
   550    get_form ((mI,m):tac'_) ((p,p_):pos') ppp;
   551    *)
   552 fun get_form ((mI,m):tac'_) ((p,p_):pos') pt = 
   553   case applicable_in (p,p_) pt m of
   554     Notappl e => Error' (Error_ e)
   555   | Appl m => 
   556       (* val Appl m=applicable_in (p,p_) pt m;
   557          *)
   558       if member op = specsteps mI
   559 	then let val (_,_,f,_,_,_) = specify m (p,p_) [] pt
   560 	     in f end
   561       else let val (*_,_,f,_,_,_*)_ = solve (mI,m) (pt,(p,p_))
   562 	   in (*f*) EmptyMout end;
   563