src/sml/ME/script.sml
author wneuper
Fri, 16 Sep 2005 19:01:49 +0200
branchstart_Take
changeset 394 4670777fbcd7
parent 393 090d6b29b1ea
child 395 4934112a6ab8
permissions -rw-r--r--
'handle_leaf' runs, call not yet cleaned
     1 (* interpreter for scripts
     2    (c) Walther Neuper 2000
     3 
     4 use"ME/script.sml";
     5 use"script.sml";
     6 *)
     7 
     8 signature INTERPRETER =
     9 sig
    10   (*type ets (list of executed tactics) see sequent.sml*)
    11 
    12   datatype locate
    13     = NotLocatable
    14     | Steps of (tac_ * mout * ptree * pos' * cid * safe (* ets*)) list
    15 (*    | ToDo of ets 28.4.02*)
    16 
    17   (*diss: next-tactic-function*)
    18   val next_tac : theory' -> ptree * pos' -> metID -> scr -> ets -> tac_
    19   (*diss: locate-function*)
    20   val locate_gen : theory'
    21                    -> tac_
    22                       -> ptree * pos' -> scr * rls -> ets -> loc_ -> locate
    23 
    24   val sel_rules : ptree -> pos' -> tac list
    25   val init_form : scr -> ets -> loc_ * term option (*FIXME not up to date*)
    26   val formal_args : term -> term list
    27 
    28   (*shift to library ...*)
    29   val inst_abs : theory' -> term -> term
    30   val itms2args : metID -> itm list -> term list
    31   val user_interrupt : loc_ * (tac_ * env * env * term * term * safe)
    32   (*val empty : term*) 
    33 end 
    34 
    35 
    36 
    37 
    38 (*
    39 structure Interpreter : INTERPRETER =
    40 struct
    41 *)
    42 
    43 (*.traces the leaves (ie. non-tactical nodes) of the script
    44    found by next_tac.
    45    a leaf is either a tactic or an 'exp' in 'let v = expr'
    46    where 'exp' does not contain a tactic.*)   
    47 val trace_script = ref false;
    48 
    49 val string_of_thm' = (implode o tl o drop_last o explode o string_of_thm);
    50 (*
    51   string_of_thm sym;
    52 val it = "\"?s = ?t ==> ?t = ?s\"" : string
    53   string_of_thm' sym;
    54 val it = "?s = ?t ==> ?t = ?s" : string*)
    55 
    56 type step =     (*data for creating a new node in the ptree;
    57 		 designed for use:
    58                	 fun ass* scrstate steps =
    59                	 ... case ass* scrstate steps of
    60                	     Assoc (scrstate, steps) => ... ass* scrstate steps*)
    61     tac_       (*transformed from associated tac*)
    62     * mout       (*result with indentation etc.*)
    63     * ptree      (*containing node created by tac_ + resp. scrstate*)
    64     * pos'       (*position in ptree; ptree * pos' is the proofstate*)
    65     * pos' list; (*of ptree-nodes probably cut (by fst tac_)*)
    66 val e_step = (Empty_Tac_, EmptyMout, EmptyPtree, e_pos',[]:pos' list):step;
    67 
    68 fun rule2thm' (Thm (id, thm)) = (id, string_of_thm thm):thm'
    69   | rule2thm' r = raise error ("rule2thm': not defined for "^(rule2str r));
    70 
    71 (*.makes a (rule,term) list to a Step (m, mout, pt', p', cid) for solve;
    72    complicated with current t in rrlsstate.*)
    73 fun rts2steps steps ((pt,p),(f,f'',rss,rts),(thy',ro,er,pa)) [(r, (f', am))] =
    74     let val thy = assoc_thy thy'
    75 	val m = Rewrite' (thy',ro,er,pa, rule2thm' r, f, (f', am))
    76 	val is = RrlsState (f',f'',rss,rts)
    77 	val p = case p of (p',Frm) => p | (p',Res) => (lev_on p',Res)
    78 	val (p', cid, mout, pt') = generate1 thy m is p pt
    79     in (is, (m, mout, pt', p', cid)::steps) end
    80   | rts2steps steps ((pt,p),(f,f'',rss,rts),(thy',ro,er,pa)) 
    81 	      ((r, (f', am))::rts') =
    82     let val thy = assoc_thy thy'
    83 	val m = Rewrite' (thy',ro,er,pa, rule2thm' r, f, (f', am))
    84 	val is = RrlsState (f',f'',rss,rts)
    85 	val p = case p of (p',Frm) => p | (p',Res) => (lev_on p',Res)
    86 	val (p', cid, mout, pt') = generate1 thy m is p pt
    87     in rts2steps ((m, mout, pt', p', cid)::steps) 
    88 		 ((pt',p'),(f',f'',rss,rts),(thy',ro,er,pa)) rts' end;
    89 
    90 
    91 (*. functions for the environment stack .*)
    92 fun accessenv id es = the (assoc((top es):env, id))
    93     handle _ => error ("accessenv: "^(free2str id)^" not in env");
    94 fun updateenv id vl (es:env stack) = 
    95     (push (overwrite(top es, (id, vl))) (pop es)):env stack;
    96 fun pushenv id vl (es:env stack) = 
    97     (push (overwrite(top es, (id, vl))) es):env stack;
    98 val popenv = pop:env stack -> env stack;
    99 
   100 
   101 
   102 fun de_esc_underscore str =
   103   let fun scan [] = []
   104 	| scan (s::ss) = if s = "'" then (scan ss)
   105 			 else (s::(scan ss))
   106   in (implode o scan o explode) str end;
   107 (*
   108 > val str = "Rewrite_Set_Inst";
   109 > val esc = esc_underscore str;
   110 val it = "Rewrite'_Set'_Inst" : string
   111 > val des = de_esc_underscore esc;
   112  val des = de_esc_underscore esc;*)
   113 
   114 
   115 (*WN.12.5.03 not used any more,
   116   tacs are more stable than listepxr: subst_tacexpr
   117 fun is_listexpr t = 
   118   (((ids_of o head_of) t) inter (!listexpr)) <> [];
   119 ----*)
   120 
   121 (*go at a location in a script and fetch the contents*)
   122 fun go [] t = t
   123   | go (D::p) (Abs(s,ty,t0)) = go (p:loc_) t0
   124   | go (L::p) (t1 $ t2) = go p t1
   125   | go (R::p) (t1 $ t2) = go p t2
   126   | go l _ = raise error ("go: no "^(loc_2str l));
   127 (*
   128 > val t = (term_of o the o (parse thy)) "a+b";
   129 val it = Const (#,#) $ Free (#,#) $ Free ("b","RealDef.real") : term
   130 > val plus_a = go [L] t; 
   131 > val b = go [R] t; 
   132 > val plus = go [L,L] t; 
   133 > val a = go [L,R] t;
   134 
   135 > val t = (term_of o the o (parse thy)) "a+b+c";
   136 val t = Const (#,#) $ (# $ # $ Free #) $ Free ("c","RealDef.real") : term
   137 > val pl_pl_a_b = go [L] t; 
   138 > val c = go [R] t; 
   139 > val a = go [L,R,L,R] t; 
   140 > val b = go [L,R,R] t; 
   141 *)
   142 
   143 
   144 (* get a subterm t with test t, and record location *)
   145 fun get l test (t as Const (s,T)) = 
   146     if test t then Some (l,t) else None
   147   | get l test (t as Free (s,T)) = 
   148     if test t then Some (l,t) else None 
   149   | get l test (t as Bound n) =
   150     if test t then Some (l,t) else None 
   151   | get l test (t as Var (s,T)) =
   152     if test t then Some (l,t) else None
   153   | get l test (t as Abs (s,T,body)) =
   154     if test t then Some (l:loc_,t) else get ((l@[D]):loc_) test body
   155   | get l test (t as t1 $ t2) =
   156     if test t then Some (l,t) 
   157     else case get (l@[L]) test t1 of 
   158       None => get (l@[R]) test t2
   159     | Some (l',t') => Some (l',t');
   160 (*18.6.00
   161 > val sss = ((term_of o the o (parse thy))
   162   "Script Solve_root_equation (eq_::bool) (v_::real) (err_::bool) =\
   163    \ (let e_ = Try (Rewrite square_equation_left True eq_) \
   164    \  in [e_])");
   165           ______ compares head_of !!
   166 > get [] (eq_str "Let") sss;            [R]
   167 > get [] (eq_str "Script.Try") sss;     [R,L,R]
   168 > get [] (eq_str "Script.Rewrite") sss; [R,L,R,R]
   169 > get [] (eq_str "True") sss;           [R,L,R,R,L,R]
   170 > get [] (eq_str "e_") sss;             [R,R]
   171 *)
   172 
   173 fun test_negotiable t = ((strip_thy o (term_str Script.thy) o head_of) t) 
   174   mem (!negotiable);
   175 
   176 (*30.4.02: vvv--- doesnt work with curried functions ---> get_tac ------
   177 (*18.6.00: below _ALL_ negotiables must be in fun-patterns !
   178   then the last (non)pattern must be a subproblem*)
   179 fun init_frm thy (Const ("Script.Rewrite",_) $ _ $ _ $ eq) = Some eq
   180   | init_frm thy (Const ("Script.Rewrite'_Inst",_) $ _ $ _ $ _ $ eq) = Some eq
   181   | init_frm thy (Const ("Script.Rewrite'_Set",_) $ _ $ _ $ eq) = Some eq
   182   | init_frm thy (Const ("Script.Rewrite'_Set'_Inst",_) $ _ $ _ $ _ $ eq) = 
   183     Some eq
   184   | init_frm thy (Const ("Script.Calculate",_) $ _ $ t) = Some t
   185   | init_frm thy t = 
   186   (*if ((strip_thy o (term_str thy) o head_of) t) mem (!subpbls)
   187     then None 
   188   else *)raise error ("init_frm: not impl. for "^
   189 		    (Sign.string_of_term (sign_of thy) t));
   190 
   191 > val t = (term_of o the o (parse thy)) 
   192  "Rewrite square_equation_left True (sqrt(#9+#4*x)=sqrt x + sqrt(#5+x))";
   193 > val Some ini = init_frm thy t;
   194 > Sign.string_of_term (sign_of thy) ini;
   195 val it = "sqrt (#9 + #4 * x) = sqrt x + sqrt (#5 + x)" : string
   196 
   197 > val t = (term_of o the o (parse thy)) 
   198  "solve_univar (Reals, [univar,equation], no_met) e1_ v1_";
   199 > val ini = init_frm thy t;
   200 > Sign.string_of_term (sign_of thy) ini;
   201 val it = "empty" : string
   202 
   203 > val t = (term_of o the o (parse thy)) 
   204  "Rewrite_Set norm_equation False x + #1 = #2";
   205 > val Some ini = init_frm thy t;
   206 > Sign.string_of_term (sign_of thy) ini;
   207 val it = "x + #1 = #2" : string                                                
   208 
   209 > val t = (term_of o the o (parse thy)) 
   210  "Rewrite_Set_Inst [(bdv,x)] isolate_bdv False x + #1 = #2";
   211 > val Some ini = init_frm thy t;
   212 > Sign.string_of_term (sign_of thy) ini;
   213 val it = "x + #1 = #2" : string                           *)
   214 
   215 
   216 (*.get argument of first stactic in a script for init_form.*)
   217 fun get_stac thy (h $ body) =
   218 (* 
   219    *)
   220   let
   221     fun get_t y (Const ("Script.Seq",_) $ e1 $ e2) a = 
   222     	(case get_t y e1 a of None => get_t y e2 a | la => la)
   223       | get_t y (Const ("Script.Seq",_) $ e1 $ e2 $ a) _ = 
   224     	(case get_t y e1 a of None => get_t y e2 a | la => la)
   225       | get_t y (Const ("Script.Try",_) $ e) a = get_t y e a
   226       | get_t y (Const ("Script.Try",_) $ e $ a) _ = get_t y e a
   227       | get_t y (Const ("Script.Repeat",_) $ e) a = get_t y e a
   228       | get_t y (Const ("Script.Repeat",_) $ e $ a) _ = get_t y e a
   229       | get_t y (Const ("Script.Or",_) $e1 $ e2) a =
   230     	(case get_t y e1 a of None => get_t y e2 a | la => la)
   231       | get_t y (Const ("Script.Or",_) $e1 $ e2 $ a) _ =
   232     	(case get_t y e1 a of None => get_t y e2 a | la => la)
   233       | get_t y (Const ("Script.While",_) $ c $ e) a = get_t y e a
   234       | get_t y (Const ("Script.While",_) $ c $ e $ a) _ = get_t y e a
   235       | get_t y (Const ("Script.Letpar",_) $ e1 $ Abs (_,_,e2)) a = 
   236     	(case get_t y e1 a of None => get_t y e2 a | la => la)
   237     (*| get_t y (Const ("Let",_) $ e1 $ Abs (_,_,e2)) a =
   238     	(writeln("get_t: Let e1= "^(term2str e1)^", e2= "^(term2str e2));
   239 	 case get_t y e1 a of None => get_t y e2 a | la => la)
   240       | get_t y (Abs (_,_,e)) a = get_t y e a*)
   241       | get_t y (Const ("Let",_) $ e1 $ Abs (_,_,e2)) a =
   242     	get_t y e1 a (*don't go deeper without evaluation !*)
   243       | get_t y (Const ("If",_) $ c $ e1 $ e2) a = None
   244     	(*(case get_t y e1 a of None => get_t y e2 a | la => la)*)
   245     
   246       | get_t y (Const ("Script.Rewrite",_) $ _ $ _ $ a) _ = Some a
   247       | get_t y (Const ("Script.Rewrite",_) $ _ $ _    ) a = Some a
   248       | get_t y (Const ("Script.Rewrite'_Inst",_) $ _ $ _ $ _ $ a) _ = Some a
   249       | get_t y (Const ("Script.Rewrite'_Inst",_) $ _ $ _ $ _ )    a = Some a
   250       | get_t y (Const ("Script.Rewrite'_Set",_) $ _ $ _ $ a) _ = Some a
   251       | get_t y (Const ("Script.Rewrite'_Set",_) $ _ $ _ )    a = Some a
   252       | get_t y (Const ("Script.Rewrite'_Set'_Inst",_) $ _ $ _ $ _ $a)_ =Some a
   253       | get_t y (Const ("Script.Rewrite'_Set'_Inst",_) $ _ $ _ $ _ )  a =Some a
   254       | get_t y (Const ("Script.Calculate",_) $ _ $ a) _ = Some a
   255       | get_t y (Const ("Script.Calculate",_) $ _ )    a = Some a
   256     
   257       | get_t y (Const ("Script.Substitute",_) $ _ $ a) _ = Some a
   258       | get_t y (Const ("Script.Substitute",_) $ _ )    a = Some a
   259     
   260       | get_t y (Const ("Script.SubProblem",_) $ _ $ _) _ = None
   261 
   262       | get_t y x _ =  
   263 	((*writeln ("### get_t yac: list-expr "^(term2str x));*)
   264 	 None)
   265 in get_t thy body e_term end;
   266     
   267 (*FIXME: get 1st stac by next_stac [] instead of ... ?? 29.7.02*)
   268 (* val Script sc = scr;
   269    *)
   270 fun init_form thy (Script sc) env =
   271   (case get_stac thy sc of
   272      None => None (*raise error ("init_form: no 1st stac in "^
   273 			  (Sign.string_of_term (sign_of thy) sc))*)
   274    | Some stac => Some (subst_atomic env stac))
   275   | init_form _ _ _ = raise error "init_form: no match";
   276 
   277 (* use"ME/script.sml";
   278    use"script.sml";
   279    *)
   280 
   281 
   282 
   283 (*the 'iteration-argument' of a stac (args not eval)*)
   284 fun itr_arg _ (Const ("Script.Rewrite'_Inst",_) $ _ $ _ $ _ $ v) = v
   285   | itr_arg _ (Const ("Script.Rewrite",_) $ _ $ _ $ v) = v
   286   | itr_arg _ (Const ("Script.Rewrite'_Set'_Inst",_) $ _ $ _ $ _ $ v) = v
   287   | itr_arg _ (Const ("Script.Rewrite'_Set",_) $ _ $ _ $ v) = v
   288   | itr_arg _ (Const ("Script.Calculate",_) $ _ $ v) = v
   289   | itr_arg _ (Const ("Script.Check'_elementwise",_) $ consts $ _) = consts
   290   | itr_arg _ (Const ("Script.Or'_to'_List",_) $ _) = e_term
   291   | itr_arg _ (Const ("Script.Tac",_) $ _) = e_term
   292   | itr_arg _ (Const ("Script.SubProblem",_) $ _ $ _) = e_term
   293   | itr_arg thy t = raise error 
   294     ("itr_arg not impl. for "^
   295      (Sign.string_of_term (sign_of (assoc_thy thy)) t));
   296 (* val t = (term_of o the o (parse thy))"Rewrite rroot_square_inv False e_";
   297 > itr_arg "Script.thy" t;
   298 val it = Free ("e_","RealDef.real") : term 
   299 > val t = (term_of o the o (parse thy))"xxx";
   300 > itr_arg "Script.thy" t;
   301 *** itr_arg not impl. for xxx
   302 uncaught exception ERROR
   303   raised at: library.ML:1114.35-1114.40*)
   304 
   305 
   306 (*.get the arguments of the script out of the scripts parsetree.*)
   307 fun formal_args scr = (fst o split_last o snd o strip_comb) scr;
   308 (*
   309 > formal_args scr;
   310   [Free ("f_","RealDef.real"),Free ("v_","RealDef.real"),
   311    Free ("eqs_","bool List.list")] : term list
   312 *)
   313 
   314 (*.get the identifier of the script out of the scripts parsetree.*)
   315 fun id_of_scr sc = (id_of o fst o strip_comb) sc;
   316 
   317 
   318 (*26.5.02: not clear, when a is available in ass_up for eva-_true*)
   319 fun upd_env_opt env (Some a, v) = upd_env env (a,v)
   320   | upd_env_opt env (None, v) = 
   321     (writeln("*** upd_env_opt: (None,"^(term2str v)^")");env);
   322 
   323 
   324 type dsc = typ; (*<-> nam..unknow in Descript.thy*)
   325 fun typ_str (Type (s,_)) = s
   326   | typ_str (TFree(s,_)) = s
   327   | typ_str (TVar ((s,i),_)) = s^(string_of_int i);
   328 	     
   329 (*get the _result_-type of a description*)
   330 fun dsc_valT (Const (_,(Type (_,[_,T])))) = (strip_thy o typ_str) T;
   331 (*> val t = (term_of o the o (parse thy)) "equality";
   332 > val T = type_of t;
   333 val T = "bool => Tools.una" : typ
   334 > val dsc = dsc_valT t;
   335 val dsc = "una" : string
   336 
   337 > val t = (term_of o the o (parse thy)) "fixedValues";
   338 > val T = type_of t;
   339 val T = "bool List.list => Tools.nam" : typ
   340 > val dsc = dsc_valT t;
   341 val dsc = "nam" : string*)
   342 
   343 (*.from penv in itm_ make args for script depending on type of description.*)
   344 (*6.5.03 TODO: push penv into script -- and drop mk_arg here || drop penv
   345   9.5.03 penv postponed: penv = env for script at the moment, (*mk_arg*)*)
   346 fun mk_arg thy d [] = raise error ("mk_arg: no data for "^
   347 			       (Sign.string_of_term (sign_of thy) d))
   348   | mk_arg thy d [t] = 
   349     (case dsc_valT d of
   350 	 "una" => [t]
   351        | "nam" => 
   352 	 [case t of
   353 	      r as (Const ("op =",_) $ _ $ _) => r
   354 	    | _ => raise error 
   355 			     ("mk_arg: dsc-typ 'nam' applied to non-equality "^
   356 			      (Sign.string_of_term (sign_of thy) t))]
   357        | s => raise error ("mk_arg: not impl. for "^s))
   358     
   359   | mk_arg thy d (t::ts) = (mk_arg thy d [t]) @ (mk_arg thy d ts);
   360 (* 
   361  val d = d_in itm_;
   362  val [t] = ts_in itm_;
   363 mk_arg thy
   364 *)
   365 
   366 
   367 
   368 
   369 (*.create the actual parameters (args) of script: their order 
   370   is given by the order in met.pat .*)
   371 (*WN.5.5.03: ?: does this allow for different descriptions ???
   372              ?: why not taken from formal args of script ???
   373 !: FIXXXME penv: push it here in itms2args into script-evaluation*)
   374 (* val (thy, mI, itms) = (thy, metID, itms);
   375    *)
   376 fun itms2args thy mI (itms:itm list) =
   377     let val mvat = max_vt itms
   378 	fun okv mvat (_,vats,b,_,_) = mvat mem vats andalso b
   379 	val itms = filter (okv mvat) itms
   380 	fun test_dsc d (_,_,_,_,itm_) = (d = d_in itm_)
   381 	fun itm2arg itms (_,(d,_)) =
   382 	    case find_first (test_dsc d) itms of
   383 		None => 
   384 		raise error ("itms2args: '"^term2str d^"' not in itms")
   385 	      (*| Some (_,_,_,_,itm_) => mk_arg thy (d_in itm_) (ts_in itm_);
   386                penv postponed; presently penv holds already env for script*)
   387 	      | Some (_,_,_,_,itm_) => penvval_in itm_
   388 	fun sel_given_find (s,_) = (s = "#Given") orelse (s = "#Find")
   389 	val pats = (#ppc o get_met) mI
   390     in (flat o (map (itm2arg itms))) pats end;
   391 (*
   392 > val sc = ... Solve_root_equation ...
   393 > val mI = ("Script.thy","sqrt-equ-test");
   394 > val PblObj{meth={ppc=itms,...},...} = get_obj I pt [];
   395 > val ts = itms2args thy mI itms;
   396 > map (Sign.string_of_term (sign_of thy)) ts;
   397 ["sqrt (#9 + #4 * x) = sqrt x + sqrt (#5 + x)","x","#0"] : string list
   398 *)
   399 
   400 
   401 (*["bool_ (1+x=2)","real_ x"] --match_ags--> oris 
   402   --oris2fmz_vals--> ["equality (1+x=2)","boundVariable x","solutions L"]*)
   403 fun oris2fmz_vals oris =
   404     let fun ori2fmz_vals ((_,_,_,dsc,ts):ori) = 
   405 	    ((term2str o comp_dts') (dsc, ts), last_elem ts) 
   406 	    handle _ => raise error ("ori2fmz_env called with "^terms2str ts)
   407     in (split_list o (map ori2fmz_vals)) oris end;
   408 
   409 (*detour necessary, because generate1 delivers a string-result*)
   410 fun mout2term thy (Form' (FormKF (_,_,_,_,res))) = 
   411   (term_of o the o (parse (assoc_thy thy))) res
   412   | mout2term thy (Form' (PpcKF _)) = e_term;(*3.8.01: res of subpbl 
   413 					   at time of detection in script*)
   414 
   415 (*.convert a script-tac 'stac' to a tactic 'tac'; if stac is an initac,
   416    then convert to a 'tac_' (as required in appy).
   417    arg pt:ptree for pushing the thy specified in rootpbl into subpbls.*)
   418 fun stac2tac_ pt thy (Const ("Script.Rewrite",_) $ Free (thmID,_) $ _ $ f) =
   419 (* val (pt, thy, (Const ("Script.Rewrite",_) $ Free (thmID,_) $ _ $ f)) = 
   420        (pt, (assoc_thy th), stac);
   421    *)
   422     let val tid = (de_esc_underscore o strip_thy) thmID
   423     in (Rewrite (tid, (de_quote o string_of_thm o 
   424 		       (assoc_thm' thy)) (tid,"")), Empty_Tac_) end
   425 (* val (thy,
   426 	mm as(Const ("Script.Rewrite'_Inst",_) $  sub $ Free(thmID,_) $ _ $ f))
   427      = (assoc_thy th,stac);
   428    stac2tac_ pt thy mm;
   429 
   430    assoc_thm' (assoc_thy "Isac.thy") (tid,"");
   431    assoc_thm' Isac.thy (tid,"");
   432    *)
   433   | stac2tac_ pt thy (Const ("Script.Rewrite'_Inst",_) $ 
   434 	       sub $ Free (thmID,_) $ _ $ f) =
   435   let val subML = ((map isapair2pair) o isalist2list) sub
   436     val subStr = subst2subs subML
   437     val tid = (de_esc_underscore o strip_thy) thmID (*4.10.02 unnoetig*)
   438   in (Rewrite_Inst 
   439 	  (subStr, (tid, (de_quote o string_of_thm o
   440 			  (assoc_thm' thy)) (tid,""))), Empty_Tac_) end
   441       
   442   | stac2tac_ pt thy (Const ("Script.Rewrite'_Set",_) $ Free (rls,_) $ _ $ f)=
   443   (Rewrite_Set ((de_esc_underscore o strip_thy) rls), Empty_Tac_)
   444 
   445   | stac2tac_ pt thy (Const ("Script.Rewrite'_Set'_Inst",_) $ 
   446 	       sub $ Free (rls,_) $ _ $ f) =
   447   let val subML = ((map isapair2pair) o isalist2list) sub;
   448     val subStr = subst2subs subML;
   449   in (Rewrite_Set_Inst (subStr,rls), Empty_Tac_) end
   450 
   451   | stac2tac_ pt thy (Const ("Script.Calculate",_) $ Free (op_,_) $ f) =
   452   (Calculate op_, Empty_Tac_)
   453 
   454   | stac2tac_ pt thy (Const ("Script.Take",_) $ t) =
   455   (Take (term2str t), Empty_Tac_)
   456 
   457   | stac2tac_ pt thy (Const ("Script.Substitute",_) $ isasub $ arg) =
   458   (Substitute ((subte2sube o isalist2list) isasub), Empty_Tac_)
   459 (* val t = str2term"Substitute [x = L, M_b L = 0] (M_b x = q_0 * x + c)";
   460    val Const ("Script.Substitute", _) $ isasub $ arg = t;
   461    *)
   462 
   463 (*12.1.01.*)
   464   | stac2tac_ pt thy (Const("Script.Check'_elementwise",_) $ _ $ 
   465 		    (set as Const ("Collect",_) $ Abs (_,_,pred))) = 
   466   (Check_elementwise (Sign.string_of_term (sign_of thy) pred), 
   467    (*set*)Empty_Tac_)
   468 
   469   | stac2tac_ pt thy (Const("Script.Or'_to'_List",_) $ _ ) = 
   470   (Or_to_List, Empty_Tac_)
   471 
   472 (*12.1.01.for subproblem_equation_dummy in root-equation *)
   473   | stac2tac_ pt thy (Const ("Script.Tac",_) $ Free (str,_)) = 
   474   (Tac ((de_esc_underscore o strip_thy) str),  Empty_Tac_) 
   475 		    (*L_ will come from pt in appl_in*)
   476 
   477   (*3.12.03 copied from assod SubProblem*)
   478 (* val Const ("Script.SubProblem",_) $
   479 			 (Const ("Pair",_) $
   480 				Free (dI',_) $ 
   481 				(Const ("Pair",_) $ pI' $ mI')) $ ags' =
   482     str2term 
   483     "SubProblem (Test_,[linear,univariate,equation,test],[Test,solve_linear])\
   484     \ [bool_ (-1+x=0), real_ x]";
   485 *)
   486   | stac2tac_ pt thy (stac as Const ("Script.SubProblem",_) $
   487 			 (Const ("Pair",_) $
   488 				Free (dI',_) $ 
   489 			(Const ("Pair",_) $ pI' $ mI')) $ ags') =
   490 (*compare "| assod _ (Subproblem'"*)
   491     let val dI = ((implode o drop_last(*.._*) o explode) dI')^".thy";
   492         val thy = maxthy (assoc_thy dI) (rootthy pt);
   493 	val pI = ((map (de_esc_underscore o free2str)) o isalist2list) pI';
   494 	val mI = ((map (de_esc_underscore o free2str)) o isalist2list) mI';
   495 	val ags = isalist2list ags';
   496 	val (pI, pors, mI) = 
   497 	    if mI = ["no_met"] 
   498 	    then let val pors = (match_ags thy ((#ppc o get_pbt) pI) ags)
   499 			 handle _ => (match_ags_msg pI stac(*raise exn*); [])
   500 		     val pI' = refine_ori' pors pI;
   501 		 in (pI', pors (*refinement over models with diff.prec only*), 
   502 		     (hd o #met o get_pbt) pI') end
   503 	    else (pI, (match_ags thy ((#ppc o get_pbt) pI) ags)
   504 		  handle _ => (match_ags_msg pI stac(*raise exn*); []), 
   505 		  mI);
   506         val (fmz_, vals) = oris2fmz_vals pors;
   507 	val {cas,ppc,thy,...} = get_pbt pI
   508 	val dI = theory2theory' thy (*take dI from _refined_ pbl*)
   509 	val dI = theory2theory' (maxthy (assoc_thy dI) (rootthy pt));
   510 	val hdl = case cas of
   511 		      None => pblterm dI pI
   512 		    | Some t => subst_atomic ((vars_of_pbl_' ppc) ~~~ vals) t
   513         val f = subpbl (strip_thy dI) pI
   514     in (Subproblem (dI, pI),
   515 	Subproblem' ((dI, pI, mI), pors, hdl, fmz_, f))
   516     end
   517 
   518   | stac2tac_ pt thy t = raise error 
   519   ("stac2tac_ TODO: no match for "^
   520    (Sign.string_of_term (sign_of thy) t));
   521 (*
   522 > val t = (term_of o the o (parse thy)) 
   523  "Rewrite_Set_Inst [(bdv,v_::real)] isolate_bdv False (x=a+#1)";
   524 > stac2tac_ pt t;
   525 val it = Rewrite_Set_Inst ([(#,#)],"isolate_bdv") : tac
   526 
   527 > val t = (term_of o the o (parse SqRoot.thy)) 
   528 "(SubProblem (SqRoot_,[equation,univariate],(SqRoot_,solve_linear))\
   529    \         [bool_ e_, real_ v_])::bool list";
   530 > stac2tac_ pt SqRoot.thy t;
   531 val it = (Subproblem ("SqRoot.thy",[#,#]),Const (#,#) $ (# $ # $ (# $ #)))
   532 *)
   533 
   534 fun stac2tac pt thy t = (fst o stac2tac_ pt thy) t;
   535 
   536 
   537 (*.get the stactics and problems of a script as tacs
   538   instantiated with the current environment;
   539   l is the location which generated the given formula.*)
   540 (*WN.12.5.03: quick-and-dirty repair for listexpressions*)
   541 fun is_spec_pos Pbl = true
   542   | is_spec_pos Met = true
   543   | is_spec_pos _ = false;
   544 
   545 fun sel_rules _ (([],Res):pos') = 
   546     raise PTREE "no tactics applicable at the end of a calculation"
   547 | sel_rules pt (p,p_) =
   548   if is_spec_pos p_ 
   549   then [get_obj g_tac pt p]
   550   else
   551     let val pp = par_pblobj pt p;
   552 	val thy' = (get_obj g_domID pt pp):theory';
   553 	val thy = assoc_thy thy';
   554 	val metID = get_obj g_metID pt pp;
   555 	val metID' =if metID =e_metID then(thd3 o snd3)(get_obj g_origin pt pp)
   556 		     else metID;
   557         val Script sc = (#scr o get_met) metID';
   558 	val ScrState (env,_,_,_,_,_) = get_istate pt (p,p_);
   559     in map ((stac2tac pt thy) o rep_stacexpr o 
   560 	    (subst_stacexpr env None e_term)) (stacpbls sc) end;
   561 (*
   562 > val Script sc = (#scr o get_met) ("SqRoot.thy","sqrt-equ-test");
   563 > val env = [((term_of o the o (parse Isac.thy)) "bdv",
   564              (term_of o the o (parse Isac.thy)) "x")];
   565 > map ((stac2tac pt thy) o (subst_stacexpr env None e_term)) (stacpbls sc);
   566 *)
   567 
   568 
   569 
   570 
   571 
   572 (*test a term for being a _list_ (set ?) of constants; could be more rigorous*)
   573 fun list_of_consts (Const ("List.list.Cons",_) $ _ $ _) = true
   574   | list_of_consts (Const ("List.list.Nil",_)) = true
   575   | list_of_consts _ = false;
   576 (*val ttt = (term_of o the o (parse thy)) "[x=#1,x=#2,x=#3]";
   577 > list_of_consts ttt;
   578 val it = true : bool
   579 > val ttt = (term_of o the o (parse thy)) "[]";
   580 > list_of_consts ttt;
   581 val it = true : bool*)
   582 
   583 
   584 
   585 
   586 
   587 (* 15.1.01: evaluation of preds only works occasionally,
   588             but luckily for the 2 examples of root-equ:
   589 > val s = ((term_of o the o (parse thy)) "x",
   590 	   (term_of o the o (parse thy)) "-#5//#12");
   591 > val asm = (term_of o the o (parse thy)) 
   592              "#0 <= #9 + #4 * x  &  #0 <= sqrt x + sqrt (#-3 + x)";
   593 > val pred = subst_atomic [s] asm;
   594 > rewrite_set_ thy false (cterm_of (sign_of thy) pred);
   595 val it = None : (cterm * cterm list) option !!!!!!!!!!!!!!!!!!!!!!!!!!!!
   596 > eval_true' (string_of_thy thy) "eval_rls" (subst_atomic [s] pred);
   597 val it = false : bool
   598 
   599 > val s = ((term_of o the o (parse thy)) "x",
   600 	   (term_of o the o (parse thy)) "#4");
   601 > val asm = (term_of o the o (parse thy)) 
   602              "#0 <= #9 + #4 * x  &  #0 <= sqrt x + sqrt (#5 + x)";
   603 > val pred = subst_atomic [s] asm;
   604 > rewrite_set_ thy false (cterm_of (sign_of thy) pred);
   605 val it = Some ("True & True",[]) : (cterm * cterm list) option
   606 > eval_true' (string_of_thy thy) "eval_rls" (subst_atomic [s] pred);
   607 val it = true : bool`*)
   608 
   609 (*for check_elementwise: take apart the set, ev. instantiate assumptions
   610 fun rep_set thy pt p (set as Const ("Collect",_) $ Abs _) =
   611   let val (_ $ Abs (bdv,T,pred)) = inst_abs thy set;
   612     val bdv = Free (bdv,T);
   613     val pred = if pred <> Const ("Script.Assumptions",bool)
   614 		 then pred 
   615 	       else (mk_and o (map fst)) (get_assumptions_ pt (p,Res))
   616   in (bdv, pred) end
   617   | rep_set thy _ _ set = 
   618     raise error ("check_elementwise: no set "^ (*from script*)
   619 		 (Sign.string_of_term (sign_of thy) set));
   620 (*> val set = (term_of o the o (parse thy)) "{(x::real). Assumptions}";
   621 > val p = [];
   622 > val pt = union_asm pt p [("#0 <= sqrt x + sqrt (#5 + x)",[11]),
   623                            ("#0 <= #9 + #4 * x",[22]),
   624 			   ("#0 <= x ^^^ #2 + #5 * x",[33]),
   625 			   ("#0 <= #2 + x",[44])];
   626 > val (bdv,pred) = rep_set thy pt p set;
   627 val bdv = Free ("x","RealDef.real") : term
   628 > writeln (Sign.string_of_term (sign_of thy) pred);
   629 ((#0 <= sqrt x + sqrt (#5 + x) & #0 <= #9 + #4 * x) &
   630  #0 <= x ^^^ #2 + #5 * x) &
   631 #0 <= #2 + x
   632 *)
   633 --------------------------------------------11.6.03--was unused*)
   634 
   635 
   636 
   637 
   638 datatype ass = 
   639   Ass of tac_ *  (*SubProblem gets args instantiated in assod*)
   640 	 term      (*for itr_arg,result in ets*)
   641 | AssWeak of tac_ *
   642 	     term  (*for itr_arg,result in ets*)
   643 | NotAss;
   644 
   645 (*.assod: tac_ associated with stac w.r.t. d
   646 args
   647  pt:ptree for pushing the thy specified in rootpbl into subpbls
   648 returns
   649  Ass    : associated: e.g. thmID in stac = thmID in m
   650                        +++ arg   in stac = arg   in m
   651  AssWeak: weakly ass.:e.g. thmID in stac = thmID in m, //arg//
   652  NotAss :             e.g. thmID in stac/=/thmID in m (not =)
   653 8.01:
   654  tac_ SubProblem with args completed from script
   655 .*)
   656 fun assod pt d (m as Rewrite_Inst' (thy',rod,rls,put,subs,(thmID,thm),f,(f',asm)))
   657   (Const ("Script.Rewrite'_Inst",_) $ subs_ $ Free (thmID_,idT) $ b $ f_) = 
   658    if thmID = thmID_ then 
   659     if f = f_ then ((*writeln"3### assod ..Ass";*)Ass (m,f')) 
   660     else ((*writeln"3### assod ..AssWeak";*)AssWeak(m, f'))
   661   else ((*writeln"3### assod ..NotAss";*)NotAss)
   662 
   663   | assod pt d (m as Rewrite' (thy,rod,rls,put,(thmID,thm),f,(f',asm))) 
   664   (t as Const ("Script.Rewrite",_) $ Free (thmID_,idT) $ b $ f_) =
   665   ((*writeln("3### assod: stac = "^
   666 	   (Sign.string_of_term (sign_of (assoc_thy thy)) t));
   667    writeln("3### assod: f(m)= "^
   668 	   (Sign.string_of_term (sign_of (assoc_thy thy)) f));*)
   669    if thmID = thmID_ then 
   670     if f = f_ then ((*writeln"3### assod ..Ass";*)Ass (m,f')) 
   671     else ((*writeln"### assod ..AssWeak";
   672 	  writeln("### assod: f(m)  = "^
   673 		  (Sign.string_of_term (sign_of (assoc_thy thy)) f));
   674 	  writeln("### assod: f(stac)= "^
   675 		  (Sign.string_of_term (sign_of (assoc_thy thy)) f_));*)
   676 	  AssWeak (m,f'))
   677   else ((*writeln"3### assod ..NotAss";*)NotAss))
   678 
   679 (*val f = (term_of o the o (parse thy))"#0+(sqrt(sqrt(sqrt a))^^^#2)^^^#2=#0";
   680 > val f'= (term_of o the o (parse thy))"#0+(sqrt(sqrt a))^^^#2=#0";
   681 > val m =   Rewrite'("Script.thy","tless_true","eval_rls",false,
   682  ("rroot_square_inv",""),f,(f',[]));
   683 > val stac = (term_of o the o (parse thy))
   684  "Rewrite rroot_square_inv False (#0+(sqrt(sqrt(sqrt a))^^^#2)^^^#2=#0)";
   685 > assod e_rls m stac;
   686 val it =
   687   (Some (Rewrite' (#,#,#,#,#,#,#)),Const ("empty","RealDef.real"),
   688    Const ("empty","RealDef.real")) : tac_ option * term * term*)
   689 
   690   | assod pt d (m as Rewrite_Set_Inst' (thy',put,sub,rls,f,(f',asm))) 
   691   (Const ("Script.Rewrite'_Set'_Inst",_) $ sub_ $ Free (rls_,_) $ _ $ f_)= 
   692   if id_rls rls = rls_ then 
   693     if f = f_ then Ass (m,f') else AssWeak (m,f')
   694   else NotAss
   695 
   696   | assod pt d (m as Detail_Set_Inst' (thy',put,sub,rls,f,(f',asm))) 
   697   (Const ("Script.Rewrite'_Set'_Inst",_) $ sub_ $ Free (rls_,_) $ _ $ f_)= 
   698   if id_rls rls = rls_ then 
   699     if f = f_ then Ass (m,f') else AssWeak (m,f')
   700   else NotAss
   701 
   702   | assod pt d (m as Rewrite_Set' (thy,put,rls,f,(f',asm))) 
   703   (Const ("Script.Rewrite'_Set",_) $ Free (rls_,_) $ _ $ f_) = 
   704   if id_rls rls = rls_ then 
   705     if f = f_ then Ass (m,f') else AssWeak (m,f')
   706   else NotAss
   707 
   708   | assod pt d (m as Detail_Set' (thy,put,rls,f,(f',asm))) 
   709   (Const ("Script.Rewrite'_Set",_) $ Free (rls_,_) $ _ $ f_) = 
   710   if id_rls rls = rls_ then 
   711     if f = f_ then Ass (m,f') else AssWeak (m,f')
   712   else NotAss
   713 
   714   | assod pt d (m as Calculate' (thy',op_,f,(f',thm'))) 
   715   (Const ("Script.Calculate",_) $ Free (op__,_) $ f_) = 
   716   if op_ = op__ then
   717     if f = f_ then Ass (m,f') else AssWeak (m,f')
   718   else NotAss
   719 
   720   | assod pt _ (m as Check_elementwise' (consts,_,(consts_chkd,_)))
   721     (Const ("Script.Check'_elementwise",_) $ consts' $ _) =
   722     ((*writeln("### assod Check'_elementwise: consts= "^(term2str consts)^
   723 	     ", consts'= "^(term2str consts'));
   724      atomty consts; atomty consts';*)
   725      if consts = consts' then ((*writeln"### assod Check'_elementwise: Ass";*)
   726 			       Ass (m, consts_chkd))
   727      else ((*writeln"### assod Check'_elementwise: NotAss";*) NotAss))
   728 
   729   | assod pt _ (m as Or_to_List' (ors, list)) 
   730 	  (Const ("Script.Or'_to'_List",_) $ _) =
   731 	  Ass (m, list) 
   732 
   733   | assod pt _ (m as Take' term) 
   734 	  (Const ("Script.Take",_) $ _) =
   735 	  Ass (m, term)
   736 
   737   | assod pt _ (m as Substitute' (_, _, res)) 
   738 	  (Const ("Script.Substitute",_) $ _ $ _) =
   739 	  Ass (m, res) 
   740 (* val t = str2term "Substitute [(x, 3)] (x^^^2 + x + 1)";
   741    val (Const ("Script.Substitute",_) $ _ $ _) = t;
   742    *)
   743 
   744   | assod pt _ (m as Tac_ (thy,f,id,f'))  
   745     (Const ("Script.Tac",_) $ Free (id',_)) =
   746     if id = id' then Ass (m, ((term_of o the o (parse thy)) f'))
   747     else NotAss
   748 
   749 
   750 (* val t = str2term 
   751               "SubProblem (DiffApp_,[make,function],[no_met]) \
   752 	      \[real_ m_, real_ v_, bool_list_ rs_]";
   753 
   754  val (Subproblem' ((domID,pblID,metID),_,_,_,f)) = m;
   755  val (Const ("Script.SubProblem",_) $
   756 		 (Const ("Pair",_) $
   757 			Free (dI',_) $
   758 			(Const ("Pair",_) $ pI' $ mI')) $ ags') = stac;
   759  *)
   760   | assod pt _ (Subproblem' ((domID,pblID,metID),_,_,_,f))
   761 	  (stac as Const ("Script.SubProblem",_) $
   762 		 (Const ("Pair",_) $
   763 			Free (dI',_) $ 
   764 			(Const ("Pair",_) $ pI' $ mI')) $ ags') =
   765 (*compare "| stac2tac_ thy (Const ("Script.SubProblem",_)"*)
   766     let val dI = ((implode o drop_last o explode) dI')^".thy";
   767         val thy = maxthy (assoc_thy dI) (rootthy pt);
   768 	val pI = ((map (de_esc_underscore o free2str)) o isalist2list) pI';
   769 	val mI = ((map (de_esc_underscore o free2str)) o isalist2list) mI';
   770 	val ags = isalist2list ags';
   771 	val (pI, pors, mI) = 
   772 	    if mI = ["no_met"] 
   773 	    then let val pors = (match_ags thy ((#ppc o get_pbt) pI) ags)
   774 			 handle _ => (match_ags_msg pI stac(*raise exn*); []);
   775 		     val pI' = refine_ori' pors pI;
   776 		 in (pI', pors (*refinement over models with diff.prec only*), 
   777 		     (hd o #met o get_pbt) pI') end
   778 	    else (pI, (match_ags thy ((#ppc o get_pbt) pI) ags)
   779 		      handle _ => (match_ags_msg pI stac(*raise exn*); []), 
   780 		  mI);
   781         val (fmz_, vals) = oris2fmz_vals pors;
   782 	val {cas, ppc,...} = get_pbt pI
   783 	val {cas, ppc, thy,...} = get_pbt pI
   784 	val dI = theory2theory' thy (*take dI from _refined_ pbl*)
   785 	val dI = theory2theory' (maxthy (assoc_thy dI) (rootthy pt))
   786 	val hdl = case cas of
   787 		      None => pblterm dI pI
   788 		    | Some t => subst_atomic ((vars_of_pbl_' ppc) ~~~ vals) t
   789         val f = subpbl (strip_thy dI) pI
   790     in if domID = dI andalso pblID = pI
   791        then Ass (Subproblem' ((dI, pI, mI), pors, hdl, fmz_, f), f) 
   792        else NotAss
   793     end
   794 
   795   | assod pt d m t = 
   796     (writeln("### assod: NotAss m= "^(tac_2str m)^" , ..\n\
   797              \### ..assod:   stac= "^(term2str t));
   798      NotAss);
   799 
   800 
   801 
   802 fun tac_2tac (Refine_Tacitly' (pI,_,_,_,_)) = Refine_Tacitly pI
   803   | tac_2tac (Model_Problem' (pI,_))        = Model_Problem pI
   804   | tac_2tac (Add_Given' (t,_))             = Add_Given t
   805   | tac_2tac (Add_Find' (t,_))              = Add_Find t
   806   | tac_2tac (Add_Relation' (t,_))          = Add_Relation t
   807  
   808   | tac_2tac (Specify_Theory' dI)           = Specify_Theory dI
   809   | tac_2tac (Specify_Problem' (dI,_))      = Specify_Problem dI
   810   | tac_2tac (Specify_Method' (dI,_,_))     = Specify_Method dI
   811   
   812   | tac_2tac (Rewrite' (thy,rod,erls,put,(thmID,thm),f,(f',asm))) =
   813     Rewrite (thmID,thm)
   814 
   815   | tac_2tac (Rewrite_Inst' (thy,rod,erls,put,sub,(thmID,thm),f,(f',asm)))=
   816     Rewrite_Inst (subst2subs sub,(thmID,thm))
   817 
   818   | tac_2tac (Rewrite_Set' (thy,put,rls,f,(f',asm))) = 
   819     Rewrite_Set (id_rls rls)
   820 
   821   | tac_2tac (Detail_Set' (thy,put,rls,f,(f',asm))) = 
   822     Detail_Set (id_rls rls)
   823 
   824   | tac_2tac (Rewrite_Set_Inst' (thy,put,sub,rls,f,(f',asm))) = 
   825     Rewrite_Set_Inst (subst2subs sub,id_rls rls)
   826 
   827   | tac_2tac (Detail_Set_Inst' (thy,put,sub,rls,f,(f',asm))) = 
   828     Detail_Set_Inst (subst2subs sub,id_rls rls)
   829 
   830   | tac_2tac (Calculate' (thy,op_,t,(t',thm'))) = Calculate (op_)
   831 
   832   | tac_2tac (Check_elementwise' (consts,pred,consts')) =
   833     Check_elementwise pred
   834 
   835   | tac_2tac (Or_to_List' _) = Or_to_List
   836   | tac_2tac (Take' term) = Take (term2str term)
   837   | tac_2tac (Substitute' (subte, t, res)) = Substitute (subte2sube subte) 
   838 
   839   | tac_2tac (Tac_ (_,f,id,f')) = Tac id
   840 
   841   | tac_2tac (Subproblem' ((domID, pblID, _), _, _,_,_)) = 
   842 		  Subproblem (domID, pblID)
   843   | tac_2tac (Check_Postcond' (pblID, _)) = 
   844 		  Check_Postcond pblID
   845   | tac_2tac Empty_Tac_ = Empty_Tac
   846 
   847   | tac_2tac m = 
   848   raise error ("tac_2tac: not impl. for "^(tac_2str m));
   849 
   850 
   851 
   852 
   853 (** decompose tac_ to a rule and to (lhs,rhs)
   854     unly needed                            ~~~ **)
   855 
   856 val idT = Type ("Script.ID",[]);
   857 (*val tt = (term_of o the o (parse thy)) "square_equation_left::ID";
   858 type_of tt = idT;
   859 val it = true : bool
   860 *)
   861 (* 13.3.01
   862 v
   863 *)
   864 fun make_rule thy t =
   865   let val ct = cterm_of (sign_of thy) (Trueprop $ t)
   866   in Thm (string_of_cterm ct, make_thm ct) end;
   867 
   868 (* val (Rewrite_Inst'(thy',rod,rls,put,subs,(thmID,thm),f,(f',asm)))=m;
   869    *)
   870 (*decompose tac_ to a rule and to (lhs,rhs) for ets FIXME.12.03: obsolete!
   871  NOTE.12.03: also used for msg 'not locatable' ?!: 'Subproblem' missing !!!
   872 WN0508 only use in tac_2res, which uses only last return-value*)
   873 fun rep_tac_ (Rewrite_Inst' 
   874 		 (thy',rod,rls,put,subs,(thmID,thm),f,(f',asm))) = 
   875   let val fT = type_of f;
   876     val b = if put then HOLogic.true_const else HOLogic.false_const;
   877     val sT = (type_of o fst o hd) subs;
   878     val subs' = list2isalist (HOLogic.mk_prodT (sT, sT))
   879       (map HOLogic.mk_prod subs);
   880     val sT' = type_of subs';
   881     val lhs = Const ("Script.Rewrite'_Inst",[sT',idT,(*fT*)bool,fT] ---> fT) 
   882       $ subs' $ Free (thmID,idT) $ b $ f;
   883   in (((make_rule (assoc_thy thy')) o HOLogic.mk_eq) (lhs,f'),(lhs,f')) end
   884 (*Fehlersuche 25.4.01
   885 (a)----- als String zusammensetzen:
   886 ML> Sign.string_of_term (sign_of thy)f; 
   887 val it = "d_d x #4 + d_d x (x ^^^ #2 + #3 * x)" : string
   888 ML> Sign.string_of_term (sign_of thy)f'; 
   889 val it = "#0 + d_d x (x ^^^ #2 + #3 * x)" : string
   890 ML> subs;
   891 val it = [(Free ("bdv","RealDef.real"),Free ("x","RealDef.real"))] : subst
   892 > val tt = (term_of o the o (parse thy))
   893   "(Rewrite_Inst[(bdv,x)]diff_const False(d_d x #4 + d_d x (x ^^^ #2 + #3 * x)))=(#0 + d_d x (x ^^^ #2 + #3 * x))";
   894 > atomty tt;
   895 ML> writeln(Sign.string_of_term (sign_of thy)tt); 
   896 (Rewrite_Inst [(bdv,x)] diff_const False d_d x #4 + d_d x (x ^^^ #2 + #3 * x)) =
   897  #0 + d_d x (x ^^^ #2 + #3 * x)
   898 
   899 (b)----- laut rep_tac_:
   900 > val ttt=HOLogic.mk_eq (lhs,f');
   901 > atomty ttt;
   902 
   903 
   904 (*Fehlersuche 1-2Monate vor 4.01:*)
   905 > val tt = (term_of o the o (parse thy))
   906   "Rewrite_Inst[(bdv,x)]square_equation_left True(x=#1+#2)";
   907 > atomty tt;
   908 
   909 > val f = (term_of o the o (parse thy)) "x=#1+#2";
   910 > val f' = (term_of o the o (parse thy)) "x=#3";
   911 > val subs = [((term_of o the o (parse thy)) "bdv",
   912 	       (term_of o the o (parse thy)) "x")];
   913 > val sT = (type_of o fst o hd) subs;
   914 > val subs' = list2isalist (HOLogic.mk_prodT (sT, sT))
   915 			      (map HOLogic.mk_prod subs);
   916 > val sT' = type_of subs';
   917 > val lhs = Const ("Script.Rewrite'_Inst",[sT',idT,fT,fT] ---> fT) 
   918   $ subs' $ Free (thmID,idT) $ HOLogic.true_const $ f;
   919 > lhs = tt;
   920 val it = true : bool
   921 > rep_tac_ (Rewrite_Inst' 
   922 	       ("Script.thy","tless_true","eval_rls",false,subs,
   923 		("square_equation_left",""),f,(f',[])));
   924 *)
   925   | rep_tac_ (Rewrite' (thy',rod,rls,put,(thmID,thm),f,(f',asm)))=
   926   let 
   927     val fT = type_of f;
   928     val b = if put then HOLogic.true_const else HOLogic.false_const;
   929     val lhs = Const ("Script.Rewrite",[idT,HOLogic.boolT,fT] ---> fT)
   930       $ Free (thmID,idT) $ b $ f;
   931   in (((make_rule (assoc_thy thy')) o HOLogic.mk_eq) (lhs,f'),(lhs,f')) end
   932 (* 
   933 > val tt = (term_of o the o (parse thy)) (*____   ____..test*)
   934   "Rewrite square_equation_left True (x=#1+#2) = (x=#3)";
   935 
   936 > val f = (term_of o the o (parse thy)) "x=#1+#2";
   937 > val f' = (term_of o the o (parse thy)) "x=#3";
   938 > val Thm (id,thm) = 
   939   rep_tac_ (Rewrite' 
   940    ("Script.thy","tless_true","eval_rls",false,
   941     ("square_equation_left",""),f,(f',[])));
   942 > val Some ct = parse thy   
   943   "Rewrite square_equation_left True (x=#1+#2)"; 
   944 > rewrite_ Script.thy tless_true eval_rls true thm ct;
   945 val it = Some ("x = #3",[]) : (cterm * cterm list) option
   946 *)
   947   | rep_tac_ (Rewrite_Set_Inst' 
   948 		 (thy',put,subs,rls,f,(f',asm))) =
   949     (e_rule, (e_term, f'))
   950 (*WN050824: type error ...
   951   let val fT = type_of f;
   952     val sT = (type_of o fst o hd) subs;
   953     val subs' = list2isalist (HOLogic.mk_prodT (sT, sT))
   954       (map HOLogic.mk_prod subs);
   955     val sT' = type_of subs';
   956     val b = if put then HOLogic.true_const else HOLogic.false_const
   957     val lhs = Const ("Script.Rewrite'_Set'_Inst",
   958 		     [sT',idT,fT,fT] ---> fT) 
   959       $ subs' $ Free (id_rls rls,idT) $ b $ f;
   960   in (((make_rule (assoc_thy thy')) o HOLogic.mk_eq) (lhs,f'),(lhs,f')) end*)
   961 (* ... vals from Rewrite_Inst' ...
   962 > rep_tac_ (Rewrite_Set_Inst' 
   963 	       ("Script.thy",false,subs,
   964 		"isolate_bdv",f,(f',[])));
   965 *)
   966 (* val (Rewrite_Set' (thy',put,rls,f,(f',asm)))=m;
   967 *)
   968   | rep_tac_ (Rewrite_Set' (thy',put,rls,f,(f',asm)))=
   969   let val fT = type_of f;
   970     val b = if put then HOLogic.true_const else HOLogic.false_const;
   971     val lhs = Const ("Script.Rewrite'_Set",[idT,bool,fT] ---> fT) 
   972       $ Free (id_rls rls,idT) $ b $ f;
   973   in (((make_rule (assoc_thy thy')) o HOLogic.mk_eq) (lhs,f'),(lhs,f')) end
   974 (* 13.3.01:
   975 val thy = assoc_thy thy';
   976 val t = HOLogic.mk_eq (lhs,f');
   977 make_rule thy t;
   978 --------------------------------------------------
   979 val lll = (term_of o the o (parse thy)) 
   980   "Rewrite_Set SqRoot_simplify False (d_d x (x ^^^ #2 + #3 * x) + d_d x #4)";
   981 
   982 --------------------------------------------------
   983 > val f = (term_of o the o (parse thy)) "x=#1+#2";
   984 > val f' = (term_of o the o (parse thy)) "x=#3";
   985 > val Thm (id,thm) = 
   986   rep_tac_ (Rewrite_Set' 
   987    ("Script.thy",false,"SqRoot_simplify",f,(f',[])));
   988 val id = "(Rewrite_Set SqRoot_simplify True x = #1 + #2) = (x = #3)" : string
   989 val thm = "(Rewrite_Set SqRoot_simplify True x = #1 + #2) = (x = #3)" : thm
   990 *)
   991   | rep_tac_ (Calculate' (thy',op_,f,(f',thm')))=
   992   let val fT = type_of f;
   993     val lhs = Const ("Script.Calculate",[idT,fT] ---> fT) 
   994       $ Free (op_,idT) $ f
   995   in (((make_rule (assoc_thy thy')) o HOLogic.mk_eq) (lhs,f'),(lhs,f')) end
   996 (*
   997 > val lhs'=(term_of o the o (parse thy))"Calculate plus (#1+#2)";
   998   ... test-root-equ.sml: calculate ...
   999 > val Appl m'=applicable_in p pt (Calculate "plus");
  1000 > val (lhs,_)=tac_2etac m';
  1001 > lhs'=lhs;
  1002 val it = true : bool*)
  1003   | rep_tac_ (Check_elementwise' (t,str,(t',asm)))  = (Erule, (e_term, t'))
  1004   | rep_tac_ (Subproblem' (_,_,_,_,t'))  = (Erule, (e_term, t'))
  1005   | rep_tac_ (Take' (t'))  = (Erule, (e_term, t'))
  1006   | rep_tac_ (Substitute' (subst,t,t'))  = (Erule, (t, t'))
  1007   | rep_tac_ (Or_to_List' (t, t'))  = (Erule, (t, t'))
  1008   | rep_tac_ m = raise error ("rep_tac_: not impl.for "^
  1009 				 (tac_2str m));
  1010 
  1011 (*"N.3.6.03------
  1012 fun tac_2rule m = (fst o rep_tac_) m;
  1013 fun tac_2etac m = (snd o rep_tac_) m;
  1014 fun tac_2tac m = (fst o snd o rep_tac_) m;*)
  1015 fun tac_2res m = (snd o snd o rep_tac_) m;(*ONLYuse of rep_tac_
  1016 					        FIXXXXME: simplify rep_tac_*)
  1017 
  1018 
  1019 (* use"ME/script.sml";
  1020    use"script.sml";
  1021    *)
  1022 
  1023 
  1024 
  1025 
  1026 (** locate an applicable stactic in a script **)
  1027 
  1028 datatype assoc = (*ExprVal in the sense of denotational semantics*)
  1029   Assoc of     (*the stac is associated, strongly or weakly*)
  1030   scrstate *       (*the current; returned for next_tac etc. outside ass* *)  
  1031   (step list)    (*list of steps done until associated stac found;
  1032 	           initiated with the data for doing the 1st step,
  1033                    thus the head holds these data further on,
  1034 		   while the tail holds steps finished (incl.scrstate in ptree)*)
  1035 | NasApp of   (*stac not associated, but applicable, ptree-node generated*)
  1036   scrstate * (step list)
  1037 | NasNap of     (*stac not associated, not applicable, nothing generated;
  1038 	         for distinction in Or, for leaving iterations, leaving Seq,
  1039 		 evaluate scriptexpressions*)
  1040   term * env;
  1041 fun assoc2str (Assoc     _) = "Assoc"
  1042   | assoc2str (NasNap  _) = "NasNap"
  1043   | assoc2str (NasApp _) = "NasApp";
  1044 
  1045 
  1046 datatype asap = (*arg. of assy _only_ for distinction w.r.t. Or*)
  1047   Aundef   (*undefined: set only by (topmost) Or*)
  1048 | AssOnly  (*do not execute appl stacs - there could be an associated
  1049 	     in parallel Or-branch*)
  1050 | AssGen;  (*no Ass(Weak) found within Or, thus 
  1051              search for _applicable_ stacs, execute and generate pt*)
  1052 (*this constructions doesnt allow arbitrary nesting of Or !!!*)
  1053 
  1054 
  1055 (*assy, ass_up, astep_up scanning for locate_gen at stactic in a script.
  1056   search is clearly separated into (1)-(2):
  1057   (1) assy is recursive descent;
  1058   (2) ass_up resumes interpretation at a location somewhere in the script;
  1059       astep_up does only get to the parentnode of the scriptexpr.
  1060   consequence:
  1061   * call of (2) means _always_ that in this branch below
  1062     there was an appl.stac (Repeat, Or e1, ...)
  1063 *)
  1064 
  1065 fun assy ya (is as (E,l,a,v,S,b),ss)
  1066 	  (Const ("Let",_) $ e $ (Abs (id,T,body))) =
  1067     ((*writeln("### assy Let$e$Abs: is=");
  1068      writeln(istate2str (ScrState is));*)
  1069      case assy ya ((E , l@[L,R], a,v,S,b),ss) e of
  1070 	 NasApp ((E',l,a,v,S,bb),ss) => 
  1071 	 let val id' = mk_Free (id, T);
  1072 	     val E' = upd_env E' (id', v);
  1073 	 (*val _=writeln("### assy Let -> NasApp");*)
  1074 	 in assy ya ((E', l@[R,D], a,v,S,b),ss) body end
  1075      | NasNap (v,E) => 	 
  1076 	 let val id' = mk_Free (id, T);
  1077 	   val E' = upd_env E (id', v);
  1078 	   (*val _=writeln("### assy Let -> NasNap");*)
  1079 	 in assy ya ((E', l@[R,D], a,v,S,b),ss) body end
  1080      | ay => ay)
  1081 
  1082   | assy (ya as (((thy,srls),_),_)) ((E,l,_,v,S,b),ss) 
  1083 	 (Const ("Script.While",_) $ c $ e $ a) =
  1084     ((*writeln("### assy While $ c $ e $ a, upd_env= "^
  1085 	     (subst2str (upd_env E (a,v))));*)
  1086      if eval_true_ thy srls (subst_atomic (upd_env E (a,v)) c) 
  1087      then assy ya ((E, l@[L,R], Some a,v,S,b),ss)  e
  1088      else NasNap (v, E))
  1089    
  1090   | assy (ya as (((thy,srls),_),_)) ((E,l,a,v,S,b),ss) 
  1091 	 (Const ("Script.While",_) $ c $ e) =
  1092     ((*writeln("### assy While, l= "^(loc_2str l));*)
  1093      if eval_true_ thy srls (subst_atomic (upd_env_opt E (a,v)) c) 
  1094      then assy ya ((E, l@[R], a,v,S,b),ss) e
  1095      else NasNap (v, E)) 
  1096 
  1097   | assy (ya as (((thy,srls),_),_)) ((E,l,a,v,S,b),ss) 
  1098 	 (Const ("If",_) $ c $ e1 $ e2) =
  1099     (if eval_true_ thy srls (subst_atomic (upd_env_opt E (a,v)) c) 
  1100      then assy ya ((E, l@[L,R], a,v,S,b),ss) e1
  1101      else assy ya ((E, l@[  R], a,v,S,b),ss) e2) 
  1102 
  1103   | assy ya ((E,l,_,v,S,b),ss) (Const ("Script.Try",_) $ e $ a) =
  1104   ((*writeln("### assy Try, l= "^(loc_2str l));*)
  1105     case assy ya ((E, l@[L,R], Some a,v,S,b),ss) e of
  1106      ay => ay) 
  1107 
  1108   | assy ya ((E,l,a,v,S,b),ss) (Const ("Script.Try",_) $ e) =
  1109   ((*writeln("### assy Try, l= "^(loc_2str l));*)
  1110     case assy ya ((E, l@[R], a,v,S,b),ss) e of
  1111      ay => ay)
  1112 
  1113   | assy ya ((E,l,_,v,S,b),ss) (Const ("Script.Seq",_) $e1 $ e2 $ a) =
  1114     ((*writeln("### assy Seq $e1 $ e2 $ a, E= "^(subst2str E));*)
  1115      case assy ya ((E, l@[L,L,R], Some a,v,S,b),ss) e1 of
  1116 	 NasNap (v, E) => assy ya ((E, l@[L,R], Some a,v,S,b),ss) e2
  1117        | NasApp ((E,_,_,v,_,_),ss) => 
  1118 	 assy ya ((E, l@[L,R], Some a,v,S,b),ss) e2
  1119        | ay => ay)
  1120 
  1121   | assy ya ((E,l,a,v,S,b),ss) (Const ("Script.Seq",_) $e1 $ e2) =
  1122     (case assy ya ((E, l@[L,R], a,v,S,b),ss) e1 of
  1123 	 NasNap (v, E) => assy ya ((E, l@[R], a,v,S,b),ss) e2
  1124        | NasApp ((E,_,_,v,_,_),ss) => 
  1125 	 assy ya ((E, l@[R], a,v,S,b),ss) e2
  1126        | ay => ay)
  1127     
  1128   | assy ya ((E,l,_,v,S,b),ss) (Const ("Script.Repeat",_) $ e $ a) =
  1129     assy ya ((E,(l@[L,R]),Some a,v,S,b),ss) e
  1130 
  1131   | assy ya ((E,l,a,v,S,b),ss) (Const ("Script.Repeat",_) $ e) =
  1132     assy ya ((E,(l@[R]),a,v,S,b),ss) e
  1133 
  1134 (*15.6.02: ass,app Or nochmals "uberlegen FIXXXME*)
  1135   | assy (y, Aundef) ((E,l,_,v,S,b),ss) (Const ("Script.Or",_) $e1 $ e2 $ a) =
  1136     (case assy (y, AssOnly) ((E,(l@[L,L,R]),Some a,v,S,b),ss) e1 of
  1137 	 NasNap (v, E) => 
  1138 	 (case assy (y, AssOnly) ((E,(l@[L,R]),Some a,v,S,b),ss) e2 of
  1139 	      NasNap (v, E) => 
  1140 	      (case assy (y, AssGen) ((E,(l@[L,L,R]),Some a,v,S,b),ss) e1 of
  1141 	       NasNap (v, E) => 
  1142 	       assy (y, AssGen) ((E, (l@[L,R]), Some a,v,S,b),ss) e2
  1143 	     | ay => ay)
  1144 	    | ay =>(ay))
  1145        | NasApp _ => raise error ("assy: FIXXXME ///must not return NasApp///")
  1146        | ay => (ay))
  1147 
  1148   | assy ya ((E,l,a,v,S,b),ss) (Const ("Script.Or",_) $e1 $ e2) =
  1149     (case assy ya ((E,(l@[L,R]),a,v,S,b),ss) e1 of
  1150 	 NasNap (v, E) => 
  1151 	 assy ya ((E,(l@[R]),a,v,S,b),ss) e2
  1152        | ay => (ay)) 
  1153 (* val ((m,_,pt,(p,p_),c)::ss) = [(m,EmptyMout,pt,p,[])];
  1154    val t = (term_of o the o (parse Isac.thy)) "Rewrite rmult_1 False";
  1155 
  1156    val (ap,(p,p_),c,ss) = (Aundef,p,[],[]);
  1157    assy (((thy',srls),d),ap) ((E,l,a,v,S,b), (m,EmptyMout,pt,(p,p_),c)::ss) t;
  1158    *) 
  1159 
  1160   | assy (((thy',sr),d),ap) (is as (E,l,a,v,S,b), (m,_,pt,(p,p_),c)::ss) t =
  1161     ((*writeln("### assy, m = "^tac_2str m);
  1162      writeln("### assy, (p,p_) = "^pos'2str (p,p_));
  1163      writeln("### assy, is= ");
  1164      writeln(istate2str (ScrState is));*)
  1165      case subst_stacexpr E a v t of
  1166 	Expr s => 
  1167 	((*writeln("### assy: listexpr t= "^(term2str t)); 
  1168          writeln("### assy, E= "^(env2str E));
  1169 	 writeln("### assy, eval(..)= "^(term2str
  1170 	       (eval_listexpr_ (assoc_thy thy') sr
  1171 			       (subst_atomic (upd_env_opt E (a,v)) t))));*)
  1172 	  NasNap (eval_listexpr_ (assoc_thy thy') sr
  1173 			       (subst_atomic (upd_env_opt E (a,v)) t), E))
  1174       (* val STac stac = subst_stacexpr E a v t;
  1175          *)
  1176       | STac stac =>
  1177 	let val _=writeln("### assy, stac = "^term2str stac);
  1178 	    val p' = case p_ of Frm => p | Res => lev_on p
  1179 			      | _ => raise error ("assy: call by "^
  1180 						  (pos'2str (p,p_)));
  1181 	in case assod pt d m stac of
  1182 	 Ass (m,v') =>
  1183 	 let (*val _=writeln("### assy: Ass ("^tac_2str m^", 
  1184 					     "^term2str v'^")");*)
  1185 	     val (p'',c',f',pt') = generate1 (assoc_thy thy') m 
  1186 			        (ScrState (E,l,a,v',S,true)) (p',p_) pt;
  1187 	   in Assoc ((E,l,a,v',S,true), (m,f',pt',p'',c @ c')::ss) end
  1188        | AssWeak (m,v') => 
  1189 	   let val (p'',c',f',pt') = generate1 (assoc_thy thy') m 
  1190 			         (ScrState (E,l,a,v',S,false)) (p',p_) pt;
  1191 	   in Assoc ((E,l,a,v',S,false), (m,f',pt',p'',c @ c')::ss) end
  1192        | NotAss =>
  1193 	   ((*writeln("### assy, NotAss");*)
  1194 	    case ap of   (*switch for Or: 1st AssOnly, 2nd AssGen*)
  1195 	      AssOnly => (NasNap (v, E))
  1196 	    | gen => (case applicable_in (p,p_) pt 
  1197 					 (stac2tac pt (assoc_thy thy') stac) of
  1198 			Appl m' =>
  1199 			  let val is = (E,l,a,tac_2res m',S,false(*FIXXXME*))
  1200 			      val (p'',c',f',pt') =
  1201 			      generate1 (assoc_thy thy') m' (ScrState is) (p',p_) pt;
  1202 			  in NasApp (is,(m,f',pt',p'',c @ c')::ss) end
  1203 		      | Notappl _ => 
  1204 			    (NasNap (v, E))
  1205 			    )
  1206 		)
  1207        end);
  1208 (* (astep_up ((thy',scr,d),NasApp_) ((E,l,a,v,S,b),[(m,EmptyMout,pt,p,[])])) handle e => print_exn_G e;
  1209   *)
  1210 
  1211 
  1212 (* val (ys as (y,s,Script sc,d),(is as (E,l,a,v,S,b),ss),Const ("Let",_) $ _) =
  1213        (ys, ((E,up,a,v,S,b),ss), go up sc);
  1214    *)
  1215 fun ass_up (ys as (y,s,Script sc,d)) (is as (E,l,a,v,S,b),ss) 
  1216 	   (Const ("Let",_) $ _) =
  1217     let (*val _= writeln("### ass_up1 Let$e: is=")
  1218 	val _= writeln(istate2str (ScrState is))*)
  1219 	val l = drop_last l; (*comes from e, goes to Abs*)
  1220       val (Const ("Let",_) $ e $ (Abs (i,T,body))) = go l sc;
  1221       val i = mk_Free (i, T);
  1222       val E = upd_env E (i, v);
  1223       (*val _=writeln("### ass_up2 Let$e: E="^(subst2str E));*)
  1224     in case assy (((y,s),d),Aundef) ((E, l@[R,D], a,v,S,b),ss) body of
  1225 	   Assoc iss => Assoc iss
  1226 	 | NasApp iss => astep_up ys iss 
  1227 	 | NasNap (v, E) => astep_up ys ((E,l,a,v,S,b),ss) end
  1228 
  1229   | ass_up ys iss (Abs (_,_,_)) = 
  1230     astep_up ys iss (*TODO 5.9.00: env ?*)
  1231 
  1232   | ass_up ys (iss as (is,_)) (Const ("Let",_) $ e $ (Abs (i,T,b)))=
  1233     ((*writeln("### ass_up Let$e$Abs: is=");
  1234      writeln(istate2str (ScrState is));*)
  1235      astep_up ys iss) (*TODO 5.9.00: env ?*)
  1236 
  1237 
  1238   | ass_up ysa iss (Const ("Script.Seq",_) $ _ $ _ $ _) = 
  1239     astep_up ysa iss (*all has been done in (*2*) below*)
  1240 
  1241   | ass_up ysa iss (Const ("Script.Seq",_) $ _ $ _) = 
  1242     astep_up ysa iss (*2*: comes from e2*)
  1243 
  1244   | ass_up (ysa as (y,s,Script sc,d)) (is as (E,l,a,v,S,b),ss)
  1245 	   (Const ("Script.Seq",_) $ _ ) = (*2*: comes from e1, goes to e2*)
  1246     let val up = drop_last l;
  1247 	val Const ("Script.Seq",_) $ _ $ e2 = go up sc
  1248 	(*val _= writeln("### ass_up Seq$e: is=")
  1249 	val _= writeln(istate2str (ScrState is))*)
  1250     in case assy (((y,s),d),Aundef) ((E, up@[R], a,v,S,b),ss) e2 of
  1251 	   NasNap (v,E) => astep_up ysa ((E,up,a,v,S,b),ss)
  1252 	 | NasApp iss => astep_up ysa iss
  1253 	 | ay => ay end
  1254 
  1255   | ass_up ysa iss (Const ("Script.Try",_) $ e $ _) =
  1256     astep_up ysa iss
  1257 
  1258   | ass_up ysa iss (Const ("Script.Try",_) $ e) =
  1259     astep_up ysa iss
  1260 
  1261   | ass_up (ys as (y,s,_,d)) ((E,l,_,v,S,b),ss)
  1262 	   (Const ("Script.While",_) $ c $ e $ a) =
  1263     ((*writeln("### ass_up: While c= "^
  1264 	     (term2str (subst_atomic (upd_env E (a,v)) c)));*)
  1265      if eval_true_ y s (subst_atomic (upd_env E (a,v)) c)
  1266     then (case assy (((y,s),d),Aundef) ((E, l@[L,R], Some a,v,S,b),ss) e of 
  1267        NasNap (v,E') => astep_up ys ((E',l, Some a,v,S,b),ss)
  1268      | NasApp ((E',l,a,v,S,b),ss) =>
  1269        ass_up ys ((E',l,a,v,S,b),ss) t
  1270      | ay => ay)
  1271     else astep_up ys ((E,l, Some a,v,S,b),ss)
  1272 	 )
  1273 
  1274   | ass_up (ys as (y,s,_,d)) ((E,l,a,v,S,b),ss)
  1275 	   (Const ("Script.While",_) $ c $ e) =
  1276     if eval_true_ y s (subst_atomic (upd_env_opt E (a,v)) c)
  1277     then (case assy (((y,s),d),Aundef) ((E, l@[R], a,v,S,b),ss) e of 
  1278        NasNap (v,E') => astep_up ys ((E',l, a,v,S,b),ss)
  1279      | NasApp ((E',l,a,v,S,b),ss) =>
  1280        ass_up ys ((E',l,a,v,S,b),ss) t
  1281      | ay => ay)
  1282     else astep_up ys ((E,l, a,v,S,b),ss)
  1283 
  1284   | ass_up y iss (Const ("If",_) $ _ $ _ $ _) = astep_up y iss
  1285 
  1286   | ass_up (ys as (y,s,_,d)) ((E,l,_,v,S,b),ss)
  1287 	   (t as Const ("Script.Repeat",_) $ e $ a) =
  1288   (case assy (((y,s),d), Aundef) ((E, (l@[L,R]), Some a,v,S,b),ss) e of 
  1289        NasNap (v,E') => astep_up ys ((E',l, Some a,v,S,b),ss)
  1290      | NasApp ((E',l,a,v,S,b),ss) =>
  1291        ass_up ys ((E',l,a,v,S,b),ss) t
  1292      | ay => ay)
  1293 
  1294   | ass_up (ys as (y,s,_,d)) (is as ((E,l,a,v,S,b),ss)) 
  1295 	   (t as Const ("Script.Repeat",_) $ e) =
  1296   (case assy (((y,s),d), Aundef) ((E, (l@[R]), a,v,S,b),ss) e of 
  1297        NasNap (v', E') => astep_up ys ((E',l,a,v',S,b),ss)
  1298      | NasApp ((E',l,a,v',S,bb),ss) => 
  1299        ass_up ys ((E',l,a,v',S,b),ss) t
  1300      | ay => ay)
  1301 
  1302   | ass_up y iss (Const ("Script.Or",_) $ _ $ _ $ _) = astep_up y iss
  1303 
  1304   | ass_up y iss (Const ("Script.Or",_) $ _ $ _) = astep_up y iss
  1305 
  1306   | ass_up y ((E,l,a,v,S,b),ss) (Const ("Script.Or",_) $ _ ) = 
  1307     astep_up y ((E, (drop_last l), a,v,S,b),ss)
  1308 
  1309   | ass_up  y iss t =
  1310     raise error ("ass_up not impl for t= "^(term2str t))
  1311 (* 9.6.03
  1312    val (ys as (_,_,Script sc,_), ss) = 
  1313        ((thy',srls,scr,d), [(m,EmptyMout,pt,p,[])]:step list);
  1314    astep_up ys ((E,l,a,v,S,b),ss);
  1315 
  1316    val ((ys as (_,_,Script sc,_)), ((E,l,a,v,S,b),ss)) = 
  1317        ((thy',srls,scr,d), ((E,l,a,v,S,b), [(m,EmptyMout,pt,p,[])]));
  1318    *)  
  1319 and astep_up (ys as (_,_,Script sc,_)) ((E,l,a,v,S,b),ss) =
  1320   if 1 < length l 
  1321     then 
  1322       let val up = drop_last l;
  1323 	  (*val _= writeln("### astep_up: E= "env2str E);*)
  1324       in ass_up ys ((E,up,a,v,S,b),ss) (go up sc) end
  1325   else (NasNap (v, E))
  1326 ;
  1327 
  1328 
  1329 
  1330 
  1331 
  1332 (* use"ME/script.sml";
  1333    use"script.sml";
  1334  term2str (go up sc);
  1335 
  1336    *)
  1337 
  1338 (*check if there are tacs for rewriting only*)
  1339 fun rew_only ([]:step list) = true
  1340   | rew_only (((Rewrite' _          ,_,_,_,_))::ss) = rew_only ss
  1341   | rew_only (((Rewrite_Inst' _     ,_,_,_,_))::ss) = rew_only ss
  1342   | rew_only (((Rewrite_Set' _      ,_,_,_,_))::ss) = rew_only ss
  1343   | rew_only (((Rewrite_Set_Inst' _ ,_,_,_,_))::ss) = rew_only ss
  1344   | rew_only (((Calculate' _        ,_,_,_,_))::ss) = rew_only ss
  1345   | rew_only (((Begin_Trans' _      ,_,_,_,_))::ss) = rew_only ss
  1346   | rew_only (((End_Trans' _        ,_,_,_,_))::ss) = rew_only ss
  1347   | rew_only _ = false; 
  1348   
  1349 
  1350 datatype locate =
  1351   Steps of istate      (*producing hd of step list (which was latest)
  1352 	                 for next_tac, for reporting Safe|Unsafe to DG*)
  1353 	   * step      (*(scrstate producing this step is in ptree !)*) 
  1354 		 list  (*locate_gen may produce intermediate steps*)
  1355 | NotLocatable;        (*no (m Ass m') or (m AssWeak m') found*)
  1356 
  1357 
  1358 
  1359 (* locate_gen tries to locate an input tac m in the script. 
  1360    pursuing this goal the script is executed until an (m' equiv m) is found,
  1361    or the end of the script
  1362 args
  1363    m   : input by the user, already checked by applicable_in,
  1364          (to be searched within Or; and _not_ an m doing the step on ptree !)
  1365    p,pt: (incl ets) at the time of input
  1366    scr : the script
  1367    d   : canonical simplifier for locating Take, Substitute, Subproblems etc.
  1368    ets : ets at the time of input
  1369    l   : the location (in scr) of the stac which generated the current formula
  1370 returns
  1371    Steps: pt,p (incl. ets) with m done
  1372           pos' list of proofobjs cut (from generate)
  1373           safe: implied from last proofobj
  1374 	  ets:
  1375    ///ToDo : ets contains a list of tacs to be done before m can be done
  1376           NOT IMPL. -- "error: do other step before"
  1377    NotLocatable: thus generate_hard
  1378 *)
  1379 (* val (Rewrite'(_,ro,er,pa,(id,str),f,_), p, Rfuns {locate_rule=lo,...},
  1380 	RrlsState (_,f'',rss,rts)) = (m, (p,p_), sc, is);
  1381    *)
  1382 fun locate_gen (thy',_) (Rewrite'(_,ro,er,pa,(id,str),f,_)) (pt,p) 
  1383 	       (Rfuns {locate_rule=lo,...}, d) (RrlsState (_,f'',rss,rts)) = 
  1384     (case lo rss f (Thm (id, mk_thm (assoc_thy thy') str)) of
  1385 	 [] => NotLocatable
  1386        | rts' => 
  1387 	 Steps (rts2steps [] ((pt,p),(f,f'',rss,rts),(thy',ro,er,pa)) rts'))
  1388 (* val p as(p',p_)=(p,p_);val scr as Script(h $ body)=sc;val (E,l,a,v,S,bb)=is;
  1389    locate_gen (thy':theory') (m:tac_) ((pt,p):ptree * pos') 
  1390 	      (scr,d) (E,l,a,v,S,bb);
  1391    9.6.03
  1392    val ts = (thy',srls);
  1393    val p = (p,p_);
  1394    val (scr as Script (h $ body)) = (sc);
  1395    val ScrState (E,l,a,v,S,b) = (is);
  1396 
  1397    val (ts as (thy',srls), m, (pt,p), 
  1398 	(scr as Script (h $ body),d), (ScrState (E,l,a,v,S,b))) = 
  1399        ((thy',srls), m,  (pt,(p,p_)), (sc,d), is);
  1400    locate_gen (thy',srls) m (pt,p) (Script(h $ body),d)(ScrState(E,l,a,v,S,b));
  1401 
  1402    val (ts as (thy',srls), m, (pt,p), 
  1403 	(scr as Script (h $ body),d), (ScrState (E,l,a,v,S,b))) = 
  1404        ((thy',srls), m',  (pt,(lev_on p,Frm)), (sc,d), is');
  1405 
  1406    val (ts as (thy',srls), m, (pt,p), 
  1407 	(scr as Script (h $ body),d), (ScrState (E,l,a,v,S,b))) = 
  1408        ((thy',srls), m',  (pt,(p, Res)), (sc,d), is');
  1409    *)
  1410   | locate_gen (ts as (thy',srls)) (m:tac_) ((pt,p):ptree * pos') 
  1411 	       (scr as Script (h $ body),d) (ScrState (E,l,a,v,S,b))  = 
  1412   let (*val _= writeln("### locate_gen-----------------: is=");
  1413       val _= writeln( istate2str (ScrState (E,l,a,v,S,b)));
  1414       val _= writeln("### locate_gen: l= "^loc_2str l^", p= "^pos'2str p)*)
  1415       val thy = assoc_thy thy';
  1416   in case if l=[] orelse ((*init.in solve..Apply_Method...*)
  1417 			  (last_elem o fst) p = 0 andalso snd p = Res)
  1418 	  then (assy ((ts,d),Aundef) ((E,[R],a,v,S,b),
  1419 				      [(m,EmptyMout,pt,p,[])]) body)
  1420 (* val Assoc (iss as (is as (_,_,_,_,_,bb), ss as ((m',f',pt',p',c')::_))) =
  1421        (astep_up (thy',srls,scr,d) ((E,l,a,v,S,b),[(m,EmptyMout,pt,p,[])]));
  1422        (assy ((ts,d),Aundef) ((E,[R],a,v,S,b),[(m,EmptyMout,pt,p,[])]) body);
  1423   *)
  1424 	  else (astep_up (thy',srls,scr,d) ((E,l,a,v,S,b),
  1425 					    [(m,EmptyMout,pt,p,[])]) ) of
  1426 	 Assoc (iss as (is as (_,_,_,_,_,bb), ss as ((m',f',pt',p',c')::_))) =>
  1427 	 ((*writeln("### locate_gen Assoc: p'="^(pos'2str p'));*)
  1428 	  if bb then Steps (ScrState is, ss)
  1429 	 else if rew_only ss (*andalso 'not bb'= associated weakly*)
  1430 	 then let (*val _=writeln("### locate_gen, bef g1: p="^(pos'2str p));*)
  1431 		  val (po,p_) = p;
  1432                   val po' = case p_ of Frm => po | Res => lev_on po
  1433 		  (*WN.12.03: noticed, that pos is also updated in assy !?!
  1434 		   instead take p' from Assoc ?????????????????????????????*)
  1435                   val (p'',c'',f'',pt'') = 
  1436 		      generate1 thy m (ScrState is) (po',p_) pt;
  1437 	      (*val _=writeln("### locate_gen, aft g1: p''="^(pos'2str p''));*)
  1438 	      (*drop the intermediate steps !*)
  1439 	      in Steps (ScrState is, [(m, f'',pt'',p'',c'')]) end
  1440 	 else Steps (ScrState is, ss))
  1441 	
  1442      | NasApp _ (*[((E,l,a,v,S,bb),(m',f',pt',p',c'))] => 
  1443 	   raise error ("locate_gen: should not have got NasApp, ets =")*)
  1444        => NotLocatable
  1445      | NasNap (_,_) =>
  1446        if l=[] then NotLocatable
  1447        else (*scan from begin of script for rew_only*)
  1448 	   (case assy ((ts,d),Aundef) ((E,[R],a,v,Unsafe,b),
  1449 					 [(m,EmptyMout,pt,p,[])]) body  of
  1450 		Assoc (iss as (is as (_,_,_,_,_,bb), 
  1451 			       ss as ((m',f',pt',p',c')::_))) =>
  1452 		    ((*writeln"4### locate_gen Assoc after Fini";*)
  1453 		     if rew_only ss
  1454 		     then let val(p'',c'',f'',pt'') = 
  1455 				 generate1 thy m (ScrState is) p' pt;
  1456 			  (*drop the intermediate steps !*)
  1457 			  in Steps (ScrState is, [(m, f'',pt'',p'',c'')]) end
  1458 		     else NotLocatable)
  1459 	      | _ => ((*writeln ("#### locate_gen: after Fini");*)
  1460 		      NotLocatable))
  1461   end
  1462   | locate_gen _ m _ (sc,_) is = 
  1463     raise error ("locate_gen: wrong arguments,\n tac= "^(tac_2str m)^
  1464 		 ",\n scr= "^(scr2str sc)^",\n istate= "^(istate2str is));
  1465 
  1466 
  1467 
  1468 (** find the next stactic in a script **)
  1469 
  1470 (*.handle a leaf;
  1471    a leaf is either a tactic or an 'exp' in 'let v = expr'
  1472    where 'exp' does not contain a tactic.*)
  1473 fun handle_leaf thy srls E a v t =
  1474     let val t' = subst_atomic (case a of Some a => upd_env E (a,v) 
  1475 				       | None => E) t
  1476 	(*was only for list-expr...*)
  1477 	val t'' = eval_listexpr_ (assoc_thy thy) srls
  1478 				(subst_atomic (upd_env_opt E (a,v)) t)
  1479 	val _= if (!trace_script) 
  1480 	       then (writeln("@@@ found '"^term2str t^"' and rewritten to '"^
  1481 			     term2str t');
  1482 		     writeln("@@@ t''= "^term2str t''))
  1483 	       else ()
  1484     in subst_stacexpr E a v t end;
  1485 
  1486 datatype appy =  (*ExprVal in the sense of denotational semantics*)
  1487     Appy of      (*applicable stac found, search stalled*)
  1488     tac_ *       (*tac_ associated (fun assod) with stac*)
  1489     scrstate     (*after determination of stac WN.18.8.03*)
  1490   | Napp of      (*stac found was not applicable; 
  1491 	           this mode may become Skip in Repeat, Try and Or*)
  1492     env (*stack*)  (*popped while nxt_up*)
  1493   | Skip of      (*for restart after Appy, for leaving iterations,
  1494 	           for passing the value of scriptexpressions,
  1495 		   and for finishing the script successfully*)
  1496     term * env (*stack*);
  1497 
  1498 (*appy, nxt_up, nstep_up scanning for next_tac.
  1499   search is clearly separated into (1)-(2):
  1500   (1) appy is recursive descent;
  1501   (2) nxt_up resumes interpretation at a location somewhere in the script;
  1502       nstep_up does only get to the parentnode of the scriptexpr.
  1503   consequence:
  1504   * call of (2) means _always_ that in this branch below
  1505     there was an appl.stac (Repeat, Or e1, ...)
  1506 *)
  1507 
  1508 
  1509 datatype appy_ = (*as argument in nxt_up, nstep_up, from appy*)
  1510        (*  Appy is only (final) returnvalue, not argument during search
  1511        |*) Napp_ (*ev. detects 'script is not appropriate for this example'*)
  1512        | Skip_;  (*detects 'script successfully finished'
  1513 		   also used as init-value for resuming; this works,
  1514 	           because 'nxt_up Or e1' treats as Appy*)
  1515 
  1516 fun appy thy ptp E l
  1517   (t as Const ("Let",_) $ e $ (Abs (i,T,b))) a v =
  1518 (* val (thy, ptp, E, l,        t as Const ("Let",_) $ e $ (Abs (i,T,b)),a, v)=
  1519        (thy, ptp, E, up@[R,D], body,                                    a, v);
  1520    *)
  1521   ((*writeln("### appy Let$e$Abs: is=");
  1522    writeln(istate2str (ScrState (E,l,a,v,Sundef,false)));*)
  1523    case appy thy ptp E (l@[L,R]) e a v of
  1524      Skip (res, E) => 
  1525        let (*val _= writeln("### appy Let "^(term2str t));
  1526 	 val _= writeln("### appy Let: Skip res ="^(term2str res));*)
  1527        (*val (i',b') = variant_abs (i,T,b); WN.15.5.03
  1528 	 val i = mk_Free(i',T);             WN.15.5.03 *)   
  1529 	 val E' = upd_env E (Free (i,T), res);
  1530        in appy thy ptp E' (l@[R,D]) b a v end
  1531    | ay => ay)
  1532 
  1533   | appy (thy as (th,sr)) ptp E l
  1534   (t as Const ("Script.While"(*1*),_) $ c $ e $ a) _ v = (*ohne n. 28.9.00*)
  1535   ((*writeln("### appy While $ c $ e $ a, upd_env= "^
  1536 	   (subst2str (upd_env E (a,v))));*)
  1537    if eval_true_ th sr (subst_atomic (upd_env E (a,v)) c)
  1538     then appy thy ptp E (l@[L,R]) e (Some a) v
  1539   else Skip (v, E))
  1540 
  1541   | appy (thy as (th,sr)) ptp E l
  1542   (t as Const ("Script.While"(*2*),_) $ c $ e) a v =(*ohne nachdenken 28.9.00*)
  1543   ((*writeln("### appy While $ c $ e, upd_env= "^
  1544 	   (subst2str (upd_env_opt E (a,v))));*)
  1545    if eval_true_ th sr (subst_atomic (upd_env_opt E (a,v)) c)
  1546     then appy thy ptp E (l@[R]) e a v
  1547   else Skip (v, E))
  1548 
  1549   | appy (thy as (th,sr)) ptp E l (t as Const ("If",_) $ c $ e1 $ e2) a v =
  1550     ((*writeln("### appy If: t= "^(term2str t));
  1551      writeln("### appy If: c= "^(term2str(subst_atomic(upd_env_opt E(a,v))c)));
  1552      writeln("### appy If: thy= "^(fst thy));*)
  1553      if eval_true_ th sr (subst_atomic (upd_env_opt E (a,v)) c)
  1554      then ((*writeln("### appy If: true");*)appy thy ptp E (l@[L,R]) e1 a v)
  1555      else ((*writeln("### appy If: false");*)appy thy ptp E (l@[  R]) e2 a v))
  1556 
  1557   | appy thy ptp E (*env*) l
  1558   (Const ("Script.Repeat"(*1*),_) $ e $ a) _ v = 
  1559     ((*writeln("### appy Repeat a: ");*)
  1560      appy thy ptp E (*env*) (l@[L,R]) e (Some a) v)
  1561 
  1562   | appy thy ptp E (*env*) l
  1563   (Const ("Script.Repeat"(*2*),_) $ e) a v = 
  1564     ((*writeln("3### appy Repeat: a= "^
  1565 	     (Sign.string_of_term (sign_of (assoc_thy thy)) a));*)
  1566      appy thy ptp E (*env*) (l@[R]) e a v)
  1567 
  1568   | appy thy ptp E l
  1569   (t as Const ("Script.Try",_) $ e $ a) _ v =
  1570   (case appy thy ptp E (l@[L,R]) e (Some a) v of
  1571      Napp E => ((*writeln("### appy Try "^
  1572 			  (Sign.string_of_term (sign_of (assoc_thy thy)) t));*)
  1573 		 Skip (v, E))
  1574    | ay => ay)
  1575 (* val (l,t as Const ("Script.Try",_) $ e) = (l@[L,R],e1);
  1576    appy thy ptp E l t a v;
  1577    *)
  1578   | appy thy ptp E l
  1579   (t as Const ("Script.Try",_) $ e) a v =
  1580   (case appy thy ptp E (l@[R]) e a v of
  1581      Napp E => ((*writeln("### appy Try "^
  1582 			  (Sign.string_of_term (sign_of (assoc_thy thy)) t));*)
  1583 		 Skip (v, E))
  1584    | ay => ay)
  1585 
  1586 
  1587   | appy thy ptp E l
  1588 	 (Const ("Script.Or"(*1*),_) $e1 $ e2 $ a) _ v =
  1589     (case appy thy ptp E (l@[L,L,R]) e1 (Some a) v of
  1590 	 Appy lme => Appy lme
  1591        | _ => appy thy ptp E (*env*) (l@[L,R]) e2 (Some a) v)
  1592     
  1593   | appy thy ptp E l
  1594 	 (Const ("Script.Or"(*2*),_) $e1 $ e2) a v =
  1595     (case appy thy ptp E (l@[L,R]) e1 a v of
  1596 	 Appy lme => Appy lme
  1597        | _ => appy thy ptp E (l@[R]) e2 a v)
  1598     
  1599 
  1600   | appy thy ptp E l
  1601 	 (Const ("Script.Seq"(*1*),_) $e1 $ e2 $ a) _ v =
  1602     ((*writeln("### appy Seq $ e1 $ e2 $ a, upd_env= "^
  1603 	     (subst2str (upd_env E (a,v))));*)
  1604      case appy thy ptp E (l@[L,L,R]) e1 (Some a) v of
  1605 	 Skip (v,E) => appy thy ptp E (l@[L,R]) e2 (Some a) v
  1606        | ay => ay)
  1607 (* val (l,t as Const ("Script.Seq",_) $e1 $ e2) = (up@[R],e2);
  1608    appy thy ptp E l t a v;
  1609    *)    
  1610   | appy thy ptp E l
  1611 	 (Const ("Script.Seq",_) $e1 $ e2) a v =
  1612     (case appy thy ptp E (l@[L,R]) e1 a v of
  1613 	 Skip (v,E) => appy thy ptp E (l@[R]) e2 a v
  1614        | ay => ay)
  1615 
  1616   (*.a leaf has been found*)   
  1617   | appy (thy as (th,sr)) (pt, p) E l t a v =
  1618 (*
  1619 val (thy as (th,sr),(pt, p),E, l,        t,    a, v) = 
  1620     (thy,            ptp,   E, up@[R,D], body, a, v);
  1621 val (thy as (th,sr),(pt, p),E, l,       t, a, v) = 
  1622     (thy,            ptp,   E, l@[L,R], e, a, v);
  1623    *)
  1624     ((*case subst_stacexpr E a v t of*)
  1625      case handle_leaf th sr E a v t of
  1626 (* val Expr s = subst_stacexpr E a v t;
  1627    *)
  1628 	Expr s => (writeln("### appy, listexpr= "^(term2str t));
  1629           (*writeln("### appy, E= "^(env2str E));*)
  1630 	  writeln("### appy, eval(..)= "^(term2str
  1631 	       (eval_listexpr_ (assoc_thy th) sr
  1632 			       (subst_atomic (upd_env_opt E (a,v)) t)) ));(**)
  1633 	  Skip (eval_listexpr_ (assoc_thy th) sr
  1634 			       (subst_atomic (upd_env_opt E (a,v)) t), E) )
  1635 (* val STac stac = subst_stacexpr E a v t;
  1636    *)
  1637      | STac stac =>
  1638 	let
  1639 	 val _= writeln("### appy t, stac= "^(term2str stac))
  1640 (*--->>*)
  1641          (*val _= writeln("### appy t, vor  stac2tac_ is="); 
  1642            val _= writeln(istate2str (ScrState (E,l,a,v,Sundef,false)));*)
  1643 	   val (m,m') = stac2tac_ pt (assoc_thy th) stac;
  1644        (*val _= writeln("### appy t, nach stac2tac, m= "^(tac2str m));*)
  1645        in case m of 
  1646 	      Subproblem _ => Appy (m', (E,l,a,tac_2res m',Sundef,false))
  1647 	    | _ => (case applicable_in p pt m of
  1648 (* val Appl m' = applicable_in p pt m;
  1649    *)
  1650 			Appl m' => 
  1651 			((*writeln("### appy: Appy");*)
  1652 			 Appy (m', (E,l,a,tac_2res m',Sundef,false)))
  1653 		      | _ => ((*writeln("### appy: Napp");*)Napp E)) 
  1654 	end);
  1655 	 
  1656 
  1657 (* val (scr as Script sc, l, t as Const ("Let",_) $ _) =
  1658        (Script sc, up, go up sc);
  1659    nxt_up thy ptp (Script sc) E l ay t a v;
  1660 val (thy,ptp,scr as (Script sc),E,l, ay, t as Const ("Let",_) $ _, a, v)=
  1661     (thy,ptp,Script sc,         E,up,ay, go up sc,                 a, v);
  1662    *)
  1663 fun nxt_up thy ptp (scr as (Script sc)) E l ay
  1664     (t as Const ("Let",_) $ _) a v = (*comes from let=...*)
  1665 (* val Const ("Let",_) $ _ = (go up sc);
  1666    *)
  1667     ((*writeln("### nxt_up1 Let$e: is=");
  1668      writeln(istate2str (ScrState (E,l,a,v,Sundef,false)));*)
  1669      if ay = Napp_
  1670     then nstep_up thy ptp scr E (drop_last l) Napp_ a v
  1671     else (*Skip_*)
  1672 	let val up = drop_last l;
  1673 	    val (Const ("Let",_) $ e $ (Abs (i,T,body))) = go up sc;
  1674             val i = mk_Free (i, T);
  1675             val E = upd_env E (i, v);
  1676           (*val _= writeln("### nxt_up2 Let$e: is=");
  1677             val _= writeln(istate2str (ScrState (E,l,a,v,Sundef,false)));*)
  1678 	in case appy thy ptp (E) (up@[R,D]) body a v  of
  1679 	       Appy lre => Appy lre
  1680 	     | Napp E => nstep_up thy ptp scr E up Napp_ a v
  1681 	     | Skip (v,E) => nstep_up thy ptp scr E up Skip_ a v end)
  1682 	    
  1683   | nxt_up thy ptp scr E l ay
  1684     (t as Abs (_,_,_)) a v = 
  1685     ((*writeln("### nxt_up Abs: "^
  1686 	     (Sign.string_of_term (sign_of (assoc_thy thy)) t));*)
  1687      nstep_up thy ptp scr E (*enr*) l ay a v)
  1688 
  1689   | nxt_up thy ptp scr E l ay
  1690     (t as Const ("Let",_) $ e $ (Abs (i,T,b))) a v =
  1691     ((*writeln("### nxt_up Let$e$Abs: is=");
  1692      writeln(istate2str (ScrState (E,l,a,v,Sundef,false)));*)
  1693      (*writeln("### nxt_up Let e Abs: "^
  1694 	     (Sign.string_of_term (sign_of (assoc_thy thy)) t));*)
  1695      nstep_up thy ptp scr (*upd_env*) E (*a,v)*) 
  1696 	      (*eno,upd_env env (iar,res),iar,res,saf*) l ay a v)
  1697 
  1698   (*no appy_: never causes Napp -> Helpless*)
  1699   | nxt_up (thy as (th,sr)) ptp scr E l _ 
  1700   (Const ("Script.While"(*1*),_) $ c $ e $ _) a v = 
  1701   if eval_true_ th sr (subst_atomic (upd_env_opt E (a,v)) c) 
  1702     then case appy thy ptp E (l@[L,R]) e a v of
  1703 	     Appy lr => Appy lr
  1704 	   | Napp E => nstep_up thy ptp scr E l Skip_ a v
  1705 	   | Skip (v,E) => nstep_up thy ptp scr E l Skip_ a v
  1706   else nstep_up thy ptp scr E l Skip_ a v
  1707 
  1708   (*no appy_: never causes Napp - Helpless*)
  1709   | nxt_up (thy as (th,sr)) ptp scr E l _ 
  1710   (Const ("Script.While"(*2*),_) $ c $ e) a v = 
  1711   if eval_true_ th sr (subst_atomic (upd_env_opt E (a,v)) c) 
  1712     then case appy thy ptp E (l@[R]) e a v of
  1713 	     Appy lr => Appy lr
  1714 	   | Napp E => nstep_up thy ptp scr E l Skip_ a v
  1715 	   | Skip (v,E) => nstep_up thy ptp scr E l Skip_ a v
  1716   else nstep_up thy ptp scr E l Skip_ a v
  1717 
  1718 (* val (scr, l) = (Script sc, up);
  1719    *)
  1720   | nxt_up thy ptp scr E l ay (Const ("If",_) $ _ $ _ $ _) a v = 
  1721     nstep_up thy ptp scr E l ay a v
  1722 
  1723   | nxt_up thy ptp scr E l _ (*no appy_: there was already a stac below*)
  1724   (Const ("Script.Repeat"(*1*),T) $ e $ _) a v =
  1725     (case appy thy ptp (*upd_env*) E (*a,v)*) ((l@[L,R]):loc_) e a v  of
  1726       Appy lr => Appy lr
  1727     | Napp E => ((*writeln("### nxt_up Repeat a: ");*)
  1728 		 nstep_up thy ptp scr E l Skip_ a v)
  1729     | Skip (v,E) => ((*writeln("### nxt_up Repeat: Skip res ="^
  1730 		(Sign.string_of_term(sign_of (assoc_thy thy)) res'));*)
  1731 		    nstep_up thy ptp scr E l Skip_ a v))
  1732 
  1733   | nxt_up thy ptp scr E l _ (*no appy_: there was already a stac below*)
  1734   (Const ("Script.Repeat"(*2*),T) $ e) a v =
  1735     (case appy thy ptp (*upd_env*) E (*a,v)*) ((l@[R]):loc_) e a v  of
  1736       Appy lr => Appy lr
  1737     | Napp E => ((*writeln("### nxt_up Repeat a: ");*)
  1738 		 nstep_up thy ptp scr E l Skip_ a v)
  1739     | Skip (v,E) => ((*writeln("### nxt_up Repeat: Skip res ="^
  1740 		(Sign.string_of_term(sign_of (assoc_thy thy)) res'));*)
  1741 		    nstep_up thy ptp scr E l Skip_ a v))
  1742 
  1743 (* val (scr,l,t) = (Script sc,up,go up sc);
  1744    nxt_up thy ptp scr E l ay t a v;
  1745    *)
  1746   | nxt_up thy ptp scr E l _ (*makes Napp to Skip*)
  1747   (t as Const ("Script.Try",_) $ e $ _) a v = 
  1748     ((*writeln("### nxt_up Try "^
  1749 	     (Sign.string_of_term (sign_of (assoc_thy thy)) t));*)
  1750      nstep_up thy ptp scr E l Skip_ a v )
  1751 
  1752   | nxt_up thy ptp scr E l _ (*makes Napp to Skip*)
  1753   (t as Const ("Script.Try"(*2*),_) $ e) a v = 
  1754     ((*writeln("### nxt_up Try "^
  1755 	     (Sign.string_of_term (sign_of (assoc_thy thy)) t));*)
  1756      nstep_up thy ptp scr (*upd_env*) E (*a,v)*) l Skip_ a v)
  1757 
  1758 
  1759   | nxt_up thy ptp scr E l ay
  1760   (Const ("Script.Or",_) $ _ $ _ $ _) a v = nstep_up thy ptp scr E l ay a v
  1761 
  1762   | nxt_up thy ptp scr E l ay
  1763   (Const ("Script.Or",_) $ _ $ _) a v = nstep_up thy ptp scr E l ay a v
  1764 
  1765   | nxt_up thy ptp scr E l ay
  1766   (Const ("Script.Or",_) $ _ ) a v = 
  1767     nstep_up thy ptp scr E (drop_last l) ay a v
  1768 
  1769 
  1770   | nxt_up thy ptp scr E l ay (*all has been done in (*2*) below*)
  1771   (Const ("Script.Seq"(*1*),_) $ _ $ _ $ _) a v =
  1772     nstep_up thy ptp scr E l ay a v
  1773 
  1774   | nxt_up thy ptp scr E l ay (*comes from e2*)
  1775 	   (Const ("Script.Seq"(*2*),_) $ _ $ e2) a v =
  1776     nstep_up thy ptp scr E l ay a v
  1777 (* val (scr as Script sc,l,t) = (Script sc,up,go up sc);
  1778    !! Const ("Script.Seq",_ $ _ 
  1779    nxt_up thy ptp scr E l ay t a v;
  1780    *)
  1781   | nxt_up thy ptp (scr as Script sc) E l ay (*comes from e1*)
  1782 	   (Const ("Script.Seq",_) $ _ ) a v = 
  1783     if ay = Napp_
  1784     then nstep_up thy ptp scr E (drop_last l) Napp_ a v
  1785     else (*Skip_*)
  1786 	let val up = drop_last l;
  1787 	    val Const ("Script.Seq"(*2*),_) $ _ $ e2 = go up sc;
  1788 	in case appy thy ptp E (up@[R]) e2 a v  of
  1789 	    Appy lr => Appy lr
  1790 	  | Napp E => nstep_up thy ptp scr E up Napp_ a v
  1791 	  | Skip (v,E) => nstep_up thy ptp scr E up Skip_ a v end
  1792 
  1793   | nxt_up (thy,_) ptp scr E l ay t a v =
  1794   raise error ("nxt_up not impl for "^
  1795 	       (Sign.string_of_term (sign_of (assoc_thy thy)) t))
  1796 
  1797 (* val (thy, ptp, (Script sc), E, l, ay,    a, v)=
  1798        (thy, ptp, sc,          E, l, Skip_, a, v);
  1799    *)
  1800 and nstep_up thy ptp (Script sc) E l ay a v = 
  1801   ((*writeln("### nstep_up from: "^(loc_2str l));
  1802    writeln("### nstep_up from: "^
  1803 	   (Sign.string_of_term (sign_of (assoc_thy thy)) (go l sc)));*)
  1804    if 1 < length l 
  1805    then 
  1806        let 
  1807 	   val up = drop_last l; 
  1808        in ((*writeln("### nstep_up to: "^
  1809 	      (Sign.string_of_term (sign_of (assoc_thy thy)) (go up sc)));*)
  1810 	   nxt_up thy ptp (Script sc) E up ay (go up sc) a v ) end
  1811    else (*interpreted to end*)
  1812        if ay = Skip_ then Skip (v, E) else Napp E 
  1813 );
  1814 
  1815 (* decide for the next applicable stac in the script;
  1816    returns (stactic, value) - the value in case the script is finished 
  1817    12.8.02:         ~~~~~ and no assumptions ??? FIXME ???
  1818    20.8.02: must return p in case of finished, because the next script
  1819             consulted need not be the calling script:
  1820             in case of detail ie. _inserted_ PrfObjs, the next stac
  1821             has to searched in a script with PblObj.status<>Complete !
  1822             (.. not true for other details ..PrfObj ??????????????????
  1823    20.8.02: do NOT return safe (is only changed in locate !!!)
  1824 *)
  1825 (* val (thy, (pt,p), Rfuns {next_rule=ne,...}, RrlsState (f,f',rss,_)) = 
  1826        (thy', (pt,p), sc, RrlsState (ii t));
  1827    val (thy, (pt,p), Rfuns {next_rule=ne,...}, RrlsState (f,f',rss,_)) = 
  1828        (thy', (pt',p'), sc, is');
  1829    *)
  1830 fun next_tac (thy,_) (pt,p) (Rfuns {next_rule,...}) (RrlsState(f,f',rss,_))=
  1831     if f = f' then (End_Detail' (f',[])(*8.6.03*), Uistate, 
  1832 		    (f', Sundef(*FIXME is no value of next_tac! vor 8.6.03*)))
  1833                                                           (*finished*)
  1834     else (case next_rule rss f of
  1835 	      None => (Empty_Tac_, Uistate, (e_term, Sundef)) 	  (*helpless*)
  1836 (* val Some (Thm (id,thm)) = next_rule rss f;
  1837    *)
  1838 	    | Some (Thm (id,thm))(*8.6.03: muss auch f' liefern ?!!*) => 
  1839 	      (Rewrite' (thy, "e_rew_ord", e_rls,(*!?!8.6.03*) false,
  1840 			 (id, string_of_thm' thm), f,(e_term,[(*!?!8.6.03*)])),
  1841 	       Uistate, (e_term, Sundef)))                 (*next stac*)
  1842 
  1843 (* 
  1844    val(thy, ptp as (pt,(p,_)), sc as Script (h $ body),ScrState (E,l,a,v,s,b))=
  1845       ((thy',srls), (pt,pos),  sc,                     is);
  1846  *)
  1847   | next_tac thy (ptp as (pt,(p,_)):ptree * pos') (sc as Script (h $ body)) 
  1848 	     (ScrState (E,l,a,v,s,b)) =
  1849   ((*writeln("### next_tac-----------------: E= ");
  1850    writeln( istate2str (ScrState (E,l,a,v,s,b)));*)
  1851    case if l=[] then appy thy ptp E [R] body None e_term
  1852        else nstep_up thy ptp sc E l Skip_ a v of
  1853       Skip (v,_) =>                                              (*finished*)
  1854       (case par_pbl_det pt p of
  1855 	   (true, p', _) => 
  1856 	   let val (_,pblID,_) = get_obj g_spec pt p';
  1857 	   in (Check_Postcond' (pblID, (v, [(*8.6.03 NO asms???*)])), 
  1858 	       e_istate, (v,s)) end
  1859 	 | (_,p',rls') => (End_Detail' (e_term,[])(*8.6.03*), e_istate, (v,s)))
  1860     | Napp _ => (Empty_Tac_, e_istate, (e_term, Sundef))         (*helpless*)
  1861     | Appy (m', scrst as (_,_,_,v,_,_)) => (m', ScrState scrst,
  1862 			   (v, Sundef)))                         (*next stac*)
  1863 
  1864   | next_tac _ _ _ is = raise error ("next_tac: not impl for "^
  1865 				     (istate2str is));
  1866 
  1867 
  1868 
  1869 
  1870 (*.create the initial interpreter state from the items of the guard.*)
  1871 (* val (thy, itms, metID) = (thy, itms, mI);
  1872    *)
  1873 fun init_scrstate thy itms metID =
  1874     let val actuals = itms2args thy metID itms;
  1875 	val scr as Script sc = (#scr o get_met) metID;
  1876         val formals = formal_args sc
  1877 	(*expects same sequence of (actual) args in itms 
  1878           and (formal) args in met*)
  1879 	fun relate_args env [] [] = env
  1880 	  | relate_args env _ [] = 
  1881 	    raise error ("ERROR in creating the environment for '"
  1882 			 ^id_of_scr sc^"' from \nthe items of the guard of "
  1883 			 ^metID2str metID^",\n\
  1884 			 \formal arg(s) miss actual arg(s):\n"
  1885 			 ^(string_of_int o length) formals
  1886 			 ^" formals: "^terms2str formals^"\n"
  1887 			 ^(string_of_int o length) actuals
  1888 			 ^" actuals: "^terms2str actuals)
  1889 	  | relate_args env [] actual_finds = env (*may drop Find!*)
  1890 	  | relate_args env (a::aa) (f::ff) = 
  1891 	    if type_of a = type_of f 
  1892 	    then relate_args (env @ [(a, f)]) aa ff else 
  1893 	    raise error ("ERROR in creating the environment for '"
  1894 			 ^id_of_scr sc^"' from \nthe items of the guard of "
  1895 			 ^metID2str metID^",\n\			 
  1896 			 \different types of formal arg and actual arg:'\n\
  1897 			 \formal: '"^term2str a^"::"^(type2str o type_of) a^"'\n\
  1898 			 \actual: '"^term2str f^"::"^(type2str o type_of) f^"'\n\
  1899 			 \in\n\
  1900 			 \formals: "^terms2str formals^"\n\
  1901 			 \actuals: "^terms2str actuals)
  1902         val env = relate_args [] formals actuals;
  1903     in (ScrState (env,[],None,e_term,Safe,true), scr):istate * scr end;
  1904 
  1905 (*.decide, where to get script/istate from:
  1906    (*1*) from PblObj.env: at begin of script if no init_form
  1907    (*2*) from PblObj/PrfObj: if stac is in the middle of the script
  1908    (*3*) from rls/PrfObj: in case of detail a ruleset.*)
  1909 fun from_pblobj_or_detail' thy' (p,p_) pt =
  1910     if p_ mem [Pbl,Met]
  1911     then case get_obj g_env pt p of
  1912 	     None => raise error "from_pblobj_or_detail': no istate"
  1913 	   | Some is =>
  1914 	     let val metID = get_obj g_metID pt p
  1915 		 val {srls,...} = get_met metID
  1916 	     in (srls, is, (#scr o get_met) metID) end
  1917     else
  1918     let val (pbl,p',rls') = par_pbl_det pt p
  1919     in if pbl 
  1920        then (*2*)
  1921 	   let val thy = assoc_thy thy'
  1922 	       val PblObj{meth=itms,...} = get_obj I pt p'
  1923 	       val metID = get_obj g_metID pt p'
  1924 	       val {srls,...} = get_met metID
  1925 	   in (*if last_elem p = 0 (*nothing written to pt yet*)
  1926 	      then let val (is, sc) = init_scrstate thy itms metID
  1927 		   in (srls, is, sc) end
  1928 	      else*) (srls, get_istate pt (p,p_), (#scr o get_met) metID)
  1929 	   end
  1930        else (*3*)
  1931 	   (e_rls, (*FIXME: get from pbl or met !!!
  1932 		    unused for Rrls in locate_gen, next_tac*)
  1933 	    get_istate pt (p,p_),
  1934 	    case rls' of
  1935 		Rls {scr=scr,...} => scr
  1936 	      | Rrls {scr=rfuns,...} => rfuns)
  1937     end;
  1938 
  1939 (*.get script and istate from PblObj, see (*1*) above.*)
  1940 fun from_pblobj' thy' (p,p_) pt = 
  1941     let val p' = par_pblobj pt p
  1942 	val thy = assoc_thy thy'
  1943 	val PblObj{meth=itms,...} = get_obj I pt p'
  1944 	val metID = get_obj g_metID pt p'
  1945 	val {srls,scr,...} = get_met metID
  1946     in if last_elem p = 0 (*nothing written to pt yet*)
  1947        then let val (is, scr) = init_scrstate thy itms metID
  1948 	    in (srls, is, scr) end
  1949        else (srls, get_istate pt (p,p_), scr)
  1950     end;
  1951     
  1952 (*
  1953 end
  1954 open Interpreter;
  1955 *)
  1956 
  1957 (* use"ME/script.sml";
  1958    use"script.sml";
  1959    *)