src/Tools/isac/Specify/p-spec.sml
author Walther Neuper <walther.neuper@jku.at>
Wed, 03 Feb 2021 16:39:44 +0100
changeset 60154 2ab0d1523731
parent 60132 2f94484d6637
child 60223 740ebee5948b
permissions -rw-r--r--
Isac's MethodC not shadowing Isabelle's Method
     1 (* Title:  Specify/input-calchead.sml
     2    Author: Walther Neuper
     3    (c) due to copyright terms
     4 
     5 This will be dropped at switch to Isabelle/PIDE .
     6 *)
     7 
     8 signature PRESENTATION_SPECIFICATION =
     9 sig
    10   type record
    11 (*/------- rename -------\*)
    12   datatype iitem =
    13       Find of TermC.as_string list
    14     | Given of TermC.as_string list
    15     | Relate of TermC.as_string list
    16   type imodel = iitem list
    17   type icalhd = Pos.pos' * TermC.as_string * imodel * Pos.pos_ * References.T
    18   val empty: icalhd
    19   val input_icalhd : Ctree.ctree -> icalhd -> Ctree.ctree * SpecificationC.T
    20 (* ---- for tests only: shifted from below to remove the Warning "unused" at fun.def. --------- *)
    21   (*  NONE *)
    22 (*/-------------------------------------------------------- ! aktivate for Test_Isac BEGIN ---\* )
    23   val appl_add': ThyC.id -> O_Model.T -> I_Model.T -> Model_Pattern.T ->
    24     string * TermC.as_string -> I_Model.single
    25   val appl_adds: ThyC.id -> O_Model.T -> I_Model.T -> Model_Pattern.T ->
    26     (string * TermC.as_string) list -> I_Model.T
    27   val eq7: ''a * ''b -> ''a * (''b * 'c) -> bool
    28   val filter_sep: ('a -> bool) -> 'a list -> 'a list * 'a list
    29   val fstr2itm_: theory -> (''a * (term * term)) list -> ''a * string ->
    30     int list * bool * ''a * I_Model.feedback (*I_Model.single'*)
    31   val imodel2fstr: iitem list -> (string * TermC.as_string) list
    32   val is_Par: 'a * 'b * 'c * 'd * I_Model.feedback -> bool (*I_Model.T?*)
    33   val is_e_ts: term list -> bool
    34   val itms2fstr: I_Model.single -> string * string
    35   val par2fstr: I_Model.single -> string * TermC.as_string
    36   val parsitm: theory -> I_Model.single -> I_Model.single
    37   val unknown_expl: ThyC.id -> (''a * (term * term)) list -> (*Model_Pattern.T?*)
    38     (''a * string) list ->
    39       (int * int list * bool * ''a * Model_Def.i_model_feedback) list (*I_Model.T?*)
    40 ( *\--- ! aktivate for Test_Isac END ----------------------------------------------------------/*)
    41 (*\------- rename -------/*)
    42 end
    43 
    44 (**)
    45 structure P_Spec(**): PRESENTATION_SPECIFICATION(**) =
    46 struct
    47 (**)
    48 
    49   type record = {thy_id: ThyC.id, pbl_id: Problem.id,           (* headline of Problem *)
    50     givens: TermC.as_string list, wheres: TermC.as_string list, (* Model.T             *)
    51       find: TermC.as_string, relates: TermC.as_string list,
    52     rthy_id: ThyC.id, rpbl_id: Problem.id, rmet_id: MethodC.id}  (* References.T        *)
    53 
    54 fun flattup2 (a, (b ,c, d, e)) = (a, b, c, d, e)
    55 
    56 (** handle an input P_Specific'action **)
    57 
    58 datatype iitem = 
    59   Given of TermC.as_string list
    60 (*Where is still not input*) 
    61 | Find  of TermC.as_string list
    62 | Relate  of TermC.as_string list
    63 
    64 type imodel = iitem list
    65 
    66 type icalhd =
    67   Pos.pos' *         (* the position in Ctree              *) 
    68   TermC.as_string *  (* the headline shown on Calc.T       *)
    69   imodel *           (* the model                          *)
    70   Pos.pos_ *         (* model belongs to Problem or MethodC *)
    71   References.T;      (* into Know_Store                    *)
    72 val empty = (Pos.e_pos', "", [Given [""]], Pos.Pbl, References.empty)
    73 
    74 (* re-parse itms with a new thy and prepare for checking with ori list *)
    75 fun parsitm dI (itm as (i, v, _, f, I_Model.Cor ((d, ts), _))) =
    76     (let val t = Input_Descript.join (d, ts)
    77      val _ = (UnparseC.term_in_thy dI t)
    78      (*t his ^^^^^^^^^^^^ should raise the exn on unability of re-parsing dts *)
    79     in itm end
    80     handle _ => (i, v, false, f, I_Model.Syn (UnparseC.term TermC.empty (*t  ..(t) has not been declared*))))
    81   | parsitm dI (i, v, b, f, I_Model.Syn str) =
    82     (let val _ = (Thm.term_of o the o (TermC.parse dI)) str
    83     in (i, v, b ,f, I_Model.Par str) end
    84     handle _ => (i, v, b, f, I_Model.Syn str))
    85   | parsitm dI (i, v, b, f, I_Model.Typ str) =
    86     (let val _ = (Thm.term_of o the o (TermC.parse dI)) str
    87      in (i, v, b, f, I_Model.Par str) end
    88      handle _ => (i, v, b, f, I_Model.Syn str))
    89   | parsitm dI (itm as (i, v, _, f, I_Model.Inc ((d, ts), _))) =
    90     (let val t = Input_Descript.join (d,ts);
    91 	       val _ = UnparseC.term_in_thy dI t;
    92      (*this    ^ should raise the exn on unability of re-parsing dts*)
    93      in itm end
    94      handle _ => (i, v, false, f, I_Model.Syn (UnparseC.term TermC.empty (*t  ..(t) has not been declared*))))
    95   | parsitm dI (itm as (i, v, _, f, I_Model.Sup (d, ts))) =
    96     (let val t = Input_Descript.join (d,ts);
    97 	       val _ = UnparseC.term_in_thy dI t;
    98      (*this    ^ should raise the exn on unability of re-parsing dts*)
    99     in itm end
   100     handle _ => (i, v, false, f, I_Model.Syn (UnparseC.term TermC.empty (*t  ..(t) has not been declared*))))
   101   | parsitm dI (itm as (i, v, _, f, I_Model.Mis (d, t'))) =
   102     (let val t = d $ t';
   103 	       val _ = UnparseC.term_in_thy dI t;
   104      (*this    ^ should raise the exn on unability of re-parsing dts*)
   105     in itm end
   106     handle _ => (i, v, false, f, I_Model.Syn (UnparseC.term TermC.empty (*t  ..(t) has not been declared*))))
   107   | parsitm dI (itm as (_, _, _, _, I_Model.Par _)) = 
   108     raise ERROR ("parsitm (" ^ I_Model.single_to_string (ThyC.to_ctxt dI) itm ^ "): Par should be internal");
   109 
   110 (*separate a list to a pair of elements that do NOT satisfy the predicate,
   111  and of elements that satisfy the predicate, i.e. (false, true)*)
   112 fun filter_sep pred xs =
   113   let
   114     fun filt ab [] = ab
   115       | filt (a, b) (x :: xs) =
   116         if pred x 
   117 			  then filt (a, b @ [x]) xs 
   118 			  else filt (a @ [x], b) xs
   119   in filt ([], []) xs end;
   120 fun is_Par (_, _, _, _, I_Model.Par _) = true
   121   | is_Par _ = false;
   122 
   123 fun is_e_ts [] = true
   124   | is_e_ts [Const ("List.list.Nil", _)] = true
   125   | is_e_ts _ = false;
   126 
   127 (* WN.9.11.03 copied from fun appl_add *)
   128 fun appl_add' dI oris ppc pbt (sel, ct) = 
   129   let 
   130      val ctxt = ThyC.get_theory dI |> ThyC.to_ctxt;
   131   in
   132     case TermC.parseNEW ctxt ct of
   133 	    NONE => (0, [], false, sel, I_Model.Syn ct)
   134 	  | SOME t =>
   135 	    (case O_Model.is_known ctxt sel oris t of
   136         ("", ori', all) =>
   137           (case I_Model.is_notyet_input ctxt ppc all ori' pbt of
   138             ("",itm)  => itm
   139           | (msg,_) => raise ERROR ("appl_add': " ^ msg))
   140       | (_, (i, v, _, d, ts), _) =>
   141         if is_e_ts ts
   142         then (i, v, false, sel, I_Model.Inc ((d, ts), (TermC.empty, [])))
   143         else (i, v, false, sel, I_Model.Sup (d, ts)))
   144    end
   145 
   146 (* generate preliminary itm_ from a strin (with field "#Given" etc.) *)
   147 fun eq7 (f, d) (f', (d', _)) = f = f' andalso d = d';
   148 fun fstr2itm_ thy pbt (f, str) =
   149   let
   150     val topt = TermC.parse thy str
   151   in
   152     case topt of
   153       NONE => ([], false, f, I_Model.Syn str)
   154     | SOME ct => 
   155 	    let
   156 	      val (d, ts) = (Input_Descript.split o Thm.term_of) ct
   157 	      val popt = find_first (eq7 (f, d)) pbt
   158 	    in
   159 	      case popt of
   160 	        NONE => ([1](*??*), true(*??*), f, I_Model.Sup (d, ts))
   161 	      | SOME (f, (d, id)) => ([1], true, f, I_Model.Cor ((d, ts), (id, ts))) 
   162 	    end
   163   end
   164 
   165 (*.input into empty PblObj, i.e. empty fmz+origin (unknown example).*)
   166 fun unknown_expl dI pbt selcts =
   167   let
   168     val thy = ThyC.get_theory dI
   169     val its_ = map (fstr2itm_ thy pbt) selcts (*([1],true,"#Given",Cor (...))*)
   170     val its = O_Model.add_id its_ 
   171   in map flattup2 its end
   172 
   173 (* WN.11.03 for input_icalhd, ~ specify_additem for Add_Given/_Find/_Relation
   174    appl_add': generate 1 item 
   175    appl_add' . is_known: parse, get data from oris (vats, all (elems if list)..)
   176    appl_add' . is_notyet_input: compare with items in model already input
   177    insert_ppc': insert this 1 item*)
   178 fun appl_adds dI [] _ pbt selcts = unknown_expl dI pbt selcts
   179     (*already present itms in model are being overwritten*)
   180   | appl_adds _ _ ppc _ [] = ppc
   181   | appl_adds dI oris ppc pbt (selct :: ss) =
   182     let val itm = appl_add' dI oris ppc pbt selct;
   183     in appl_adds dI oris (I_Model.add itm ppc) pbt ss end
   184 
   185 fun par2fstr (_, _, _, f, I_Model.Par s) = (f, s)
   186   | par2fstr itm = raise ERROR ("par2fstr: called with " ^ I_Model.single_to_string (ThyC.id_to_ctxt "Isac_Knowledge") itm)
   187 fun itms2fstr (_, _, _, f, I_Model.Cor ((d, ts), _)) = (f, Input_Descript.join''' (d, ts))
   188   | itms2fstr (_, _, _, f, I_Model.Syn str) = (f, str)
   189   | itms2fstr (_, _, _, f, I_Model.Typ str) = (f, str)
   190   | itms2fstr (_, _, _, f, I_Model.Inc ((d, ts), _)) = (f, Input_Descript.join''' (d,ts))
   191   | itms2fstr (_, _, _, f, I_Model.Sup (d, ts)) = (f, Input_Descript.join''' (d, ts))
   192   | itms2fstr (_, _, _, f, I_Model.Mis (d, t)) = (f, UnparseC.term (d $ t))
   193   | itms2fstr (itm as (_, _, _, _, I_Model.Par _)) = 
   194     raise ERROR ("parsitm (" ^ I_Model.single_to_string (ThyC.id_to_ctxt "Isac_Knowledge") itm ^ "): Par should be internal");
   195 
   196 fun imodel2fstr iitems = 
   197   let 
   198     fun xxx is [] = is
   199 	    | xxx is ((Given strs)::iis) = xxx (is @ (map (pair "#Given") strs)) iis
   200 	    | xxx is ((Find strs)::iis) = xxx (is @ (map (pair "#Find") strs)) iis
   201 	    | xxx is ((Relate strs)::iis) = xxx (is @ (map (pair "#Relate") strs)) iis
   202   in xxx [] iitems end;
   203 
   204 (* input a calchead, WN110505 "prep_oris -> (_, ctxt)" not handled properly *)
   205 fun input_icalhd pt (((p, _), hdf, imodel, Pos.Pbl, spec as (dI, pI, mI)) : icalhd) =
   206     let
   207 		  val (fmz, fmz_, oris, ospec, hdf', sspec, sdI, spI, smI, probl, meth) = case Ctree.get_obj I pt p of
   208 		    Ctree.PblObj {fmz = fmz as (fmz_,_), origin = (oris, ospec, hdf'), 
   209 		      spec = sspec as (sdI, spI, smI), probl, meth, ...}
   210         => (fmz, fmz_, oris, ospec, hdf', sspec, sdI, spI, smI, probl, meth)
   211       | _ => raise ERROR "input_icalhd: uncovered case of get_obj I pt p"
   212     in if CAS_Cmd.is_from hdf fmz then the (CAS_Cmd.input (TermC.str2term hdf)) 
   213        else        (*hacked WN0602 ~~~            ~~~~~~~~~,   ..dropped !*)
   214          let val (pos_, pits, mits) = 
   215 	         if dI <> sdI
   216 	         then let val its = map (parsitm (ThyC.get_theory dI)) probl;
   217 			            val (its, trms) = filter_sep is_Par its;
   218 			            val pbt = (#ppc o Problem.from_store) (#2 (References.select ospec sspec))
   219 		            in (Pos.Pbl, appl_adds dI oris its pbt  (map par2fstr trms), meth) end 
   220            else
   221              if pI <> spI 
   222 	           then if pI = snd3 ospec then (Pos.Pbl, probl, meth) 
   223                   else
   224 		                let val pbt = (#ppc o Problem.from_store) pI
   225 			                val dI' = #1 (References.select ospec spec)
   226 			                val oris = if pI = #2 ospec then oris 
   227 				                         else O_Model.init fmz_(ThyC.get_theory"Isac_Knowledge") pbt(* |> #1*);
   228 		                in (Pos.Pbl, appl_adds dI' oris probl pbt 
   229 				              (map itms2fstr probl), meth) end 
   230              else if mI <> smI (*FIXME.WN0311: what if probl is incomplete?!*)
   231 	                then let val met = (#ppc o MethodC.from_store) mI
   232 		                     val mits = I_Model.complete oris probl meth met
   233 		                   in if foldl and_ (true, map #3 mits)
   234 		                      then (Pos.Pbl, probl, mits) else (Pos.Met, probl, mits) 
   235 		                   end 
   236                   else (Pos.Pbl, appl_adds (#1 (References.select ospec spec)) oris [(*!!!*)]
   237 			                  ((#ppc o Problem.from_store) (#2 (References.select ospec spec)))
   238 			                  (imodel2fstr imodel), meth)
   239 	         val pt = Ctree.update_spec pt p spec;
   240          in if pos_ = Pos.Pbl
   241 	          then let val {prls,where_,...} = Problem.from_store (#2 (References.select ospec spec))
   242 		               val (_, pre) = Pre_Conds.check prls where_ pits 0
   243 	               in (Ctree.update_pbl pt p pits,
   244 		                 (SpecificationC.complete pits pre spec, Pos.Pbl, hdf', pits, pre, spec): SpecificationC.T) 
   245                  end
   246 	           else let val {prls,pre,...} = MethodC.from_store (#3 (References.select ospec spec))
   247 		                val (_, pre) = Pre_Conds.check prls pre mits 0
   248 	                in (Ctree.update_met pt p mits,
   249 		                  (SpecificationC.complete mits pre spec, Pos.Met, hdf', mits, pre, spec) : SpecificationC.T)
   250                   end
   251          end 
   252     end
   253   | input_icalhd _ (_, _, _, _(*Met*), _) = raise ERROR "input_icalhd Met not impl."
   254 
   255 (**)end (**)