src/Tools/isac/Interpret/solve.sml
author Walther Neuper <neuper@ist.tugraz.at>
Wed, 04 May 2011 09:01:10 +0200
branchdecompose-isar
changeset 41972 22c5483e9bfb
parent 41968 3228aa46fd30
child 41975 61f358925792
permissions -rw-r--r--
update all "Pair" to "Product_Type.Pair"

regression test --- x+1=2 start SubProblem 'stac2tac_ TODO: no match for SubProblem
     1 (* Title:  solve an example by interpreting a method's script
     2    Author: Walther Neuper 1999
     3    (c) copyright due to lincense terms.
     4 1234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890
     5         10        20        30        40        50        60        70        80         90      100
     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, _, _, _)) (pt:ptree, (pos as (p,_))) =
   146   let val {srls, ...} = get_met mI;
   147     val PblObj {meth=itms, ...} = get_obj I pt p;
   148     val thy' = get_obj g_domID pt p;
   149     val thy = assoc_thy thy';
   150     val (is as ScrState (env,_,_,_,_,_), ctxt, sc) = init_scrstate thy itms mI;
   151     val ini = init_form thy sc env;
   152     val p = lev_dn p;
   153   in 
   154       case ini of
   155 	  SOME t => (* val SOME t = ini; 
   156 	             *)
   157 	  let val (pos,c,_,pt) = 
   158 		  generate1 thy (Apply_Method' (mI, SOME t, is, ctxt))
   159 			    (is, ctxt) (lev_on p, Frm)(*implicit Take*) pt;
   160 	  in ("ok",([(Apply_Method mI, Apply_Method' (mI, SOME t, is, ctxt), 
   161 		      ((lev_on p, Frm), (is, ctxt)))], c, (pt,pos)):calcstate') 
   162 	  end	      
   163 	| NONE => (*execute the first tac in the Script, compare solve m*)
   164 	  let val (m', (is', ctxt'), _) = next_tac (thy', srls) (pt, (p, Res)) sc (is, ctxt);
   165 	      val d = e_rls (*FIXME: get simplifier from domID*);
   166 	  in 
   167 	      case locate_gen (thy',srls) m' (pt,(p, Res))(sc,d) (is', ctxt') of 
   168 		  Steps (is'', ss as (m'',f',pt',p',c')::_) =>
   169 (* val Steps (is'', ss as (m'',f',pt',p',c')::_) =
   170        locate_gen (thy',srls) m'  (pt,(p,Res)) (sc,d) is';
   171  *)
   172 		  ("ok", (map step2taci ss, c', (pt',p')))
   173 		| NotLocatable =>  
   174 		  let val (p,ps,f,pt) = 
   175 			  generate_hard (assoc_thy "Isac") m (p,Frm) pt;
   176 		  in ("not-found-in-script",
   177 		      ([(tac_2tac m, m, (pos, (is, ctxt)))], ps, (pt,p))) end
   178     (*just-before------------------------------------------------------
   179 	      ("ok",([(Apply_Method mI,Apply_Method'(mI,NONE,e_istate),
   180 		       (pos, is))],
   181 		     [], (update_env pt (fst pos) (SOME is),pos)))
   182      -----------------------------------------------------------------*)
   183 	  end
   184   end
   185 
   186   | solve ("Free_Solve", Free_Solve')  (pt,po as (p,_)) =
   187   let (*val _=tracing"###solve Free_Solve";*)
   188     val p' = lev_dn_ (p,Res);
   189     val pt = update_metID pt (par_pblobj pt p) e_metID;
   190   in ("ok", ((*(p',Uistate,Empty_Tac_), EmptyMout, Empty_Tac, Unsafe,*)
   191       [(Empty_Tac, Empty_Tac_, (po, (Uistate, e_ctxt)))], [], (pt,p'))) end
   192 
   193 (* val (("Check_Postcond",Check_Postcond' (pI,_)), (pt,(pos as (p,p_)))) =
   194        (  m,                                       (pt, pos));
   195    *)
   196   | solve ("Check_Postcond",Check_Postcond' (pI,_)) (pt,(pos as (p,p_))) =
   197     let (*val _=tracing"###solve Check_Postcond";*)
   198       val pp = par_pblobj pt p
   199       val asm = (case get_obj g_tac pt p of
   200 		    Check_elementwise _ => (*collects and instantiates asms*)
   201 		    (snd o (get_obj g_result pt)) p
   202 		  | _ => get_assumptions_ pt (p,p_))
   203 	  handle _ => [] (*WN.27.5.03 asms in subpbls not completely clear*)
   204       val metID = get_obj g_metID pt pp;
   205       val {srls=srls,scr=sc,...} = get_met metID;
   206       val loc as (ScrState (E,l,a,_,_,b), ctxt) = get_loc pt (p,p_); 
   207      (*val _= tracing("### solve Check_postc, subpbl pos= "^(pos'2str (p,p_)));
   208       val _= tracing("### solve Check_postc, is= "^(istate2str is));*)
   209       val thy' = get_obj g_domID pt pp;
   210       val thy = assoc_thy thy';
   211       val (_,_,(scval,scsaf)) = next_tac (thy',srls) (pt,(p,p_)) sc loc;
   212       (*val _= tracing("### solve Check_postc, scval= "^(term2str scval));*)
   213 
   214     in if pp = [] then
   215 	   let val is = ScrState (E,l,a,scval,scsaf,b)
   216 	       val tac_ = Check_Postcond'(pI,(scval, map term2str asm))
   217 	       val (pos,ps,f,pt) = generate1 thy tac_ (is, ctxt) (pp,Res) pt;
   218 	   in ("ok", ((*(([],Res),is,End_Proof''), f, End_Proof', scsaf,*)
   219 	       [(Check_Postcond pI, tac_, ((pp,Res),(is, ctxt)))], ps,(pt,pos))) end
   220        else
   221         let
   222 	  (*resume script of parpbl, transfer value of subpbl-script*)
   223         val ppp = par_pblobj pt (lev_up p);
   224 	val thy' = get_obj g_domID pt ppp;
   225         val thy = assoc_thy thy';
   226 	val metID = get_obj g_metID pt ppp;
   227         val sc = (#scr o get_met) metID;
   228         val (ScrState (E,l,a,_,_,b), ctxt') = get_loc pt (pp(*!/p/*),Frm); 
   229 	      val ctxt'' = transfer_from_subproblem ctxt ctxt'
   230         val ((p,p_),ps,f,pt) = 
   231 	    generate1 thy (Check_Postcond' (pI, (scval, map term2str asm)))
   232 		(ScrState (E,l,a,scval,scsaf,b), ctxt'') (pp,Res) pt;
   233        in ("ok",(*((pp,Res),is',nx), f, tac_2tac nx, scsaf,*)
   234 	   ([(Check_Postcond pI, Check_Postcond'(pI,(scval, map term2str asm)),
   235 	      ((pp,Res), (ScrState (E,l,a,scval,scsaf,b), ctxt'')))],ps,(pt,(p,p_))))
   236 	end
   237     end
   238 (* val (msg, cs') = 
   239     ("ok",([(Check_Postcond pI,Check_Postcond'(pI, (scval, map term2str asm))),
   240 	    ((pp,Res),(ScrState (E,l,a,scval,scsaf,b)))], (pt,(p,p_))));
   241     val (_,(pt',p')) = cs';
   242    (tracing o istate2str) (get_istate pt' p');
   243    (term2str o fst) (get_obj g_result pt' (fst p'));
   244    *)
   245 
   246 (* tracing(istate2str(get_istate pt (p,p_)));
   247    *)
   248   | solve (_,End_Proof'') (pt, (p,p_)) =
   249       ("end-proof",
   250        ((*(([],Res),Uistate,Empty_Tac_), EmptyMout, Empty_Tac, Safe,*)
   251        [(Empty_Tac,Empty_Tac_,(([],Res),(Uistate, e_ctxt)))],[],(pt,(p,p_))))
   252 
   253 (*-----------vvvvvvvvvvv could be done by generate1 ?!?*)
   254   | solve (_,End_Detail' t) (pt,(p,p_)) =
   255     let val pr as (p',_) = (lev_up p, Res)
   256 	val pp = par_pblobj pt p
   257 	val r = (fst o (get_obj g_result pt)) p' 
   258 	(*Rewrite_Set* done at Detail_Set*: this result is already in ptree*)
   259 	val thy' = get_obj g_domID pt pp
   260 	val (srls, is, sc) = from_pblobj' thy' pr pt
   261 	val (tac_,is',_) = next_tac (thy',srls) (pt,pr) sc is
   262     in ("ok", ((*((pp,Frm(*???*)),is,tac_), 
   263 	Form' (FormKF (~1, EdUndef, length p', Nundef, term2str r)),
   264 	tac_2tac tac_, Sundef,*)
   265 	[(End_Detail, End_Detail' t , 
   266 	  ((p,p_), get_loc pt (p,p_)))], [], (pt,pr))) end
   267 
   268   | solve (mI,m) (pt, po as (p,p_)) =
   269 (* val ((mI,m), (pt, po as (p,p_))) = (m, (pt, pos));
   270    *)
   271     if e_metID = get_obj g_metID pt (par_pblobj pt p)(*29.8.02:
   272 						      could be detail, too !!*)
   273     then let val ((p,p_),ps,f,pt) = 
   274 		 generate1 (assoc_thy (get_obj g_domID pt (par_pblobj pt p))) 
   275 			   m (e_istate, e_ctxt) (p,p_) pt;
   276 	 in ("no-method-specified", (*Free_Solve*)
   277 	     ((*((p,p_),Uistate,Empty_Tac_),f, Empty_Tac, Unsafe,*)
   278 	     [(Empty_Tac,Empty_Tac_, ((p,p_),(Uistate, e_ctxt)))], ps, (pt,(p,p_)))) end
   279     else
   280 	let 
   281 	    val thy' = get_obj g_domID pt (par_pblobj pt p);
   282 	    val (srls, is, sc) = from_pblobj_or_detail' thy' (p,p_) pt;
   283 (*val _= tracing("### solve, before locate_gen p="^(pos'2str(p,p_)));*)
   284 		val d = e_rls; (*FIXME: canon.simplifier for domain is missing
   285 				8.01: generate from domID?*)
   286 	in case locate_gen (thy',srls) m  (pt,(p,p_)) (sc,d) is of 
   287 	       Steps (is', ss as (m',f',pt',p',c')::_) =>
   288 (* val Steps (is', ss as (m',f',pt',p',c')::_) =
   289        locate_gen (thy',srls) m  (pt,(p,p_)) (sc,d) is;
   290  *)
   291 	       let (*val _= tracing("### solve, after locate_gen: is= ")
   292 		       val _= tracing(istate2str is')*)
   293 		   (*val nxt_ = 
   294 		       case p' of (*change from solve to model subpbl*)
   295 			   (_,Pbl) => nxt_model_pbl m' (pt',p')
   296 			 | _ => fst3 (next_tac (thy',srls) (pt',p') sc is');*) 
   297 	       (*27.8.02:next_tac may change to other branches in pt FIXXXXME*)
   298 	       in ("ok", ((*(p',is',nxt_), f', tac_2tac nxt_, safe is',*)
   299 		   map step2taci ss, c', (pt',p'))) end
   300 	     | NotLocatable =>  
   301 	       let val (p,ps,f,pt) = 
   302 		       generate_hard (assoc_thy "Isac") m (p,p_) pt;
   303 	       in ("not-found-in-script",
   304 		   ((*(p,Uistate,Empty_Tac_),f, Empty_Tac, Unsafe,*) 
   305 		   [(tac_2tac m, m, (po,is))], ps, (pt,p))) end
   306 	end;
   307 
   308 
   309 (*FIXME.WN050821 compare solve ... nxt_solv*)
   310 (* nxt_solv (Apply_Method'     vvv FIXME: get args in applicable_in *)
   311 fun nxt_solv (Apply_Method' (mI,_,_,_)) _ (pt:ptree, pos as (p,_)) =
   312 (* val ((Apply_Method' (mI,_,_)),             _,    (pt:ptree, pos as (p,_))) =
   313        ((Apply_Method' (mI, NONE, e_istate)), e_istate, ptp);
   314    *)
   315   let val {srls,ppc,...} = get_met mI;
   316     val PblObj{meth=itms,origin=(oris,_,_),probl,...} = get_obj I pt p;
   317     val itms = if itms <> [] then itms
   318 	       else complete_metitms oris probl [] ppc
   319     val thy' = get_obj g_domID pt p;
   320     val thy = assoc_thy thy';
   321     val (is as ScrState (env,_,_,_,_,_), ctxt, scr) = init_scrstate thy itms mI;
   322     val ini = init_form thy scr env;
   323   in 
   324     case ini of
   325     SOME t => (* val SOME t = ini; 
   326 	         *)
   327     let val pos = ((lev_on o lev_dn) p, Frm)
   328 	val tac_ = Apply_Method' (mI, SOME t, is, ctxt);
   329 	val (pos,c,_,pt) = (*implicit Take*)
   330 	    generate1 thy tac_ (is, ctxt) pos pt
   331       (*val _= ("### nxt_solv Apply_Method, pos= "^pos'2str (lev_on p,Frm));*)
   332     in ([(Apply_Method mI, tac_, (pos, (is, ctxt)))], c, (pt, pos)):calcstate' end
   333   | NONE =>
   334     let val pt = update_env pt (fst pos) (SOME (is, ctxt))
   335 	val (tacis, c, ptp) = nxt_solve_ (pt, pos)
   336     in (tacis @ 
   337 	[(Apply_Method mI, Apply_Method' (mI, NONE, e_istate, e_ctxt), (pos, (is, ctxt)))],
   338 	c, ptp) end
   339   end
   340 (* val ("Check_Postcond",Check_Postcond' (pI,_)) = (mI,m);
   341    val (Check_Postcond' (pI,_), _, (pt, pos as (p,p_))) = 
   342        (tac_,                  is,  ptp);
   343    *)
   344   (*TODO.WN050913 remove unnecessary code below*)
   345   | nxt_solv (Check_Postcond' (pI,_)) _ (pt, pos as (p,p_))  =
   346     let (*val _=tracing"###solve Check_Postcond";*)
   347       val pp = par_pblobj pt p
   348       val asm = (case get_obj g_tac pt p of
   349 		    Check_elementwise _ => (*collects and instantiates asms*)
   350 		    (snd o (get_obj g_result pt)) p
   351 		  | _ => get_assumptions_ pt (p,p_))
   352 	  handle _ => [] (*WN.27.5.03 asms in subpbls not completely clear*)
   353       val metID = get_obj g_metID pt pp;
   354       val {srls=srls,scr=sc,...} = get_met metID;
   355       val loc as (ScrState (E,l,a,_,_,b), ctxt) = get_loc pt (p,p_); 
   356      (*val _= tracing("### solve Check_postc, subpbl pos= "^(pos'2str (p,p_)));
   357       val _= tracing("### solve Check_postc, is= "^(istate2str is));*)
   358       val thy' = get_obj g_domID pt pp;
   359       val thy = assoc_thy thy';
   360       val (_,_,(scval,scsaf)) = next_tac (thy',srls) (pt,(p,p_)) sc loc;
   361       (*val _= tracing("### solve Check_postc, scval= "^(term2str scval));*)
   362     in if pp = [] then 
   363 	   let val is = ScrState (E,l,a,scval,scsaf,b)
   364 	       val tac_ = Check_Postcond'(pI,(scval, map term2str asm))
   365 	       val ((p,p_),ps,f,pt) = 
   366 		   generate1 thy tac_ (is, ctxt) (pp,Res) pt;
   367 	   in ([(Check_Postcond pI, tac_, ((pp,Res), (is, ctxt)))],ps,(pt, (p,p_))) end
   368        else
   369         let
   370 	  (*resume script of parpbl, transfer value of subpbl-script*)
   371         val ppp = par_pblobj pt (lev_up p);
   372 	val thy' = get_obj g_domID pt ppp;
   373         val thy = assoc_thy thy';
   374 	val metID = get_obj g_metID pt ppp;
   375 	val {scr,...} = get_met metID;
   376         val (ScrState (E,l,a,_,_,b), ctxt') = get_loc pt (pp(*!/p/*),Frm)
   377 	      val ctxt'' = transfer_from_subproblem ctxt ctxt'
   378         val tac_ = Check_Postcond' (pI, (scval, map term2str asm))
   379 	val is = ScrState (E,l,a,scval,scsaf,b)
   380         val ((p,p_),ps,f,pt) = generate1 thy tac_ (is, ctxt'') (pp, Res) pt;
   381 	(*val (nx,is',_) = next_tac (thy',srls) (pt,(p,p_)) scr is;WN050913*)
   382        in ([(Check_Postcond pI, tac_, ((pp, Res), (is, ctxt'')))], ps, (pt, (p,p_))) end
   383     end
   384 
   385   | nxt_solv (End_Proof'') _ ptp = ([], [], ptp)
   386 
   387   | nxt_solv tac_ is (pt, pos as (p,p_)) =
   388 (* val (pt, pos as (p,p_)) = ptp;
   389    *)
   390     let val pos = case pos of
   391 		      (p, Met) => ((lev_on o lev_dn) p, Frm)(*begin script*)
   392 		    | (p, Res) => (lev_on p,Res) (*somewhere in script*)
   393 		    | _ => pos  (*somewhere in script*)
   394     (*val _= tracing"### nxt_solv4 Apply_Method: stored is =";
   395         val _= tracing(istate2str is);*)
   396 	val (pos',c,_,pt) = generate1 (assoc_thy "Isac") tac_ is pos pt;
   397     in ([(tac_2tac tac_, tac_, (pos,is))], c, (pt, pos')) end
   398 
   399 
   400   (*(p,p_), (([],Res),Uistate,Empty_Tac_), EmptyMout, Empty_Tac, Safe, pt*)
   401 
   402 
   403 (*.find the next tac from the script, nxt_solv will update the ptree.*)
   404 (* val (ptp as (pt,pos as (p,p_))) = ptp';
   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_))) = (pt,ip);
   408    val (ptp as (pt, pos as (p,p_))) = (pt, pos);
   409    *)
   410 and nxt_solve_ (ptp as (pt, pos as (p,p_))) =
   411       if e_metID = get_obj g_metID pt (par_pblobj pt p)
   412       then ([], [], (pt,(p,p_))):calcstate'
   413       else 
   414         let 
   415           val thy' = get_obj g_domID pt (par_pblobj pt p);
   416 	        val (srls, is, sc) = from_pblobj_or_detail' thy' (p,p_) pt;
   417 	        val (tac_,is,(t,_)) = next_tac (thy',srls) (pt,pos) sc is;
   418 	        (*TODO here ^^^  return finished/helpless/ok !*)
   419 	      in case tac_ of
   420 		         End_Detail' _ => ([(End_Detail, End_Detail' (t,[(*FIXME.040215*)]), 
   421 				       (pos, is))], [], (pt, pos))
   422 	         | _ => nxt_solv tac_ is ptp end;
   423 
   424 (*.says how may steps of a calculation should be done by "fun autocalc".*)
   425 (*TODO.WN0512 redesign togehter with autocalc ?*)
   426 datatype auto = 
   427   Step of int      (*1 do #int steps; may stop in model/specify:
   428 		     IS VERY INEFFICIENT IN MODEL/SPECIY*)
   429 | CompleteModel    (*2 complete modeling
   430                      if model complete, finish specifying + start solving*)
   431 | CompleteCalcHead (*3 complete model/specify in one go + start solving*)
   432 | CompleteToSubpbl (*4 stop at the next begin of a subproblem,
   433                      if none, complete the actual (sub)problem*)
   434 | CompleteSubpbl   (*5 complete the actual (sub)problem (incl.ev.subproblems)*)
   435 | CompleteCalc;    (*6 complete the calculation as a whole*)	
   436 fun autoord (Step _ ) = 1
   437   | autoord CompleteModel = 2
   438   | autoord CompleteCalcHead = 3
   439   | autoord CompleteToSubpbl = 4
   440   | autoord CompleteSubpbl = 5
   441   | autoord CompleteCalc = 6;
   442 
   443 (* val (auto, c, (ptp as (_, p))) = (auto, (c@c'), ptp);
   444    *)
   445 fun complete_solve auto c (ptp as (_, p): ptree * pos') =
   446     if p = ([], Res) then ("end-of-calculation", [], ptp) else
   447     case nxt_solve_ ptp of
   448 	((Subproblem _, tac_, (_, is))::_, c', ptp') =>
   449 (* val ptp' = ptp''';
   450    *)
   451 	if autoord auto < 5 then ("ok", c@c', ptp)
   452 	else let val ptp = all_modspec ptp';
   453 	         val (_, c'', ptp) = all_solve auto (c@c') ptp;
   454 	     in complete_solve auto (c@c'@c'') ptp end
   455       | ((Check_Postcond _, tac_, (_, is))::_, c', ptp' as (_, p')) =>
   456 	if autoord auto < 6 orelse p' = ([],Res) then ("ok", c@c', ptp')
   457 	else complete_solve auto (c@c') ptp'
   458       | ((End_Detail, _, _)::_, c', ptp') => 
   459 	if autoord auto < 6 then ("ok", c@c', ptp')
   460 	else complete_solve auto (c@c') ptp'
   461       | (_, c', ptp') => complete_solve auto (c@c') ptp'
   462 (* val (tacis, c', ptp') = nxt_solve_ ptp;
   463    val (tacis, c', ptp'') = nxt_solve_ 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    *)
   468 and all_solve auto c (ptp as (pt, (p,_)): ptree * pos') = 
   469 (* val (ptp as (pt, (p,_))) = ptp;
   470    val (ptp as (pt, (p,_))) = ptp';
   471    val (ptp as (pt, (p,_))) = (pt, pos);
   472    *)
   473     let val (_,_,mI) = get_obj g_spec pt p;
   474         val (_, c', ptp) = nxt_solv (Apply_Method' (mI, NONE, e_istate, e_ctxt))
   475 				(e_istate, e_ctxt) ptp;
   476     in complete_solve auto (c@c') ptp end;
   477 (*@@@ vvv @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@*)
   478 fun complete_solve auto c (ptp as (_, p as (_,p_)): ptree * pos') =
   479     if p = ([], Res) then ("end-of-calculation", [], ptp) else
   480     if member op = [Pbl,Met] p_
   481     then let val ptp = all_modspec ptp
   482 	     val (_, c', ptp) = all_solve auto c ptp
   483 	 in complete_solve auto (c@c') ptp end
   484     else case nxt_solve_ ptp of
   485 	     ((Subproblem _, tac_, (_, is))::_, c', ptp') =>
   486 	     if autoord auto < 5 then ("ok", c@c', ptp)
   487 	     else let val ptp = all_modspec ptp'
   488 		      val (_, c'', ptp) = all_solve auto (c@c') ptp
   489 		  in complete_solve auto (c@c'@c'') ptp end
   490 	   | ((Check_Postcond _, tac_, (_, is))::_, c', ptp' as (_, p')) =>
   491 	     if autoord auto < 6 orelse p' = ([],Res) then ("ok", c@c', ptp')
   492 	     else complete_solve auto (c@c') ptp'
   493 	   | ((End_Detail, _, _)::_, c', ptp') => 
   494 	     if autoord auto < 6 then ("ok", c@c', ptp')
   495 	     else complete_solve auto (c@c') ptp'
   496 	   | (_, c', ptp') => complete_solve auto (c@c') ptp'
   497 and all_solve auto c (ptp as (pt, (p,_)): ptree * pos') = 
   498     let val (_,_,mI) = get_obj g_spec pt p
   499         val (_, c', ptp) = nxt_solv (Apply_Method' (mI, NONE, e_istate, e_ctxt))
   500 				    (e_istate, e_ctxt) ptp
   501     in complete_solve auto (c@c') ptp end;
   502 
   503 (*.aux.fun for detailrls with Rrls, reverse rewriting.*)
   504 (* val (nds, t, ((rule, (t', asm)) :: rts)) = ([], t, rul_terms);
   505    *)
   506 fun rul_terms_2nds nds t [] = nds
   507   | rul_terms_2nds nds t ((rule, res as (t', _)) :: rts) =
   508     (append_atomic [] (e_istate, e_ctxt) t (rule2tac [] rule) res Complete EmptyPtree) ::
   509     (rul_terms_2nds nds t' rts);
   510 
   511 
   512 (*. detail steps done internally by Rewrite_Set* 
   513     into ctree by use of a script .*)
   514 (* val (pt, (p,p_)) = (pt, pos);
   515    *)
   516 fun detailrls pt ((p,p_):pos') = 
   517     let val t = get_obj g_form pt p
   518 	val tac = get_obj g_tac pt p
   519 	val rls = (assoc_rls o rls_of) tac
   520     in case rls of
   521 (* val Rrls {scr = Rfuns {init_state,...},...} = rls;
   522    *)
   523 	   Rrls {scr = Rfuns {init_state,...},...} => 
   524 	   let val (_,_,_,rul_terms) = init_state t
   525 	       val newnds = rul_terms_2nds [] t rul_terms
   526 	       val pt''' = ins_chn newnds pt p 
   527 	   in ("detailrls", pt''', (p @ [length newnds], Res):pos') end
   528 	 | _ =>
   529 	   let val is = init_istate tac t
   530 	(*TODO.WN060602 ScrState (["(t_, Problem (Isac,[equation,univar]))"]
   531 				      is wrong for simpl, but working ?!? *)
   532 	       val tac_ = Apply_Method' (e_metID(*WN0402: see generate1 !?!*), 
   533 					 SOME t, is, e_ctxt)
   534 	       val pos' = ((lev_on o lev_dn) p, Frm)
   535 	       val thy = assoc_thy "Isac"
   536 	       val (_,_,_,pt') = (*implicit Take*)generate1 thy tac_ (is, e_ctxt) pos' pt
   537 	       val (_,_,(pt'',_)) = complete_solve CompleteSubpbl [] (pt',pos')
   538 	       val newnds = children (get_nd pt'' p)
   539 	       val pt''' = ins_chn newnds pt p 
   540 	   (*complete_solve cuts branches after*)
   541 	   in ("detailrls", pt'''(*, get_formress [] ((lev_on o lev_dn) p)cn*),
   542 	       (p @ [length newnds], Res):pos') end
   543     end;
   544 
   545 
   546 
   547 (* val(mI,m)=m;val ppp=p;(*!!!*)val(p,p_)=pos;val(_,pt,_)=ppp(*!!!*);
   548    get_form ((mI,m):tac'_) ((p,p_):pos') ppp;
   549    *)
   550 fun get_form ((mI,m):tac'_) ((p,p_):pos') pt = 
   551   case applicable_in (p,p_) pt m of
   552     Notappl e => Error' (Error_ e)
   553   | Appl m => 
   554       (* val Appl m=applicable_in (p,p_) pt m;
   555          *)
   556       if member op = specsteps mI
   557 	then let val (_,_,f,_,_,_) = specify m (p,p_) [] pt
   558 	     in f end
   559       else let val (*_,_,f,_,_,_*)_ = solve (mI,m) (pt,(p,p_))
   560 	   in (*f*) EmptyMout end;
   561