src/Tools/isac/Specify/generate.sml
author Walther Neuper <walther.neuper@jku.at>
Thu, 09 Apr 2020 18:21:09 +0200
changeset 59863 0dcc8f801578
parent 59861 65ec9f679c3f
child 59865 75a9d629ea53
permissions -rw-r--r--
rearrange code in Rule_Set and Rule

note: mutual recursion inhibits nice separation. ThyC and ThmC are involved, too.
wneuper@59276
     1
(* Title: generate specific entries into Ctree
wneuper@59276
     2
   Author: Walther Neuper
wneuper@59276
     3
   (c) due to copyright terms
wneuper@59276
     4
*)
wneuper@59276
     5
wneuper@59271
     6
signature GENERATE_CALC_TREE =
wneuper@59276
     7
sig
wneuper@59266
     8
  type taci
wneuper@59266
     9
  val e_taci : taci
wneuper@59405
    10
  datatype pblmet = Method of Celem.metID | Problem of Celem.pblID | Upblmet
wneuper@59268
    11
  datatype mout =
wneuper@59268
    12
    EmptyMout
wneuper@59268
    13
  | Error' of string
walther@59863
    14
  | FormKF of UnparseC.cterm'
wneuper@59316
    15
  | PpcKF of pblmet * Model.item Model.ppc
wneuper@59405
    16
  | RefinedKF of Celem.pblID * (Model.itm list * (bool * term) list)
walther@59811
    17
  val generate1 : Tactic.T -> Istate_Def.T * Proof.context -> Calc.T
walther@59846
    18
    -> Pos.pos' * Pos.pos' list * mout * Ctree.ctree
walther@59737
    19
  val init_istate : Tactic.input -> term -> Istate_Def.T
wneuper@59316
    20
  val init_pbl : (string * (term * 'a)) list -> Model.itm list
wneuper@59316
    21
  val init_pbl' : (string * (term * term)) list -> Model.itm list
walther@59846
    22
  val embed_deriv : taci list -> Calc.T -> Pos.pos' list * (Calc.T) (* for inform.sml *)
wneuper@59268
    23
  val generate_hard : (* for solve.sml *)
walther@59846
    24
    theory -> Tactic.T -> Pos.pos' -> Ctree.ctree -> Pos.pos' * Pos.pos' list * mout * Ctree.ctree
walther@59846
    25
  val generate : (Tactic.input * Tactic.T * (Pos.pos' * (Istate_Def.T * Proof.context))) list ->
walther@59846
    26
    Ctree.ctree * Pos.pos' list * Pos.pos' -> Ctree.ctree * Pos.pos' list * Pos.pos' (* for mathengine.sml *)
walther@59861
    27
  val generate_inconsistent_rew : Selem.subs option * ThmC.thm'' -> term -> Istate_Def.T * Proof.context ->
walther@59846
    28
    Pos.pos' -> Ctree.ctree -> Calc.T (* for interface.sml *)
wneuper@59310
    29
(* ---- for tests only: shifted from below to remove the Warning "unused" at fun.def. --------- *)
wneuper@59312
    30
  val tacis2str : taci list -> string
walther@59639
    31
  val mout2str : mout -> string
walther@59785
    32
(*/-------------------------------------------------------- ! aktivate for Test_Isac BEGIN ---\* )
walther@59813
    33
  val res_from_taci : taci -> (term * term list)
walther@59813
    34
  val insert_pos : Pos.pos -> taci list -> taci list
walther@59785
    35
( *\--- ! aktivate for Test_Isac END ----------------------------------------------------------/*)
wneuper@59310
    36
wneuper@59310
    37
(*----- unused code, kept as hints to design ideas ---------------------------------------------*)
wneuper@59310
    38
  (* NONE *)
wneuper@59266
    39
end
neuper@37906
    40
wneuper@59271
    41
structure Generate(**): GENERATE_CALC_TREE(**) =
wneuper@59266
    42
struct
wneuper@59276
    43
open Ctree
walther@59695
    44
open Pos
wneuper@59312
    45
walther@59802
    46
(* initialize istate for Detail_Set *)
wneuper@59571
    47
fun init_istate (Tactic.Rewrite_Set rls) t =
walther@59802
    48
    let
walther@59802
    49
      val thy = Celem.assoc_thy "Isac_Knowledge"
walther@59802
    50
      val args = Auto_Prog.gen thy t (assoc_rls rls) |> Program.formal_args
walther@59802
    51
    in
walther@59802
    52
      Istate_Def.Pstate (Istate_Def.e_pstate |> Istate_Def.set_env_true [(hd args, t)])
walther@59802
    53
    end
wneuper@59571
    54
  | init_istate (Tactic.Rewrite_Set_Inst (subs, rls)) t =
wneuper@59266
    55
    let
walther@59802
    56
      val thy = Celem.assoc_thy "Isac_Knowledge"
walther@59802
    57
      val rls' = assoc_rls rls
walther@59802
    58
      val v = case Selem.subs2subst thy subs of
walther@59802
    59
        (_, v) :: _ => v (*...we suppose the substitution of only ONE bound variable*)
walther@59802
    60
      | _ => raise ERROR "init_istate: uncovered case"
walther@59802
    61
      val prog = Auto_Prog.gen thy t rls'
walther@59802
    62
      val args = Program.formal_args prog
walther@59802
    63
    in
walther@59802
    64
      Istate_Def.Pstate (Istate_Def.e_pstate |> Istate_Def.set_env_true (args ~~ [t, v]))
wneuper@59266
    65
    end
walther@59846
    66
  | init_istate tac _ = error ("init_istate: uncovered definition for " ^ Tactic.input_to_string tac)
neuper@37906
    67
wneuper@59266
    68
(* a taci holds alle information required to build a node in the calc-tree;
neuper@37906
    69
   a taci is assumed to be used efficiently such that the calc-tree
neuper@37906
    70
   resulting from applying a taci need not be stored separately;
wneuper@59266
    71
   see "type calcstate" *)
neuper@37906
    72
(*TODO.WN0504 redesign ??? or redesign generate ?? see "fun generate"
neuper@37906
    73
  TODO.WN0512 ? redesign this _list_:
neuper@37906
    74
  # only used for [Apply_Method + (Take or Subproblem)], i.e. for initacs
neuper@37906
    75
  # the latter problem may be resolved automatically if "fun autocalc" is 
neuper@37906
    76
    not any more used for the specify-phase and for changing the phases*)
neuper@37906
    77
type taci = 
walther@59823
    78
  (Tactic.input *                     (* for comparison with input tac             *)      
wneuper@59571
    79
   Tactic.T *                         (* for ctree generation                      *)
wneuper@59302
    80
   (pos' *                            (* after applying tac_, for ctree generation *)
walther@59737
    81
    (Istate_Def.T * Proof.context)))  (* after applying tac_, for ctree generation *)
walther@59846
    82
val e_taci = (Tactic.Empty_Tac, Tactic.Empty_Tac_, (e_pos', (Istate_Def.empty, ContextC.empty))): taci
bonzai@41948
    83
fun taci2str ((tac, tac_, (pos', (istate, _))):taci) =
walther@59846
    84
  "( " ^ Tactic.input_to_string tac ^ ", " ^ Tactic.string_of tac_ ^ ", ( " ^ pos'2str pos' ^ ", " ^
walther@59844
    85
  Istate_Def.string_of istate ^ " ))"
wneuper@59405
    86
fun tacis2str tacis = (strs2str o (map (Celem.linefeed o taci2str))) tacis
neuper@37906
    87
wneuper@59405
    88
datatype pblmet =           (*%^%*)
wneuper@59405
    89
  Upblmet                   (*undefined*)
wneuper@59405
    90
| Problem of Celem.pblID    (*%^%*)
wneuper@59405
    91
| Method of Celem.metID;    (*%^%*)
wneuper@59266
    92
fun pblmet2str (Problem pblID) = "Problem " ^ strs2str pblID (*%^%*)
wneuper@59405
    93
  | pblmet2str (Method metID) = "Method " ^ Celem.metID2str metID (*%^%*)
wneuper@59266
    94
  | pblmet2str x = error ("pblmet2str: uncovered definition " ^ pblmet2str x)
neuper@37906
    95
neuper@37906
    96
(*3.5.00: TODO: foppFK eliminated in interface FE-KE !!!*)
neuper@37906
    97
datatype foppFK =                  (* in DG cases div 2 *)
neuper@37906
    98
  EmptyFoppFK         (*DG internal*)
walther@59863
    99
| FormFK of UnparseC.cterm'
walther@59863
   100
| PpcFK of UnparseC.cterm' Model.ppc
wneuper@59266
   101
fun foppFK2str (FormFK ct') ="FormFK " ^ ct'
wneuper@59316
   102
  | foppFK2str (PpcFK  ppc) ="PpcFK " ^ Model.ppc2str ppc
wneuper@59266
   103
  | foppFK2str EmptyFoppFK  ="EmptyFoppFK"
neuper@37906
   104
neuper@37906
   105
datatype nest = Open | Closed | Nundef;
neuper@37906
   106
fun nest2str Open = "Open"
neuper@37906
   107
  | nest2str Closed = "Closed"
wneuper@59266
   108
  | nest2str Nundef = "Nundef"
neuper@37906
   109
neuper@37906
   110
type indent = int;
neuper@37906
   111
datatype edit = EdUndef | Write | Protect;
neuper@37906
   112
                                   (* bridge --> kernel *)
neuper@37906
   113
                                   (* bridge <-> kernel *)
neuper@37906
   114
(* needed in dialog.sml *)         (* bridge <-- kernel *)
neuper@37906
   115
fun edit2str EdUndef = "EdUndef"
neuper@37906
   116
  | edit2str Write = "Write"
neuper@37906
   117
  | edit2str Protect = "Protect";
neuper@37906
   118
neuper@42023
   119
datatype inout = (*FIXME.WN1105 drop this: was required for proto0 with dialog in sml*)
wneuper@59405
   120
  Error_ of string                                                         (*<--*)
walther@59863
   121
| FormKF of cellID * edit * indent * nest * UnparseC.cterm'                   (*<--*)
wneuper@59316
   122
| PpcKF of cellID * edit * indent * nest * (pblmet * Model.item Model.ppc) (*<--*)
wneuper@59405
   123
| RefineKF of Stool.match list                                             (*<--*)
wneuper@59405
   124
| RefinedKF of (Celem.pblID * ((Model.itm list) * ((bool * term) list)))   (*<--*)
neuper@37906
   125
wneuper@59267
   126
(*
wneuper@59267
   127
  datatype mout = EmptyMout | Error' of inout | Form' of inout | Problems of inout
wneuper@59267
   128
*)
neuper@37906
   129
datatype mout =
walther@59863
   130
  FormKF of UnparseC.cterm'
wneuper@59316
   131
| PpcKF of (pblmet * Model.item Model.ppc) 
wneuper@59405
   132
| RefinedKF of Celem.pblID * (Model.itm list * (bool * term) list)
wneuper@59267
   133
| Error' of string
wneuper@59267
   134
| EmptyMout
neuper@37906
   135
wneuper@59267
   136
fun mout2str (FormKF cterm') = "FormKF " ^ cterm'
wneuper@59316
   137
  | mout2str (PpcKF  (pm, itemppc)) = "PpcKF (" ^ pblmet2str pm ^ "," ^ Model.itemppc2str itemppc ^ ")"
wneuper@59312
   138
  | mout2str (RefinedKF  (_, _)) = "mout2str: RefinedKF not impl."
wneuper@59267
   139
  | mout2str (Error'  str) = "Error' " ^ str
wneuper@59267
   140
  | mout2str (EmptyMout    ) = "EmptyMout"
neuper@37906
   141
neuper@37906
   142
(* init pbl with ...,dsc,empty | [] *)
neuper@37906
   143
fun init_pbl pbt = 
wneuper@59266
   144
  let
walther@59861
   145
    fun pbt2itm (f, (d, _)) = (0, [], false, f, Model.Inc ((d, []), (TermC.empty, [])))
wneuper@59266
   146
  in map pbt2itm pbt end
wneuper@59266
   147
wneuper@59266
   148
(* take formal parameters from pbt, for transfer from pbl/met-hierarchy *)
neuper@37906
   149
fun init_pbl' pbt = 
neuper@37906
   150
  let 
walther@59861
   151
    fun pbt2itm (f, (d, t)) = (0, [], false, f, Model.Inc((d, [t]), (TermC.empty, [])))
wneuper@59266
   152
  in map pbt2itm pbt end
walther@59811
   153
(* generate 1 ppobj in Ctree *)
walther@59811
   154
fun generate1 (Tactic.Model_Problem' (_, itms, met)) (_, ctxt) (pt, pos as (p, _)) =
walther@59811
   155
    let
walther@59810
   156
      val pt = update_pbl pt p itms
walther@59810
   157
	    val pt = update_met pt p met
walther@59810
   158
    in
walther@59811
   159
      (pos, [], PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] []), pt)
walther@59810
   160
    end
walther@59811
   161
  | generate1 (Tactic.Add_Given' (_, itmlist)) (_, ctxt) (pt, pos as (p, p_)) = 
walther@59811
   162
    (pos: pos', [], PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [][]),
wneuper@59266
   163
       case p_ of
wneuper@59266
   164
         Pbl => update_pbl pt p itmlist
wneuper@59266
   165
	     | Met => update_met pt p itmlist
wneuper@59266
   166
       | _ => error ("uncovered case " ^ pos_2str p_))
wneuper@59266
   167
    (* WN110515 probably declare_constraints with input item (without dsc) --
wneuper@59266
   168
      -- important when specifying without formalisation *)
walther@59811
   169
  | generate1 (Tactic.Add_Find' (_, itmlist)) (_, ctxt) (pt, pos as (p, p_)) = 
walther@59811
   170
    (pos, [], (PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] [])),
wneuper@59266
   171
       case p_ of
wneuper@59266
   172
         Pbl => update_pbl pt p itmlist
wneuper@59266
   173
	     | Met => update_met pt p itmlist
wneuper@59266
   174
       | _ => error ("uncovered case " ^ pos_2str p_))
neuper@41994
   175
    (*WN110515 probably declare_constraints with input item (without dsc)*)
walther@59811
   176
  | generate1 (Tactic.Add_Relation' (_, itmlist)) (_, ctxt) (pt, pos as (p, p_)) = 
walther@59811
   177
    (pos, [],  PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] []),
wneuper@59266
   178
       case p_ of
wneuper@59266
   179
         Pbl => update_pbl pt p itmlist
wneuper@59266
   180
	     | Met => update_met pt p itmlist
wneuper@59266
   181
       | _ => error ("uncovered case " ^ pos_2str p_))
walther@59811
   182
  | generate1 (Tactic.Specify_Theory' domID) (_, ctxt) (pt, pos as (p,_)) = 
walther@59811
   183
    (pos, [] , PpcKF  (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] []),
wneuper@59266
   184
      update_domID pt p domID)
walther@59811
   185
  | generate1 (Tactic.Specify_Problem' (pI, (_, (itms, _)))) (_, ctxt) (pt, (p, _)) =
wneuper@59266
   186
    let
wneuper@59266
   187
      val pt = update_pbl pt p itms
wneuper@59266
   188
      val pt = update_pblID pt p pI
wneuper@59266
   189
    in
walther@59811
   190
      ((p, Pbl), [], PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] []), pt)
wneuper@59266
   191
    end
walther@59811
   192
  | generate1 (Tactic.Specify_Method' (mID, oris, itms)) (_, ctxt) (pt, (p, _)) =
wneuper@59266
   193
    let
wneuper@59266
   194
      val pt = update_oris pt p oris
wneuper@59266
   195
      val pt = update_met pt p itms
wneuper@59266
   196
      val pt = update_metID pt p mID
wneuper@59266
   197
    in
walther@59811
   198
      ((p, Met), [], PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] []), pt)
wneuper@59266
   199
    end
walther@59811
   200
  | generate1 (Tactic.Refine_Tacitly' (_, pIre, domID, metID, pbl)) (_, ctxt) (pt, pos as (p, _)) = 
wneuper@59266
   201
    let
wneuper@59266
   202
      val pt = update_pbl pt p pbl
wneuper@59266
   203
      val pt = update_orispec pt p (domID, pIre, metID)
wneuper@59266
   204
    in
walther@59811
   205
      (pos, [], PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] []), pt)
wneuper@59266
   206
    end
walther@59811
   207
  | generate1 (Tactic.Refine_Problem' (pI, _)) (_, ctxt) (pt, pos as (p, _)) =
wneuper@59266
   208
    let
wneuper@59266
   209
      val (dI, _, mI) = get_obj g_spec pt p
wneuper@59266
   210
      val pt = update_spec pt p (dI, pI, mI)
wneuper@59266
   211
    in
walther@59811
   212
      (pos, [], PpcKF (Upblmet, Specify.itms2itemppc (Proof_Context.theory_of ctxt) [] []), pt)
wneuper@59266
   213
    end
walther@59811
   214
  | generate1 (Tactic.Apply_Method' (_, topt, is, _)) (_, ctxt) (pt, pos as (p, _)) = 
wneuper@59266
   215
    (case topt of 
wneuper@59266
   216
      SOME t => 
wneuper@59266
   217
        let val (pt, c) = cappend_form pt p (is, ctxt) t
wneuper@59266
   218
        in (pos, c, EmptyMout, pt) end
walther@59839
   219
    | NONE => (pos, [], EmptyMout, pt))
walther@59811
   220
  | generate1 (Tactic.Take' t) l (pt, (p, _)) = (* val (Take' t) = m; *)
wneuper@59266
   221
    let
wneuper@59266
   222
      val p =
wneuper@59266
   223
        let val (ps, p') = split_last p (* no connex to prev.ppobj *)
wneuper@59266
   224
	      in if p' = 0 then ps @ [1] else p end
wneuper@59266
   225
      val (pt, c) = cappend_form pt p l t
wneuper@59266
   226
    in
walther@59861
   227
      ((p, Frm): pos', c, FormKF (UnparseC.term2str t), pt)
wneuper@59266
   228
    end
walther@59811
   229
  | generate1 (Tactic.Begin_Trans' t) l (pt, (p, Frm)) =
wneuper@59266
   230
    let
wneuper@59266
   231
      val (pt, c) = cappend_form pt p l t
neuper@37906
   232
      val pt = update_branch pt p TransitiveB (*040312*)
wneuper@59266
   233
      (* replace the old PrfOjb ~~~~~ *)
wneuper@59266
   234
      val p = (lev_on o lev_dn (* starts with [...,0] *)) p
wneuper@59266
   235
      val (pt, c') = cappend_form pt p l t (*FIXME.0402 same istate ???*)
wneuper@59266
   236
    in
walther@59861
   237
      ((p, Frm), c @ c', FormKF (UnparseC.term2str t), pt)
wneuper@59266
   238
    end
walther@59811
   239
  | generate1 (Tactic.Begin_Trans' t) l (pt, (p, Res)) = 
wneuper@59266
   240
    (*append after existing PrfObj    vvvvvvvvvvvvv*)
walther@59811
   241
    generate1 (Tactic.Begin_Trans' t) l (pt, (lev_on p, Frm))
walther@59811
   242
  | generate1 (Tactic.End_Trans' tasm) l (pt, (p, _)) =
wneuper@59266
   243
    let
wneuper@59266
   244
      val p' = lev_up p
wneuper@59266
   245
      val (pt, c) = append_result pt p' l tasm Complete
wneuper@59266
   246
    in
wneuper@59374
   247
      ((p', Res), c, FormKF "DUMMY" (*term2str t ..ERROR (t) has not been declared*), pt)
wneuper@59266
   248
    end
walther@59811
   249
  | generate1 (Tactic.Rewrite_Inst' (_, _, _, _, subs', thm', f, (f', asm))) (is, ctxt) (pt, (p, _)) =
wneuper@59266
   250
    let
walther@59809
   251
      val (pt, c) = cappend_atomic pt p (is, ctxt) f
wneuper@59571
   252
        (Tactic.Rewrite_Inst (Selem.subst2subs subs', thm')) (f',asm) Complete;
wneuper@59266
   253
      val pt = update_branch pt p TransitiveB
wneuper@59267
   254
    in
walther@59861
   255
      ((p, Res), c, FormKF (UnparseC.term2str f'), pt)
wneuper@59267
   256
    end
walther@59811
   257
 | generate1 (Tactic.Rewrite' (_, _, _, _, thm', f, (f', asm))) (is, ctxt) (pt, (p, _)) =
wneuper@59266
   258
   let
walther@59813
   259
     val (pt, c) = cappend_atomic pt p (is, ctxt) f (Tactic.Rewrite thm') (f', asm) Complete
wneuper@59266
   260
     val pt = update_branch pt p TransitiveB
wneuper@59266
   261
   in
walther@59861
   262
    ((p, Res), c, FormKF (UnparseC.term2str f'), pt)
wneuper@59266
   263
   end
walther@59811
   264
  | generate1 (Tactic.Rewrite_Set_Inst' (_, _, subs', rls', f, (f', asm))) (is, ctxt) (pt, (p, _)) =
wneuper@59266
   265
    let
walther@59828
   266
      val (pt, c) = cappend_atomic pt p (is, ctxt) f 
walther@59863
   267
        (Tactic.Rewrite_Set_Inst (Selem.subst2subs subs', Rule_Set.rls2str rls')) (f', asm) Complete
wneuper@59266
   268
      val pt = update_branch pt p TransitiveB
wneuper@59266
   269
    in
walther@59861
   270
      ((p, Res), c, FormKF (UnparseC.term2str f'), pt)
wneuper@59266
   271
    end
walther@59828
   272
  | generate1 (Tactic.Detail_Set_Inst' (_, _, subs, rls, f, _)) (is, ctxt) (pt, (p, _)) =
wneuper@59266
   273
    let
walther@59828
   274
      val (pt, _) = cappend_form pt p (is, ctxt) f 
wneuper@59266
   275
      val pt = update_branch pt p TransitiveB
walther@59863
   276
      val is = init_istate (Tactic.Rewrite_Set_Inst (Selem.subst2subs subs, Rule_Set.rls2str rls)) f 
walther@59861
   277
      val tac_ = Tactic.Apply_Method' (Celem.e_metID, SOME TermC.empty (*t ..has not been declared*), is, ctxt)
wneuper@59266
   278
      val pos' = ((lev_on o lev_dn) p, Frm)
wneuper@59266
   279
    in
walther@59828
   280
      generate1 tac_ (is, ctxt) (pt, pos') (*implicit Take*)
wneuper@59266
   281
    end
walther@59811
   282
  | generate1 (Tactic.Rewrite_Set' (_, _, rls', f, (f', asm))) (is, ctxt) (pt, (p, _)) =
wneuper@59266
   283
    let
walther@59828
   284
      val (pt, c) = cappend_atomic pt p (is, ctxt) f 
walther@59863
   285
        (Tactic.Rewrite_Set (Rule_Set.rls2str rls')) (f', asm) Complete
wneuper@59266
   286
      val pt = update_branch pt p TransitiveB
wneuper@59266
   287
    in
walther@59861
   288
      ((p, Res), c, FormKF (UnparseC.term2str f'), pt)
wneuper@59266
   289
    end
walther@59828
   290
  | generate1 (Tactic.Detail_Set' (_, _, rls, f, _)) (is, ctxt) (pt, (p, _)) =
wneuper@59266
   291
    let
walther@59828
   292
      val (pt, _) = cappend_form pt p (is, ctxt) f 
wneuper@59266
   293
      val pt = update_branch pt p TransitiveB
walther@59863
   294
      val is = init_istate (Tactic.Rewrite_Set (Rule_Set.rls2str rls)) f
walther@59861
   295
      val tac_ = Tactic.Apply_Method' (Celem.e_metID, SOME TermC.empty (*t ..has not been declared*), is, ctxt)
wneuper@59266
   296
      val pos' = ((lev_on o lev_dn) p, Frm)
wneuper@59266
   297
    in
walther@59828
   298
      generate1 tac_ (is, ctxt) (pt, pos') (*implicit Take*)
wneuper@59266
   299
    end
walther@59843
   300
  | generate1 (Tactic.Check_Postcond' (_, scval)) l (pt, (p, _)) =
neuper@42394
   301
      let
walther@59843
   302
        val (pt, c) = append_result pt p l (scval, []) Complete
wneuper@59266
   303
      in
walther@59861
   304
        ((p, Res), c, FormKF (UnparseC.term2str scval), pt)
wneuper@59266
   305
      end
walther@59811
   306
  | generate1 (Tactic.Calculate' (_, op_, f, (f', _))) l (pt, (p, _)) =
neuper@42394
   307
      let
wneuper@59571
   308
        val (pt,c) = cappend_atomic pt p l f (Tactic.Calculate op_) (f', []) Complete
wneuper@59266
   309
      in
walther@59861
   310
        ((p, Res), c, FormKF (UnparseC.term2str f'), pt)
wneuper@59266
   311
      end
walther@59811
   312
  | generate1 (Tactic.Check_elementwise' (consts, pred, (f', asm))) l (pt, (p, _)) =
neuper@42394
   313
      let
wneuper@59571
   314
        val (pt,c) = cappend_atomic pt p l consts (Tactic.Check_elementwise pred) (f', asm) Complete
wneuper@59266
   315
      in
walther@59861
   316
        ((p, Res), c, FormKF (UnparseC.term2str f'), pt)
wneuper@59266
   317
      end
walther@59811
   318
  | generate1 (Tactic.Or_to_List' (ors, list)) l (pt, (p, _)) =
neuper@42394
   319
      let
wneuper@59571
   320
        val (pt,c) = cappend_atomic pt p l ors Tactic.Or_to_List (list, []) Complete
wneuper@59266
   321
      in
walther@59861
   322
        ((p, Res), c, FormKF (UnparseC.term2str list), pt)
wneuper@59266
   323
      end
walther@59811
   324
  | generate1 (Tactic.Substitute' (_, _, subte, t, t')) l (pt, (p, _)) =
neuper@41983
   325
      let
neuper@41983
   326
        val (pt,c) =
wneuper@59571
   327
          cappend_atomic pt p l t (Tactic.Substitute (Selem.subte2sube subte)) (t',[]) Complete
walther@59861
   328
        in ((p, Res), c, FormKF (UnparseC.term2str t'), pt) 
wneuper@59266
   329
        end
walther@59811
   330
  | generate1 (Tactic.Tac_ (_, f, id, f')) l (pt, (p, _)) =
neuper@42394
   331
      let
wneuper@59571
   332
        val (pt, c) = cappend_atomic pt p l (TermC.str2term f) (Tactic.Tac id) (TermC.str2term f', []) Complete
wneuper@59266
   333
      in
wneuper@59267
   334
        ((p,Res), c, FormKF f', pt)
wneuper@59266
   335
      end
walther@59819
   336
  | generate1 (Tactic.Subproblem' ((domID, pblID, metID), oris, hdl, fmz_, ctxt_specify, f))
walther@59810
   337
      (l as (_, ctxt)) (pt, (p, _)) =
wneuper@59266
   338
    let
walther@59819
   339
	    val (pt, c) = cappend_problem pt p l (fmz_, (domID, pblID, metID))
walther@59819
   340
	      (oris, (domID, pblID, metID), hdl, ctxt_specify)
walther@59854
   341
	    val f = Syntax.string_of_term (ThyC.thy2ctxt (Proof_Context.theory_of ctxt)) f
wneuper@59266
   342
    in
wneuper@59267
   343
      ((p, Pbl), c, FormKF f, pt)
wneuper@59266
   344
    end
walther@59811
   345
  | generate1 m' _ _ = error ("generate1: not impl.for " ^ Tactic.string_of m')
bonzai@41951
   346
neuper@42437
   347
fun generate_inconsistent_rew (subs_opt, thm') f' (is, ctxt) (pos as (p,_)) pt =
neuper@42434
   348
  let
wneuper@59266
   349
    val f = get_curr_formula (pt, pos)
wneuper@59266
   350
    val pos' as (p', _) = (lev_on p, Res)
wneuper@59266
   351
    val (pt, _) = case subs_opt of
walther@59828
   352
      NONE => cappend_atomic pt p' (is, ctxt) f
wneuper@59571
   353
        (Tactic.Rewrite thm') (f', []) Inconsistent
walther@59828
   354
    | SOME subs => cappend_atomic pt p' (is, ctxt) f
wneuper@59571
   355
        (Tactic.Rewrite_Inst (subs, thm')) (f', []) Inconsistent
wneuper@59266
   356
    val pt = update_branch pt p' TransitiveB
neuper@42437
   357
  in (pt, pos') end
neuper@42432
   358
walther@59828
   359
fun generate_hard _(*thy*) m' (p,p_) pt =
neuper@37906
   360
  let  
wneuper@59266
   361
    val p = case p_ of
wneuper@59266
   362
      Frm => p | Res => lev_on p
wneuper@59266
   363
    | _ => error ("generate_hard: call by " ^ pos'2str (p,p_))
walther@59810
   364
  in
walther@59846
   365
    generate1 m' (Istate_Def.empty, ContextC.empty) (pt, (p, p_))
walther@59810
   366
  end
neuper@37906
   367
walther@59760
   368
(* tacis are in reverse order from do_next/specify_: last = fst to insert *)
neuper@37906
   369
fun generate ([]: taci list) ptp = ptp
walther@59813
   370
  | generate tacis (pt, c, _: pos'(*!dropped!WN0504redesign generate/tacis?*)) = 
wneuper@59266
   371
    let
wneuper@59266
   372
      val (tacis', (_, tac_, (p, is))) = split_last tacis
walther@59813
   373
	    val (p',c',_,pt') = generate1 tac_ is (pt, p)
wneuper@59266
   374
    in
wneuper@59266
   375
      generate tacis' (pt', c@c', p')
wneuper@59266
   376
    end
neuper@37906
   377
wneuper@59266
   378
(* update pos in tacis for embedding by generate *)
wneuper@59266
   379
fun insert_pos (_: pos) [] = []
wneuper@59266
   380
  | insert_pos (p: pos) (((tac, tac_, (_, ist)): taci) :: tacis) = 
wneuper@59266
   381
    ((tac, tac_, ((p, Res), ist)): taci) :: (insert_pos (lev_on p) tacis)
neuper@37906
   382
wneuper@59571
   383
fun res_from_taci (_, Tactic.Rewrite' (_, _, _, _, _, _,(res, asm)), _) = (res, asm)
wneuper@59571
   384
  | res_from_taci (_, Tactic.Rewrite_Set' (_, _, _, _, (res, asm)), _) = (res, asm)
walther@59728
   385
  | res_from_taci (_, tac_, _) = error ("res_from_taci: called with" ^ Tactic.string_of tac_)
neuper@37906
   386
wneuper@59266
   387
(* embed the tacis created by a '_deriv'ation; sys.form <> input.form
wneuper@59266
   388
  tacis are in order, thus are reverted for generate *)
walther@59813
   389
fun embed_deriv tacis (pt, pos as (p, Frm)) =
neuper@37906
   390
  (*inform at Frm: replace the whole PrfObj by a Transitive-ProfObj FIXME?0402
neuper@37906
   391
    and transfer the istate (from _after_ compare_deriv) from Frm to Res*)
wneuper@59266
   392
    let
wneuper@59266
   393
      val (res, asm) = (res_from_taci o last_elem) tacis
wneuper@59266
   394
    	val (ist, ctxt) = case get_obj g_loc pt p of
wneuper@59266
   395
    	  (SOME (ist, ctxt), _) => (ist, ctxt)
wneuper@59266
   396
      | (NONE, _) => error "embed_deriv Frm: uncovered case get_obj"
wneuper@59266
   397
    	val form = get_obj g_form pt p
walther@59813
   398
      (*val p = lev_on p; ---------------only difference to (..,Res) below*)
walther@59737
   399
    	val tacis = (Tactic.Begin_Trans, Tactic.Begin_Trans' form, (pos, (Istate_Def.Uistate, ctxt))) ::
wneuper@59571
   400
    		(insert_pos ((lev_on o lev_dn) p) tacis) @ [(Tactic.End_Trans, Tactic.End_Trans' (res, asm),
wneuper@59266
   401
    			(pos_plus (length tacis) (lev_dn p, Res), (new_val res ist, ctxt)))]
wneuper@59269
   402
    	val {nrls, ...} = Specify.get_met (get_obj g_metID pt (par_pblobj pt p))
wneuper@59266
   403
    	val (pt, c, pos as (p, _)) = generate (rev tacis) (pt, [], (p, Res))
walther@59863
   404
    	val pt = update_tac pt p (Tactic.Derive (Rule_Set.rls2str nrls))
wneuper@59266
   405
    	val pt = update_branch pt p TransitiveB
wneuper@59266
   406
    in (c, (pt, pos: pos')) end
wneuper@59266
   407
  | embed_deriv tacis (pt, (p, Res)) =
wneuper@59266
   408
    (*inform at Res: append a Transitive-PrfObj FIXME?0402 other branch-types ?
wneuper@59266
   409
      and transfer the istate (from _after_ compare_deriv) from Res to new Res*)
neuper@37906
   410
    let val (res, asm) = (res_from_taci o last_elem) tacis
wneuper@59266
   411
    	val (ist, ctxt) = case get_obj g_loc pt p of
wneuper@59266
   412
    	  (_, SOME (ist, ctxt)) => (ist, ctxt)
wneuper@59266
   413
      | (_, NONE) => error "embed_deriv Frm: uncovered case get_obj"
wneuper@59266
   414
    	val (f, _) = get_obj g_result pt p
wneuper@59266
   415
    	val p = lev_on p(*---------------only difference to (..,Frm) above*);
walther@59737
   416
    	val tacis = (Tactic.Begin_Trans, Tactic.Begin_Trans' f, ((p, Frm), (Istate_Def.Uistate, ctxt))) ::
wneuper@59571
   417
    		(insert_pos ((lev_on o lev_dn) p) tacis) @ [(Tactic.End_Trans, Tactic.End_Trans' (res, asm), 
wneuper@59266
   418
    			(pos_plus (length tacis) (lev_dn p, Res), (new_val res ist, ctxt)))];
wneuper@59269
   419
    	val {nrls, ...} = Specify.get_met (get_obj g_metID pt (par_pblobj pt p))
wneuper@59266
   420
    	val (pt, c, pos as (p, _)) = generate (rev tacis) (pt, [], (p, Res))
walther@59863
   421
    	val pt = update_tac pt p (Tactic.Derive (Rule_Set.rls2str nrls))
wneuper@59266
   422
    	val pt = update_branch pt p TransitiveB
wneuper@59266
   423
    in (c, (pt, pos)) end
wneuper@59266
   424
  | embed_deriv _ _ = error "embed_deriv: uncovered definition"
wneuper@59266
   425
end