src/Tools/isac/ME/script.sml
author Walther Neuper <neuper@ist.tugraz.at>
Fri, 20 Aug 2010 12:25:37 +0200
branchisac-update-Isa09-2
changeset 37934 56f10b13005e
parent 37933 b65c6037eb6d
child 37935 27d365c3dd31
permissions -rw-r--r--
finished update ME/calchead.sml + pushed updates over all sml+test

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