test/Tools/isac/Interpret/script.sml
author Walther Neuper <neuper@ist.tugraz.at>
Sat, 17 Mar 2012 11:06:46 +0100
changeset 42394 977788dfed26
parent 42387 767debe8a50c
child 42438 31e1aa39b5cb
permissions -rw-r--r--
uncomment test/../rateq.sml (Isabelle 2002 --> 2011)

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