src/Tools/isac/Interpret/script.sml
author Walther Neuper <wneuper@ist.tugraz.at>
Mon, 10 Oct 2016 18:24:14 +0200
changeset 59250 727dff4f6b2c
parent 59240 bd9f7f08000c
child 59252 7d3dbc1171ff
permissions -rw-r--r--
transport terms in theorems to frontend

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