test/Tools/isac/Interpret/script.sml
author Walther Neuper <neuper@ist.tugraz.at>
Thu, 11 Jul 2013 16:58:31 +0200
changeset 48895 35751d90365e
parent 48790 98df8f6dc3f9
child 52101 c3f399ce32af
permissions -rw-r--r--
end of improving tests for isac on Isabelle2012

improvements:
# reactivated tests for error patterns, fill patterns
# reasons for outcommented test are given as much as possible,
see subsubsection {* State of tests *} in Test_Isac.thy
# detailed "Plans for updating isac from Isabelle2011 to Isabelle2012 and Isabelle2013"
in Build_Thydata.thy

remaining deficiencies:
# Counting "error in kernel" for Frontend/interface.sml (the tests considered most significant)
yields 69 hits, some of which were already present before Isabelle2002-->2009-2
# many tests are still outcommented; reactivation would require comparison
with isac on Isabelle2002 on an old notebook in many cases.
     1 (* Title:  test/../script.sml
     2    Author: Walther Neuper 050908
     3    (c) copyright due to lincense terms.
     4 *)
     5 "-----------------------------------------------------------------";
     6 "table of contents -----------------------------------------------";
     7 "-----------------------------------------------------------------";
     8 "----------- WN0509 why does next_tac doesnt find Substitute -----";
     9 "----------- WN0509 Substitute 2nd part --------------------------";
    10 "----------- fun sel_appl_atomic_tacs ----------------------------";
    11 "----------- fun init_form, fun get_stac -------------------------";
    12 "----------- x+1=2 start SubProblem 'stac2tac_ TODO: no match for ";
    13 "----------- Take as 1st stac in script --------------------------";
    14 "----------- 'trace_script' from outside 'fun me '----------------";
    15 "----------- fun sel_rules ---------------------------------------";
    16 "----------- fun sel_appl_atomic_tacs ----------------------------";
    17 "-----------------------------------------------------------------";
    18 "-----------------------------------------------------------------";
    19 "-----------------------------------------------------------------";
    20 
    21 val thy =  @{theory Isac};
    22 
    23 "----------- WN0509 why does next_tac doesnt find Substitute -----";
    24 "----------- WN0509 why does next_tac doesnt find Substitute -----";
    25 "----------- WN0509 why does next_tac doesnt find Substitute -----";
    26 
    27 (*replace met 'IntegrierenUndKonstanteBestimmen' with this script...*)
    28 val str = (*#1#*)
    29 "Script BiegelinieScript                                             " ^ 
    30 "(l_l::real) (q__q::real) (v_v::real) (b_b::real=>real)              " ^ 
    31 "(rb_rb::bool list) (rm_rm::bool list) =                             " ^
    32 "  (let q___q = Take (M_b v_v = q__q);                               " ^
    33 "       (M1__M1::bool) = ((Substitute [v_v = 0])) q___q              " ^
    34 " in True)";
    35 
    36 val sc' = ((inst_abs thy) o term_of o the o (parse thy)) str;
    37 
    38 val str = (*#2#*)
    39 "Script BiegelinieScript                                             " ^ 
    40 "(l_l::real) (q__q::real) (v_v::real) (b_b::real=>real)              " ^ 
    41 "(rb_rb::bool list) (rm_rm::bool list) =                             " ^ 
    42 "       (M1__M1::bool) = ((Substitute [v_v = 0]) @@                  " ^
    43 " in True)";(*..doesnt find Substitute with ..@@ !!!!!!!!!!!!!!!!!!!!!*)
    44 
    45 val str = (*#3#*)
    46 "Script BiegelinieScript                                             " ^
    47 "(l_l::real) (q__q::real) (v_v::real) (b_b::real=>real)              " ^
    48 "(rb_rb::bool list) (rm_rm::bool list) =                             " ^
    49 "  (let q___q = Take (q_q v_v = q__q);                               " ^
    50 "      (M1__M1::bool) = Substitute [v_v = 0]      q___q ;            " ^
    51 "       M1__m1 =        Substitute [M_b 0 = 0]  M1__M1               " ^
    52 " in True)"
    53 ;
    54 val str = (*#4#*)
    55 "Script BiegelinieScript                                             " ^
    56 "(l_l::real) (q__q::real) (v_v::real) (b_b::real=>real)              " ^
    57 "(rb_rb::bool list) (rm_rm::bool list) =                             " ^
    58 "  (let q___q = Take (q_q v_v = q__q);                               " ^
    59 "      (M1__M1::bool) = Substitute [v_v = 0]      q___q ;            " ^
    60 "       M1__M1 =        Substitute [v_v = 1]      q___q ;            " ^
    61 "       M1__M1 =        Substitute [v_v = 2]      q___q ;            " ^
    62 "       M1__M1 =        Substitute [v_v = 3]      q___q ;            " ^
    63 "       M1__M1 =        Substitute [M_b 0 = 0]  M1__M1               " ^
    64 " in True)"
    65 ;
    66 val str = (*#5#*)
    67 "Script BiegelinieScript                                             " ^
    68 "(l_l::real) (q__q::real) (v_v::real) (b_b::real=>real)              " ^
    69 "(rb_rb::bool list) (rm_rm::bool list) =                             " ^
    70 "  (let q___q = Take (M_b v_v = q__q);                               " ^
    71 "      (M1__M1::bool) = Substitute [v_v = 0]      q___q ;            " ^
    72 "       M2__M2 = Take q___q ;                                        " ^
    73 "       M2__M2 =        Substitute [v_v = 2]      q___q              " ^
    74 " in True)"
    75 ;
    76 
    77 val sc' = ((inst_abs thy) o term_of o the o (parse thy)) str;
    78 atomty sc';
    79 
    80 val {scr = Prog sc,...} = get_met ["IntegrierenUndKonstanteBestimmen"];
    81 (*---------------------------------------------------------------------
    82 if sc = sc' then () else error"script.sml, doesnt find Substitute #1";
    83 ---------------------------------------------------------------------*)
    84 
    85 "----------- WN0509 Substitute 2nd part --------------------------";
    86 "----------- WN0509 Substitute 2nd part --------------------------";
    87 "----------- WN0509 Substitute 2nd part --------------------------";
    88 (*replace met 'IntegrierenUndKonstanteBestimmen' with this script...*)
    89 val str = (*Substitute ; Substitute works*)
    90 "Script BiegelinieScript                                             " ^
    91 "(l_l::real) (q__q::real) (v_v::real) (b_b::real=>real)              " ^
    92 "(rb_rb::bool list) (rm_rm::bool list) =                             "^
    93 (*begin after the 2nd integrate*)
    94 "  (let M__M = Take (M_b v_v = q__q);                                " ^
    95 "       e1__e1 = nth_nth 1 rm_rm ;                                   " ^
    96 "       (x1__x1::real) = argument_in (lhs e1__e1);                   " ^
    97 "       (M1__M1::bool) = Substitute [v_v = x1__x1] M__M;             " ^
    98 "        M1__M1        = Substitute [e1__e1] M1__M1                  " ^
    99 " in True)"
   100 ;
   101 val sc' = ((inst_abs thy) o term_of o the o (parse thy)) str;
   102 atomty sc';
   103 
   104 val str = (*Substitute @@ Substitute does NOT work???*)
   105 "Script BiegelinieScript                                             " ^
   106 "(l_l::real) (q__q::real) (v_v::real) (b_b::real=>real)              " ^
   107 "(rb_rb::bool list) (rm_rm::bool list) =                             "^
   108 (*begin after the 2nd integrate*)
   109 "  (let M__M = Take (M_b v_v = q__q);                                " ^
   110 "       e1__e1 = nth_nth 1 rm_rm ;                                   " ^
   111 "       (x1__x1::real) = argument_in (lhs e1__e1);                   " ^
   112 "       (M1__M1::bool) = ((Substitute [v_v = x1__x1]) @@             " ^
   113 "                       (Substitute [e1__e1]))        M__M           " ^
   114 " in True)"
   115 ;
   116 
   117 val {scr = Prog sc,...} = get_met ["IntegrierenUndKonstanteBestimmen"];
   118 (*---------------------------------------------------------------------
   119 if sc = sc' then () else error "script.sml, doesnt find Substitute #1";
   120 ---------------------------------------------------------------------*)
   121 val fmz = ["Traegerlaenge L",
   122 	   "Streckenlast (- q_0 * x^^^2 / 2 + x * c + c_2)",
   123 	   "Biegelinie y",
   124 	   "RandbedingungenBiegung [y 0 = 0, y L = 0]",
   125 	   "RandbedingungenMoment [M_b 0 = 0, M_b L = 0]",
   126 	   "FunktionsVariable x"];
   127 val (dI',pI',mI') =
   128   ("Biegelinie",["MomentBestimmte","Biegelinien"],
   129    ["IntegrierenUndKonstanteBestimmen"]);
   130 val p = e_pos'; val c = [];
   131 val (p,_,f,nxt,_,pt) = CalcTreeTEST [(fmz, (dI',pI',mI'))];
   132 val (p,_,f,nxt,_,pt) = me nxt p c pt; val (p,_,f,nxt,_,pt) = me nxt p c pt;
   133 val (p,_,f,nxt,_,pt) = me nxt p c pt; val (p,_,f,nxt,_,pt) = me nxt p c pt;
   134 val (p,_,f,nxt,_,pt) = me nxt p c pt; val (p,_,f,nxt,_,pt) = me nxt p c pt;
   135 val (p,_,f,nxt,_,pt) = me nxt p c pt; val (p,_,f,nxt,_,pt) = me nxt p c pt;
   136 val (p,_,f,nxt,_,pt) = me nxt p c pt; val (p,_,f,nxt,_,pt) = me nxt p c pt;
   137 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   138 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   139 case nxt of (_, Apply_Method ["IntegrierenUndKonstanteBestimmen"]) => ()
   140 	  | _ => error "script.sml, doesnt find Substitute #2";
   141 (* ERROR: caused by f2str f *)
   142 trace_rewrite:=true;
   143 
   144 val (p,_,f,nxt,_,pt) = me nxt p c pt; f2str f(*------------------------*);
   145 trace_rewrite:=false;
   146   (*Exception TYPE raised:
   147     Illegal type for constant "HOL.eq" :: "[real, bool] => bool"
   148     Atools.argument'_in (Tools.lhs (ListG.nth_ (1 + -1 + -1) [])) =
   149     ListG.nth_ (1 + -1 + -1) []
   150     Exception-
   151        TYPE
   152           ("Illegal type for constant \"op =\" :: \"[real, bool] => bool\"",
   153              [],
   154              [Const ("HOL.Trueprop", "bool => prop") $
   155                    (Const ("HOL.eq", "[RealDef.real, bool] => bool") $ ... $ ...)])
   156        raised
   157     ... this was because eval_argument_in took "argument_in (lhs (M_b 0 = 0))"
   158     ie. the argument had not been simplified before          ^^^^^^^^^^^^^^^
   159     thus corrected eval_argument_in OK*)
   160 val {srls,...} = get_met ["IntegrierenUndKonstanteBestimmen"];
   161 val e1__e1 = str2term "NTH 1 [M_b 0 = 0, M_b L = 0]";
   162 val e1__e1 = eval_listexpr_ @{theory Biegelinie} srls e1__e1; term2str e1__e1;
   163 if term2str e1__e1 = "M_b 0 = 0"
   164   then ()
   165   else error"script.sml diff.beh. eval_listexpr_ nth_nth 1 [...";
   166 
   167 (*TODO.WN050913 ??? doesnt eval_listexpr_ go into subterms ???...
   168  val x1__ = str2term"argument_in (lhs (M_b 0 = 0))";
   169  val x1__ = eval_listexpr_ Biegelinie.thy srls x1__; term2str x1__;
   170  (*no rewrite*)
   171  calculate_ Biegelinie.thy ("Tools.lhs", eval_rhs"eval_lhs_") x1__;
   172  val SOME (str, t) = eval_lhs 0 "Tools.lhs" (str2term"lhs (M_b 0 = 0)") 0;*)
   173 
   174 val l__l = str2term "lhs (M_b 0 = 0)";
   175 val l__l = eval_listexpr_ @{theory Biegelinie} srls l__l; term2str l__l;
   176 val SOME (str, t) = eval_lhs 0 "Tools.lhs" (str2term "lhs (M_b 0 = 0)") 0;
   177 
   178 val (p,_,f,nxt,_,pt) = me nxt p c pt; f2str f (*------------------------*);
   179 if nxt = ("Rewrite", Rewrite ("Belastung_Querkraft", "Biegelinie.Belastung_Querkraft"))
   180 then () else error "";
   181 
   182 
   183 "----------- fun sel_appl_atomic_tacs ----------------------------";
   184 "----------- fun sel_appl_atomic_tacs ----------------------------";
   185 "----------- fun sel_appl_atomic_tacs ----------------------------";
   186 
   187 states:=[];
   188 CalcTree [(["equality (x+1=(2::real))", "solveFor x","solutions L"], 
   189   ("Test", ["sqroot-test","univariate","equation","test"],
   190    ["Test","squ-equ-test-subpbl1"]))];
   191 Iterator 1;
   192 moveActiveRoot 1;
   193 autoCalculate 1 CompleteCalcHead;
   194 autoCalculate 1 (Step 1);
   195 autoCalculate 1 (Step 1);
   196 val ((pt, p), _) = get_calc 1; show_pt pt;
   197 val appltacs = sel_appl_atomic_tacs pt p;
   198 if appltacs = 
   199 (* WN130613
   200    [Rewrite ("radd_commute", "Test.radd_commute") (*"?m + ?n = ?n + ?m"*),
   201     Rewrite ("radd_assoc", "?m + ?n + ?k = ?m + (?n + ?k)"), Calculate "TIMES"] *)
   202    [Rewrite ("radd_commute", "Test.radd_commute"), 
   203     Rewrite ("add_assoc", "Groups.semigroup_add_class.add_assoc"), Calculate "TIMES"]
   204 then () else error "script.sml fun sel_appl_atomic_tacs diff.behav.";
   205 
   206 trace_script := true;
   207 trace_script := false;
   208 applyTactic 1 p (hd appltacs);
   209 val ((pt, p), _) = get_calc 1; show_pt pt;
   210 val appltacs = sel_appl_atomic_tacs pt p;
   211 (*applyTactic 1 p (hd appltacs); WAS assy: call by ([3], Pbl)*)
   212 
   213 "~~~~~ fun applyTactic, args:"; val ((cI:calcID), ip, tac) = (1, p, (hd appltacs));
   214 val ((pt, _), _) = get_calc cI;
   215 val p = get_pos cI 1;
   216 locatetac;
   217 locatetac tac;
   218 
   219 (*locatetac tac (pt, ip); (*WAS assy: call by ([3], Pbl)*)*)
   220 "~~~~~ fun locatetac, args:"; val (tac, (ptp as (pt, p))) = (tac, (pt, ip));
   221 val (mI,m) = mk_tac'_ tac;
   222 applicable_in p pt m ; (*Appl*)
   223 member op = specsteps mI; (*false*)
   224 (*loc_solve_ (mI,m) ptp; (*Argument: (mI, m) : string * tac Reason: Can't unify tac_ with tac*)*)
   225 loc_solve_; (*without _ ??? result is -> lOc writing error ???*)
   226 (*val it = fn: string * tac_ -> ptree * (pos * pos_) -> lOc_*)
   227 (mI,m); (*string * tac*)
   228 ptp (*ptree * pos'*);
   229 "~~~~~ fun loc_solve_, args:"; val (m ,(pt,pos)) = ((mI,m), ptp);
   230 (*val (msg, cs') = solve m (pt, pos);
   231 (*Argument: m : string * tac Reason: Can't unify tac_ with tac (Different type constructors)*)*)
   232 m;
   233 (pt, pos);
   234 "~~~~~ fun solve, args:"; val ((mI,m), (pt, po as (p,p_))) = (m, (pt, pos));
   235 (*solve has still p_!!!!!!!!!!!!!!!!!!!!!!!!!*)
   236 
   237 e_metID = get_obj g_metID pt (par_pblobj pt p); (*false*)
   238 val ctxt = get_ctxt pt po;
   239 
   240 (*generate1 (assoc_thy (get_obj g_domID pt (par_pblobj pt p))) m (e_istate, ctxt) (p,p_) pt;
   241 (*Argument: m : tac Reason: Can't unify tac_ with tac (Different type constructors)*)*)
   242 (assoc_thy (get_obj g_domID pt (par_pblobj pt p)));
   243 assoc_thy;
   244 
   245 autoCalculate 1 CompleteCalc;
   246 
   247 "----------- fun init_form, fun get_stac -------------------------";
   248 "----------- fun init_form, fun get_stac -------------------------";
   249 "----------- fun init_form, fun get_stac -------------------------";
   250 val fmz = ["equality (x+1=(2::real))", "solveFor x", "solutions L"];
   251 val (dI',pI',mI') = ("Test",["sqroot-test","univariate","equation","test"],
   252   ["Test","squ-equ-test-subpbl1"]);
   253 val (p,_,f,nxt,_,pt) = CalcTreeTEST [(fmz, (dI',pI',mI'))];
   254 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   255 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   256 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   257 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   258 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   259 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   260 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   261 "~~~~~ fun me, args:"; val (_,tac) = nxt;
   262 "~~~~~ fun locatetac, args:"; val ptp as (pt, p) = (pt, p);
   263 val (mI,m) = mk_tac'_ tac;
   264 val Appl m = applicable_in p pt m;
   265 member op = specsteps mI; (*false*)
   266 "~~~~~ fun loc_solve_, args:"; val (m, (pt, pos) ) = ((mI, m), ptp);
   267 "~~~~~ fun solve, args:"; val (("Apply_Method", Apply_Method' (mI,_,_,_)), pos as (p,_)) = (m, pos);
   268 val {srls, ...} = get_met mI;
   269 val PblObj {meth=itms, ...} = get_obj I pt p;
   270 val thy' = get_obj g_domID pt p;
   271 val thy = assoc_thy thy';
   272 val (is as ScrState (env,_,_,_,_,_), ctxt, sc) = init_scrstate thy itms mI;
   273 val ini = init_form thy sc env;
   274 "----- fun init_form, args:"; val (Prog sc) = sc;
   275 "----- fun get_stac, args:"; val (y, h $ body) = (thy, sc);
   276 case get_stac thy sc of SOME (Free ("e_e", _)) => ()
   277 | _ => error "script: Const (?, ?) in script (as term) changed";;
   278 
   279 
   280 "----------- x+1=2 start SubProblem 'stac2tac_ TODO: no match for ";
   281 "----------- x+1=2 start SubProblem 'stac2tac_ TODO: no match for ";
   282 "----------- x+1=2 start SubProblem 'stac2tac_ TODO: no match for ";
   283 val fmz = ["equality (x+1=(2::real))", "solveFor x","solutions L"];
   284 val (dI',pI',mI') =
   285   ("Test", ["sqroot-test","univariate","equation","test"],
   286    ["Test","squ-equ-test-subpbl1"]);
   287 val (p,_,f,nxt,_,pt) = CalcTreeTEST [(fmz, (dI',pI',mI'))];
   288 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   289 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   290 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   291 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   292 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   293 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   294 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   295 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   296 val (p,_,f,nxt,_,pt) = me nxt p [1] pt;
   297 (*val (p,_,f,nxt,_,pt) = me nxt p [1] pt; WAS: Empty_Tac, helpless*)
   298 show_pt pt;
   299 "~~~~~ fun me, args:"; val (_,tac) = nxt;
   300 val (pt, p) = case locatetac tac (pt,p) of
   301 	("ok", (_, _, ptp))  => ptp | _ => error "script.sml locatetac";
   302 "~~~~~ fun step, args:"; val (ip as (_,p_), (ptp as (pt,p), tacis)) = (p, ((pt, e_pos'), []))
   303 val pIopt = get_pblID (pt,ip); (*SOME ["linear", "univariate", "equation", "test"]*)
   304 tacis; (*= []*)
   305 member op = [Pbl,Met] p_ andalso is_none (get_obj g_env pt (fst p)); (*= false*)
   306 "~~~~~ fun nxt_solve_, args:"; val (ptp as (pt, pos as (p, p_))) = (pt, ip);
   307                                  (*WAS stac2tac_ TODO: no match for SubProblem*)
   308 val thy' = get_obj g_domID pt (par_pblobj pt p);
   309 val (srls, is, sc) = from_pblobj_or_detail' thy' (p,p_) pt;
   310 "~~~~~ fun next_tac, args:"; val (thy, (ptp as (pt,(p,_)):ptree * pos'), (sc as Prog (h $ body)), 
   311 	                               (ScrState (E,l,a,v,s,b), ctxt)) = ((thy',srls), (pt,pos), sc, is);
   312 l; (*= [R, L, R, L, R, R]*)
   313 val Appy (m', scrst as (_,_,_,v,_,_)) = nstep_up thy ptp sc E l Skip_ a v;
   314 "~~~~~ dont like to go into nstep_up...";
   315 val t = str2term ("SubProblem" ^ 
   316   "(Test', [linear, univariate, equation, test], [Test, solve_linear])" ^
   317   "[BOOL (-1 + x = 0), REAL x]");
   318 val (tac, tac_) = stac2tac_ pt @{theory "Isac"} t; (*WAS stac2tac_ TODO: no match for SubProblem*)
   319 case tac_ of 
   320   Subproblem' _ => ()
   321 | _ => error "script.sml x+1=2 start SubProblem from script";
   322 
   323 
   324 "----------- Take as 1st stac in script --------------------------";
   325 "----------- Take as 1st stac in script --------------------------";
   326 "----------- Take as 1st stac in script --------------------------";
   327 val p = e_pos'; val c = []; 
   328 val (p,_,f,nxt,_,pt) = 
   329     CalcTreeTEST 
   330         [(["functionTerm (x^^^2 + 1)", "integrateBy x", "antiDerivative FF"],
   331           ("Integrate", ["integrate","function"], ["diff","integration"]))];
   332 val (p,_,f,nxt,_,pt) = me nxt p c pt; (*nxt = ("Tac ", ...) --> Add_Given...*)
   333 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   334 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   335 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   336 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   337 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   338 val (p,_,f,nxt,_,pt) = me nxt p c pt;
   339 case nxt of (_, Apply_Method ["diff", "integration"]) => ()
   340           | _ => error "integrate.sml -- me method [diff,integration] -- spec";
   341 "----- step 8: returns nxt = Rewrite_Set_Inst ([\"(bdv, x)\"],\"integration\")";
   342 
   343 "~~~~~ fun me, args:"; val (((_,tac):tac'_), (p:pos'), _, (pt:ptree)) = (nxt, p, c, pt);
   344 "~~~~~ fun locatetac, args:"; val (tac, (ptp as (pt, p))) = (tac, (pt,p));
   345 val (mI,m) = mk_tac'_ tac;
   346 val Appl m = applicable_in p pt m;
   347 member op = specsteps mI (*false*);
   348 "~~~~~ fun loc_solve_, args:"; val (m, (pt,pos)) = ((mI,m), ptp);
   349 "~~~~~ fun solve, args:"; val ((_, m as Apply_Method' (mI, _, _, _)), (pt, (pos as (p,_)))) = 
   350                             (m, (pt, pos));
   351 val {srls, ...} = get_met mI;
   352         val PblObj {meth=itms, ...} = get_obj I pt p;
   353         val thy' = get_obj g_domID pt p;
   354         val thy = assoc_thy thy';
   355         val (is as ScrState (env,_,_,_,_,_), ctxt, sc) = init_scrstate thy itms mI;
   356         val ini = init_form thy sc env;
   357         val p = lev_dn p;
   358 ini = NONE; (*true*)
   359             val (m', (is', ctxt'), _) = next_tac (thy', srls) (pt, (p, Res)) sc (is, ctxt);
   360 	            val d = e_rls (*FIXME: get simplifier from domID*);
   361 "~~~~~ fun locate_gen, args:"; val ((ts as (thy',srls)), (m:tac_), ((pt,p):ptree * pos'), 
   362 	                     (scr as Prog (h $ body),d), (ScrState (E,l,a,v,S,b), ctxt)) = 
   363                    ((thy',srls), m', (pt,(p, Res)), (sc,d), (is', ctxt'));
   364 val thy = assoc_thy thy';
   365 l = [] orelse ((*init.in solve..Apply_Method...*)
   366 			         (last_elem o fst) p = 0 andalso snd p = Res); (*true*)
   367 "~~~~~ fun assy, args:"; val (ya, (is as (E,l,a,v,S,b),ss), 
   368                    (Const ("HOL.Let",_) $ e $ (Abs (id,T,body)))) = 
   369                  ((thy',ctxt,srls,d,Aundef), ((E,[R],a,v,S,b), [(m,EmptyMout,pt,p,[])]), body);
   370  (*check: true*) term2str e = "Take (Integral f_f D v_v)";
   371 "~~~~~ fun assy, args:"; val ((thy',ctxt,sr,d,ap), (is as (E,l,a,v,S,b), (m,_,pt,(p,p_),c)::ss), t) = 
   372                            (ya, ((E , l@[L,R], a,v,S,b),ss), e);
   373 val (a', STac stac) = handle_leaf "locate" thy' sr E a v t;
   374 (*             val ctxt = get_ctxt pt (p,p_)
   375 exception PTREE "get_obj: pos = [0] does not exist" raised 
   376 (line 908 of "/usr/local/isabisac/src/Tools/isac/Interpret/ctree.sml")*)
   377 
   378 
   379 "----------- 'trace_script' from outside 'fun me '----------------";
   380 "----------- 'trace_script' from outside 'fun me '----------------";
   381 "----------- 'trace_script' from outside 'fun me '----------------";
   382 val fmz = ["equality (x+1=(2::real))", "solveFor x","solutions L"];
   383 val (dI',pI',mI') =
   384    ("Test", ["sqroot-test","univariate","equation","test"],
   385     ["Test","squ-equ-test-subpbl1"]);
   386 val (p,_,f,nxt,_,pt) = CalcTreeTEST [(fmz, (dI',pI',mI'))];
   387 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   388 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   389 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   390 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   391 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   392 val (p,_,f,nxt,_,pt) = me nxt p [] pt;
   393 val (p,_,f,nxt,_,pt) = me nxt p [] pt; (*nxt = Apply_Method ["Test", "squ-equ-test-subpbl1"]*)
   394 (*from_pblobj_or_detail': no istate = from_pblobj_or_detail' "Isac" p pt;*)
   395 
   396 val (p,_,f,nxt,_,pt) = me nxt p [] pt; (*---------------------------------------------------*)
   397 val (p'''', pt'''') = (p, pt);
   398 f2str f = "x + 1 = 2";          snd nxt = Rewrite_Set "norm_equation";
   399 val (p, p_) = p(* = ([1], Frm)*);
   400 val (srls, (ScrState scrstate, ctxt), Prog sc) = from_pblobj_or_detail' "Isac" (p, p_) pt;
   401 val (env, loc_, curry_arg, res, Safe, true) = scrstate;
   402   env2str env = "[\"\n(e_e, x + 1 = 2)\",\"\n(v_v, x)\"]";
   403   loc_ = [];
   404   curry_arg = NONE;
   405   term2str res = "??.empty";                     (* scrstate before starting interpretation *)
   406 (*term2str (go loc_ sc) = "Prog Solve_root_equation e_e v_v = ...*)
   407 
   408 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   409 val (p'''', pt'''') = (p, pt);
   410 f2str f = "x + 1 + -1 * 2 = 0"; snd nxt = Rewrite_Set "Test_simplify";
   411 val (p, p_) = p(* = ([1], Res)*);
   412 val (srls, (ScrState scrstate, ctxt), Prog sc) = from_pblobj_or_detail' "Isac" (p, p_) pt;
   413 val (env, loc_, curry_arg, res, Safe, true) = scrstate;
   414   env2str env = "[\"\n(e_e, x + 1 = 2)\",\"\n(v_v, x)\"]";
   415   loc_ = [R, L, R, L, L, R, R];
   416   curry_arg = SOME (str2term "e_e::bool");
   417   term2str res = "x + 1 + -1 * 2 = 0";(* scrstate after norm_equation, before Test_simplify *)
   418 term2str (go loc_ sc) = "Rewrite_Set norm_equation False";
   419 
   420 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   421 val (p'''', pt'''') = (p, pt);
   422 f2str f = "-1 + x = 0"; snd nxt = Subproblem ("Test", ["linear", "univariate", "equation", "test"]);
   423 val (p, p_) = p(* = ([2], Res)*);
   424 val (srls, (ScrState scrstate, ctxt), Prog sc) = from_pblobj_or_detail' "Isac" (p, p_) pt;
   425 val (env, loc_, curry_arg, res, Safe, false) = scrstate;
   426   env2str env = "[\"\n(e_e, x + 1 = 2)\",\"\n(v_v, x)\"]";
   427   loc_ = [R, L, R, L, R, R];
   428   curry_arg = SOME (str2term "e_e::bool");
   429   term2str res = "-1 + x = 0";           (* scrstate after Test_simplify, before Subproblem *)
   430 term2str (go loc_ sc) = "Rewrite_Set Test_simplify False";
   431 
   432 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   433 val (p'''', pt'''') = (p, pt);     (*f2str f = exception Match; ...is a model, not a formula*)
   434 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   435 val (p'''', pt'''') = (p, pt);
   436 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   437 val (p'''', pt'''') = (p, pt);
   438 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   439 val (p'''', pt'''') = (p, pt);
   440 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   441 val (p'''', pt'''') = (p, pt);
   442 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   443 val (p'''', pt'''') = (p, pt);
   444 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   445 val (p'''', pt'''') = (p, pt);
   446 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*nxt = Apply_Method ["Test", "solve_linear"]*)
   447 (*from_pblobj_or_detail': no istate = from_pblobj_or_detail' "Isac" p pt;*)
   448 
   449 val (p,_,f,nxt,_,pt) = me nxt p [] pt; (*---------------------------------------------------*)
   450 val (p'''', pt'''') = (p, pt);
   451 f2str f = "-1 + x = 0"; snd nxt = Rewrite_Set_Inst (["(bdv, x)"], "isolate_bdv");
   452 val (p, p_) = p(* = ([3, 1], Frm)*);
   453 val (srls, (ScrState scrstate, ctxt), Prog sc) = from_pblobj_or_detail' "Isac" (p, p_) pt;
   454 val (env, loc_, curry_arg, res, Safe, true) = scrstate;
   455   env2str env = "[\"\n(e_e, -1 + x = 0)\",\"\n(v_v, x)\"]";
   456   loc_ = [];
   457   curry_arg = NONE;
   458   term2str res = "??.empty";                     (* scrstate before starting interpretation *)
   459 (*term2str (go loc_ sc) = "Prog Solve_linear e_e v_v = ...*)
   460 
   461 val (p,_,f,nxt,_,pt) = me nxt p'''' [] pt''''; (*-------------------------------------------*)
   462 val (p'''', pt'''') = (p, pt);
   463 f2str f = "x = 0 + -1 * -1"; snd nxt = Rewrite_Set "Test_simplify";
   464 val (p, p_) = p(* = ([3, 1], Res)*);
   465 val (srls, (ScrState scrstate, ctxt), Prog sc) = from_pblobj_or_detail' "Isac" (p, p_) pt;
   466 val (env, loc_, curry_arg, res, Safe, true) = scrstate;
   467   env2str env = "[\"\n(e_e, -1 + x = 0)\",\"\n(v_v, x)\"]";
   468   loc_ = [R, L, R, L, R, L, R];
   469   curry_arg = SOME (str2term "e_e::bool");
   470   term2str res = "x = 0 + -1 * -1";(* scrstate after isolate_bdv, before Test_simplify *)
   471 term2str (go loc_ sc) = "Rewrite_Set_Inst [(bdv, v_v)] isolate_bdv False";
   472 
   473 "----------- fun sel_rules ---------------------------------------";
   474 "----------- fun sel_rules ---------------------------------------";
   475 "----------- fun sel_rules ---------------------------------------";
   476 (* compare test/../interface.sml
   477 "--------- getTactic, fetchApplicableTactics ------------";
   478 *)
   479  states:=[];
   480  CalcTree [(["equality (x+1=(2::real))", "solveFor x","solutions L"], 
   481    ("Test", ["sqroot-test","univariate","equation","test"],
   482     ["Test","squ-equ-test-subpbl1"]))];
   483  Iterator 1;
   484  moveActiveRoot 1;
   485  autoCalculate 1 CompleteCalc;
   486  val ((pt,_),_) = get_calc 1;
   487  show_pt pt;
   488 
   489 (*UC\label{SOLVE:MANUAL:TACTIC:listall} UC 30.3.2.2 p.175*)
   490  val tacs = sel_rules pt ([],Pbl);
   491  if tacs = [Apply_Method ["Test", "squ-equ-test-subpbl1"]] then ()
   492  else error "script.sml: diff.behav. in sel_rules ([],Pbl)";
   493 
   494  val tacs = sel_rules pt ([1],Res);
   495  if tacs = [Rewrite_Set "norm_equation", Rewrite_Set "Test_simplify",
   496       Subproblem ("Test", ["linear", "univariate", "equation", "test"]),
   497       Check_elementwise "Assumptions"] then ()
   498  else error "script.sml: diff.behav. in sel_rules ([1],Res)";
   499 
   500  val tacs = sel_rules pt ([3],Pbl);
   501  if tacs = [Apply_Method ["Test", "solve_linear"]] then ()
   502  else error "script.sml: diff.behav. in sel_rules ([3],Pbl)";
   503 
   504  val tacs = sel_rules pt ([3,1],Res);
   505  if tacs = [Rewrite_Set_Inst (["(bdv, x)"], "isolate_bdv"),
   506       Rewrite_Set "Test_simplify"] then ()
   507  else error "script.sml: diff.behav. in sel_rules ([3,1],Res)";
   508 
   509  val tacs = sel_rules pt ([3],Res);
   510  if tacs = [Rewrite_Set "norm_equation", Rewrite_Set "Test_simplify",
   511       Subproblem ("Test", ["linear", "univariate", "equation", "test"]),
   512       Check_elementwise "Assumptions"] then ()
   513  else error "script.sml: diff.behav. in sel_rules ([3],Res)";
   514 
   515  val tacs = (sel_rules pt ([],Res)) handle PTREE str => [Tac str];
   516  if tacs = [Tac "no tactics applicable at the end of a calculation"] then ()
   517  else error "script.sml: diff.behav. in sel_rules ([],Res)";
   518 
   519 "----------- fun sel_appl_atomic_tacs ----------------------------";
   520 "----------- fun sel_appl_atomic_tacs ----------------------------";
   521 "----------- fun sel_appl_atomic_tacs ----------------------------";
   522  states:=[];
   523  CalcTree [(["equality (x+1=(2::real))", "solveFor x","solutions L"], 
   524    ("Test", ["sqroot-test","univariate","equation","test"],
   525     ["Test","squ-equ-test-subpbl1"]))];
   526  Iterator 1;
   527  moveActiveRoot 1;
   528  autoCalculate 1 CompleteCalc;
   529 
   530 (*UC\label{SOLVE:MANUAL:TACTIC:listall} UC 30.3.2.2 p.175*)
   531  fetchApplicableTactics 1 99999 ([],Pbl);
   532 
   533  fetchApplicableTactics 1 99999 ([1],Res);
   534 "~~~~~ fun fetchApplicableTactics, args:"; val (cI, (scope:int), (p:pos')) = (1, 99999, ([1],Res));
   535 val ((pt, _), _) = get_calc cI;
   536 (*version 1:*)
   537 if sel_rules pt p = [Rewrite_Set "norm_equation", Rewrite_Set "Test_simplify",
   538   Subproblem ("Test", ["linear", "univariate", "equation", "test"]),
   539   Check_elementwise "Assumptions"] then ()
   540 else error "fetchApplicableTactics ([1],Res) changed";
   541 (*version 2:*)
   542 (*WAS:
   543 sel_appl_atomic_tacs pt p;
   544 ...
   545 ### atomic_appl_tacs: not impl. for tac='Subproblem(Test,["linear","univariate","equation","test"])' 
   546 ### atomic_appl_tacs: not impl. for tac = 'Check_elementwise "Assumptions"' 
   547 *)
   548 
   549 "~~~~~ fun sel_appl_atomic_tacs, args:"; val (pt, (p,p_)) = (pt, p);
   550 is_spec_pos p_ = false;
   551         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' =
   556           if metID = e_metID 
   557           then (thd3 o snd3) (get_obj g_origin pt pp)
   558           else metID
   559         val {scr=Prog sc,srls,erls,rew_ord'=ro,...} = get_met metID'
   560         val ScrState (env,_,a,v,_,_) = get_istate pt (p,p_)
   561         val alltacs = (*we expect at least 1 stac in a script*)
   562           map ((stac2tac pt thy) o rep_stacexpr o #2 o
   563            (handle_leaf "selrul" thy' srls env a v)) (stacpbls sc)
   564         val f =
   565           case p_ of
   566               Frm => get_obj g_form pt p
   567             | Res => (fst o (get_obj g_result pt)) p
   568 (*WN120611 stopped and took version 1 again for fetchApplicableTactics !
   569 (distinct o flat o (map (atomic_appl_tacs thy ro erls f))) alltacs
   570 ...
   571 ### atomic_appl_tacs: not impl. for tac='Subproblem(Test,["linear","univariate","equation","test"])' 
   572 ### atomic_appl_tacs: not impl. for tac = 'Check_elementwise "Assumptions"' 
   573 *)
   574