src/Tools/isac/Interpret/inform.sml
author Walther Neuper <wneuper@ist.tugraz.at>
Sat, 12 Nov 2016 17:21:43 +0100
changeset 59257 a1daf71787b1
parent 59253 f0bb15a046ae
child 59262 0ddb3f300cce
permissions -rw-r--r--
--- polished LUCAS_INTERPRETER

Notes
# "---" marks changesets where Test_Isac does not work
# outcommented tests in script.sml moved from src/ to test/
     1 (* Handle user-input during the specify- and the solve-phase. 
     2    author: Walther Neuper
     3    0603
     4    (c) due to copyright terms
     5 
     6 use"ME/inform.sml";
     7 use"inform.sml";
     8 *)
     9 
    10 signature INFORM =
    11   sig
    12 
    13     type icalhd
    14 
    15    (* type iitem *)
    16     datatype
    17       iitem =
    18           Find of cterm' list
    19         | Given of cterm' list
    20         | Relate of cterm' list
    21     type imodel
    22     val imodel2fstr : iitem list -> (string * cterm') list
    23 
    24     
    25     val Isac : 'a -> theory
    26     val appl_add' :
    27        theory' ->
    28        SpecifyTools.ori list ->
    29        SpecifyTools.itm list ->
    30        ('a * (Term.term * Term.term)) list ->
    31        string * cterm' -> SpecifyTools.itm
    32   (*  val appl_adds :
    33        theory' ->
    34        SpecifyTools.ori list ->
    35        SpecifyTools.itm list ->
    36        (string * (Term.term * Term.term)) list ->
    37        (string * string) list -> SpecifyTools.itm list *)
    38    (* val cas_input : string -> ptree * ocalhd *)
    39    (* val cas_input_ :
    40        spec ->
    41        (Term.term * Term.term list) list ->
    42        pblID * SpecifyTools.itm list * metID * SpecifyTools.itm list *
    43        (bool * Term.term) list  *)
    44     val compare_step :
    45        calcstate' -> Term.term -> string * calcstate'
    46    (* val concat_deriv :
    47        'a * ((Term.term * Term.term) list -> Term.term * Term.term -> bool)
    48        ->
    49        rls ->
    50        rule list ->
    51        Term.term ->
    52        Term.term ->
    53        bool * (Term.term * rule * (Term.term * Term.term list)) list *)
    54     val dropwhile' :   (* systest/auto-inform.sml *)
    55        ('a -> 'b -> bool) -> 'a list -> 'b list -> 'a list * 'b list
    56    (* val dtss2itm_ :
    57        pbt_ list ->
    58        Term.term * Term.term list ->
    59        int list * bool * string * SpecifyTools.itm_ *)
    60    (* val e_icalhd : icalhd *)
    61     val eq7 : ''a * ''b -> ''a * (''b * 'c) -> bool
    62     val equal : ''a -> ''a -> bool
    63    (* val filter_dsc :
    64        SpecifyTools.ori list -> SpecifyTools.itm -> SpecifyTools.ori list *)
    65    (* val filter_sep : ('a -> bool) -> 'a list -> 'a list * 'a list *)
    66    (* val flattup2 : 'a * ('b * 'c * 'd * 'e) -> 'a * 'b * 'c * 'd * 'e *)
    67    (* val fstr2itm_ :
    68        theory ->
    69        (''a * (Term.term * Term.term)) list ->
    70        ''a * string -> int list * bool * ''a * SpecifyTools.itm_ *)
    71     val inform :
    72        calcstate' -> cterm' -> string * calcstate'   
    73     val input_icalhd : ptree -> icalhd -> ptree * ocalhd
    74    (* val is_Par : SpecifyTools.itm -> bool *)
    75    (* val is_casinput : cterm' -> fmz -> bool *)
    76    (* val is_e_ts : Term.term list -> bool *)
    77    (* val itms2fstr : SpecifyTools.itm -> string * string *)
    78    (* val mk_tacis :
    79        rew_ord' * 'a ->
    80        rls ->
    81        Term.term * rule * (Term.term * Term.term list) ->
    82        tac * tac_ * (pos' * istate)      *)
    83     val oris2itms :
    84        'a -> int -> SpecifyTools.ori list -> SpecifyTools.itm list
    85    (* val par2fstr : SpecifyTools.itm -> string * cterm' *)
    86    (* val parsitm : theory -> SpecifyTools.itm -> SpecifyTools.itm *)
    87     val rev_deriv' : 'a * rule * ('b * 'c) -> 'b * rule * ('a * 'c)
    88    (* val unknown_expl :
    89        theory' ->
    90        (string * (Term.term * Term.term)) list ->
    91        (string * string) list -> SpecifyTools.itm list *)
    92   end
    93 
    94 
    95 
    96 
    97 
    98 
    99 (***. handle an input calc-head .***)
   100 
   101 (*------------------------------------------------------------------(**)
   102 structure inform :INFORM =
   103 struct
   104 (**)------------------------------------------------------------------*)
   105 
   106 datatype iitem = 
   107   Given of cterm' list
   108 (*Where is never input*) 
   109 | Find  of cterm' list
   110 | Relate  of cterm' list;
   111 
   112 type imodel = iitem list;
   113 
   114 (*calc-head as input*)
   115 type icalhd =
   116      pos' *     (*the position of the calc-head in the calc-tree*) 
   117      cterm' *   (*the headline*)
   118      imodel *   (*the model (without Find) of the calc-head*)
   119      pos_ *     (*model belongs to Pbl or Met*)
   120      spec;      (*specification: domID, pblID, metID*)
   121 val e_icalhd = (e_pos', "", [Given [""]], Pbl, e_spec): icalhd;
   122 
   123 fun is_casinput (hdf: cterm') ((fmz_, spec): fmz) =
   124     hdf <> "" andalso fmz_ = [] andalso spec = e_spec;
   125 
   126 (*.handle an input as into an algebra system.*)
   127 fun dtss2itm_ ppc (d, ts) =
   128     let val (f, (d, id)) = the (find_first ((curry op= d) o 
   129 					    (#1: (term * term) -> term) o
   130 					    (#2: pbt_ -> (term * term))) ppc)
   131     in ([1], true, f, Cor ((d, ts), (id, ts))) end;
   132 
   133 fun flattup2 (a,(b,c,d,e)) = (a,b,c,d,e);
   134 
   135 fun cas_input_ ((dI,pI,mI): spec) dtss = (*WN110515 reconsider thy..ctxt*)
   136   let
   137     val thy = assoc_thy dI
   138 	  val {ppc, ...} = get_pbt pI
   139 	  val its_ = map (dtss2itm_ ppc) dtss (*([1],true,"#Given",Cor (...))*)
   140 	  val its = add_id its_
   141 	  val pits = map flattup2 its
   142 	  val (pI, mI) =
   143       if mI <> ["no_met"]
   144       then (pI, mI)
   145 		  else
   146         case refine_pbl thy pI pits of
   147 			    SOME (pI,_) => (pI, (hd o #met o get_pbt) pI)
   148 			  | NONE => (pI, (hd o #met o get_pbt) pI)
   149 	  val {ppc, pre, prls, ...} = get_met mI
   150 	  val its_ = map (dtss2itm_ ppc) dtss (*([1],true,"#Given",Cor (...))*)
   151 	  val its = add_id its_
   152 	  val mits = map flattup2 its
   153 	  val pre = check_preconds thy prls pre mits
   154     val ctxt = e_ctxt (*WN110515 cas_input_ DOESNT WORK*)
   155   in (pI, pits: itm list, mI, mits: itm list, pre, ctxt) end;
   156 
   157 
   158 (* check if the input term is a CAScmd and return a ptree with a _complete_ calchead *)
   159 fun cas_input hdt =
   160   let val (h,argl) = strip_comb hdt
   161   in
   162     case assoc_cas (assoc_thy "Isac") h of
   163      NONE => NONE
   164    | SOME (spec as (dI,_,_), argl2dtss) =>
   165 	      let
   166           val dtss = argl2dtss argl
   167 	        val (pI, pits, mI, mits, pre, ctxt) = cas_input_ spec dtss
   168 	        val spec = (dI, pI, mI)
   169 	        val (pt,_) = 
   170 		        cappend_problem e_ptree [] (e_istate, e_ctxt) ([], e_spec) ([], e_spec, hdt)
   171 	        val pt = update_spec pt [] spec
   172 	        val pt = update_pbl pt [] pits
   173 	        val pt = update_met pt [] mits
   174 	        val pt = update_ctxt pt [] ctxt
   175 	      in SOME (pt, (true, Met, hdt, mits, pre, spec) : ocalhd) end
   176   end;
   177 
   178 (*lazy evaluation for (Thy_Info.get_theory "Isac")*)
   179 fun Isac _  = assoc_thy "Isac";
   180 
   181 (*re-parse itms with a new thy and prepare for checking with ori list*)
   182 fun parsitm dI (itm as (i,v,b,f, Cor ((d,ts),_)):itm) =
   183     (let
   184       val t = comp_dts (d,ts);
   185       val s = term_to_string''' dI t;
   186        (*this    ^ should raise the exn on unability of re-parsing dts*)
   187     in itm end
   188     handle _ => ((i,v,false,f, Syn (term2str t)):itm))
   189   | parsitm dI (itm as (i,v,b,f, Syn str)) =
   190     (let val t = (Thm.term_of o the o (parse dI)) str
   191     in (i,v,b,f, Par str) end
   192     handle _ => (i,v,b,f, Syn str))
   193   | parsitm dI (itm as (i,v,b,f, Typ str)) =
   194     (let val t = (Thm.term_of o the o (parse dI)) str
   195      in (i,v,b,f, Par str) end
   196      handle _ => (i,v,b,f, Syn str))
   197   | parsitm dI (itm as (i,v,_,f, Inc ((d,ts),_))) =
   198     (let val t = comp_dts (d,ts);
   199 	       val s = term_to_string''' dI t;
   200      (*this    ^ should raise the exn on unability of re-parsing dts*)
   201      in itm end
   202      handle _ => ((i,v,false,f, Syn (term2str t)):itm))
   203   | parsitm dI (itm as (i,v,_,f, Sup (d,ts))) =
   204     (let val t = comp_dts (d,ts);
   205 	       val s = term_to_string''' dI t;
   206      (*this    ^ should raise the exn on unability of re-parsing dts*)
   207     in itm end
   208     handle _ => ((i,v,false,f, Syn (term2str t)):itm))
   209   | parsitm dI (itm as (i,v,_,f, Mis (d,t'))) =
   210     (let val t = d $ t';
   211 	       val s = term_to_string''' dI t;
   212      (*this    ^ should raise the exn on unability of re-parsing dts*)
   213     in itm end
   214     handle _ => ((i,v,false,f, Syn (term2str t)):itm))
   215   | parsitm dI (itm as (i,v,_,f, Par _)) = 
   216     error ("parsitm (" ^ itm2str_ (thy2ctxt dI) itm ^ "): Par should be internal");
   217 
   218 (*separate a list to a pair of elements that do NOT satisfy the predicate,
   219  and of elements that satisfy the predicate, i.e. (false, true)*)
   220 fun filter_sep pred xs =
   221   let fun filt ab [] = ab
   222         | filt (a,b) (x :: xs) = if pred x 
   223 				 then filt (a,b@[x]) xs 
   224 				 else filt (a@[x],b) xs
   225   in filt ([],[]) xs end;
   226 fun is_Par ((_,_,_,_,Par _):itm) = true
   227   | is_Par _ = false;
   228 
   229 fun is_e_ts [] = true
   230   | is_e_ts [Const ("List.list.Nil", _)] = true
   231   | is_e_ts _ = false;
   232 
   233 (*WN.9.11.03 copied from fun appl_add (in modspec.sml)*)
   234 (* val (sel,ct) = selct;
   235    val (dI, oris, ppc, pbt, (sel, ct))=
   236        (#1 (some_spec ospec spec), oris, []:itm list,
   237 	((#ppc o get_pbt) (#2 (some_spec ospec spec))),
   238 	hd (imodel2fstr imodel));
   239    *)
   240 fun appl_add' dI oris ppc pbt (sel, ct) = 
   241     let 
   242       val ctxt = assoc_thy dI |> thy2ctxt;
   243     in case parseNEW ctxt ct of
   244 	   NONE => (0,[],false,sel, Syn ct):itm
   245 	 | SOME t => (case is_known ctxt sel oris t of
   246          ("", ori', all) =>
   247            (case is_notyet_input ctxt ppc all ori' pbt of
   248 	         ("",itm)  => itm
   249 	       | (msg,_) => error ("appl_add': " ^ msg))
   250      | (_, (i, v, _, d, ts), _) => if is_e_ts ts then
   251          (i, v, false, sel, Inc ((d, ts), (e_term, []))) else
   252          (i, v, false, sel, Sup (d, ts)))
   253     end;
   254 
   255 (*.generate preliminary itm_ from a strin (with field "#Given" etc.).*)
   256 (* val (f, str) = hd selcts;
   257    *)
   258 fun eq7 (f, d) (f', (d', _)) = f=f' andalso d=d';
   259 fun fstr2itm_ thy pbt (f, str) =
   260     let val topt = parse thy str
   261     in case topt of
   262 	   NONE => ([], false, f, Syn str)
   263 	 | SOME ct => 
   264 (* val SOME ct = parse thy str;
   265    *)
   266 	   let val (d,ts) = (split_dts o Thm.term_of) ct
   267 	       val popt = find_first (eq7 (f,d)) pbt
   268 	   in case popt of
   269 		  NONE => ([1](*??*), true(*??*), f, Sup (d,ts))
   270 		| SOME (f, (d, id)) => ([1], true, f, Cor ((d,ts), (id, ts))) 
   271 	   end
   272     end; 
   273 
   274 
   275 (*.input into empty PblObj, i.e. empty fmz+origin (unknown example).*)
   276 fun unknown_expl dI pbt selcts =
   277   let
   278     val thy = assoc_thy dI
   279     val its_ = map (fstr2itm_ thy pbt) selcts (*([1],true,"#Given",Cor (...))*)
   280     val its = add_id its_ 
   281 in (map flattup2 its): itm list end;
   282 
   283 
   284 
   285 
   286 (*WN.11.03 for input_icalhd, ~ specify_additem for Add_Given/_Find/_Relation
   287  appl_add': generate 1 item 
   288  appl_add' . is_known: parse, get data from oris (vats, all (elems if list)..)
   289  appl_add' . is_notyet_input: compare with items in model already input
   290  insert_ppc': insert this 1 item*)
   291 (* val (dI,oris,ppc,pbt,selcts) =((#1 (some_spec ospec spec)),oris,[(*!!*)],
   292 			       ((#ppc o get_pbt) (#2 (some_spec ospec spec))),
   293 			       (imodel2fstr imodel));
   294    *)
   295 fun appl_adds dI [] _ pbt selcts = unknown_expl dI pbt selcts
   296   (*already present itms in model are being overwritten*)
   297   | appl_adds dI oris ppc pbt [] = ppc
   298   | appl_adds dI oris ppc pbt (selct::ss) =
   299     (* val selct = (sel, string_of_cterm ct);
   300        *)
   301     let val itm = appl_add' dI oris ppc pbt selct;
   302     in appl_adds dI oris (insert_ppc' itm ppc) pbt ss end;
   303 (* val (dI, oris, ppc, pbt, selct::ss) = 
   304        (dI, pors, probl, ppc, map itms2fstr probl);
   305    ...vvv
   306    *)
   307 (* val (dI, oris, ppc, pbt, (selct::ss))=
   308        (#1 (some_spec ospec spec), oris, []:itm list,
   309 	((#ppc o get_pbt) (#2 (some_spec ospec spec))),(imodel2fstr imodel));
   310    val iii = appl_adds dI oris ppc pbt (selct::ss); 
   311    tracing(itms2str_ thy iii);
   312 
   313  val itm = appl_add' dI oris ppc pbt selct;
   314  val ppc = insert_ppc' itm ppc;
   315 
   316  val _::selct::ss = (selct::ss);
   317  val itm = appl_add' dI oris ppc pbt selct;
   318  val ppc = insert_ppc' itm ppc;
   319 
   320  val _::selct::ss = (selct::ss);
   321  val itm = appl_add' dI oris ppc pbt selct;
   322  val ppc = insert_ppc' itm ppc;
   323  tracing(itms2str_ thy ppc);
   324 
   325  val _::selct::ss = (selct::ss);
   326  val itm = appl_add' dI oris ppc pbt selct;
   327  val ppc = insert_ppc' itm ppc;
   328    *)
   329 
   330 
   331 fun oris2itms _ _ ([]:ori list) = ([]:itm list)
   332   | oris2itms pbt vat ((i,v,f,d,ts)::(os: ori list)) =
   333     if member op = vat v 
   334     then (i,v,true,f,Cor ((d,ts),(e_term,[])))::(oris2itms pbt vat os)
   335     else oris2itms pbt vat os;
   336 
   337 fun filter_dsc oris itm = 
   338     filter_out ((curry op= ((d_in o #5) (itm:itm))) o 
   339 		(#4:ori -> term)) oris;
   340 
   341 
   342 
   343 
   344 fun par2fstr ((_,_,_,f, Par s):itm) = (f, s)
   345   | par2fstr itm = error ("par2fstr: called with " ^
   346 			      itm2str_ (thy2ctxt' "Isac") itm);
   347 fun itms2fstr ((_,_,_,f, Cor ((d,ts),_)):itm) = (f, comp_dts'' (d,ts))
   348   | itms2fstr (_,_,_,f, Syn str) = (f, str)
   349   | itms2fstr (_,_,_,f, Typ str) = (f, str)
   350   | itms2fstr (_,_,_,f, Inc ((d,ts),_)) = (f, comp_dts'' (d,ts))
   351   | itms2fstr (_,_,_,f, Sup (d,ts)) = (f, comp_dts'' (d,ts))
   352   | itms2fstr (_,_,_,f, Mis (d,t)) = (f, term2str (d $ t))
   353   | itms2fstr (itm as (_,_,_,f, Par _)) = 
   354     error ("parsitm ("^itm2str_ (thy2ctxt' "Isac") itm ^
   355 		 "): Par should be internal");
   356 
   357 fun imodel2fstr iitems = 
   358   let 
   359     fun xxx is [] = is
   360 	    | xxx is ((Given strs)::iis) = xxx (is @ (map (pair "#Given") strs)) iis
   361 	    | xxx is ((Find strs)::iis) = xxx (is @ (map (pair "#Find") strs)) iis
   362 	    | xxx is ((Relate strs)::iis) = xxx (is @ (map (pair "#Relate") strs)) iis
   363   in xxx [] iitems end;
   364 
   365 (* input a calchead, WN110505 "prep_oris -> (_, ctxt)" not handled properly *)
   366 fun input_icalhd pt (((p,_), hdf, imodel, Pbl, spec as (dI,pI,mI)):icalhd) =
   367     let val PblObj {fmz = fmz as (fmz_,_), origin = (oris, ospec, hdf'), 
   368 		      spec = sspec as (sdI,spI,smI), probl, meth, ...} = get_obj I pt p;
   369     in if is_casinput hdf fmz then the (cas_input (str2term hdf)) 
   370        else        (*hacked WN0602 ~~~            ~~~~~~~~~,   ..dropped !*)
   371          let val (pos_, pits, mits) = 
   372 	         if dI <> sdI
   373 	         then let val its = map (parsitm (assoc_thy dI)) probl;
   374 			            val (its, trms) = filter_sep is_Par its;
   375 			            val pbt = (#ppc o get_pbt) (#2(some_spec ospec sspec));
   376 		            in (Pbl, appl_adds dI oris its pbt  (map par2fstr trms), meth) end 
   377            else if pI <> spI 
   378 	              then if pI = snd3 ospec then (Pbl, probl, meth) 
   379                      else
   380 		                   let val pbt = (#ppc o get_pbt) pI
   381 			                   val dI' = #1 (some_spec ospec spec)
   382 			                   val oris = if pI = #2 ospec then oris 
   383 				                            else prep_ori fmz_(assoc_thy"Isac") pbt |> #1;
   384 		                   in (Pbl, appl_adds dI' oris probl pbt 
   385 				                 (map itms2fstr probl), meth) end 
   386                 else if mI <> smI (*FIXME.WN0311: what if probl is incomplete?!*)
   387 	                   then let val met = (#ppc o get_met) mI
   388 		                        val mits = complete_metitms oris probl meth met
   389 		                      in if foldl and_ (true, map #3 mits)
   390 		                         then (Pbl, probl, mits) else (Met, probl, mits) 
   391 		                      end 
   392                      else (Pbl, appl_adds (#1 (some_spec ospec spec)) oris [(*!!!*)]
   393 			                     ((#ppc o get_pbt) (#2 (some_spec ospec spec)))
   394 			                     (imodel2fstr imodel), meth);
   395 	         val pt = update_spec pt p spec;
   396          in if pos_ = Pbl
   397 	          then let val {prls,where_,...} = get_pbt (#2 (some_spec ospec spec))
   398 		               val pre =check_preconds(assoc_thy"Isac")prls where_ pits
   399 	               in (update_pbl pt p pits,
   400 		                 (ocalhd_complete pits pre spec, Pbl, hdf', pits, pre, spec):ocalhd) 
   401                  end
   402 	           else let val {prls,pre,...} = get_met (#3 (some_spec ospec spec))
   403 		                val pre = check_preconds (assoc_thy"Isac") prls pre mits
   404 	                in (update_met pt p mits,
   405 		                  (ocalhd_complete mits pre spec, Met, hdf', mits, pre, spec):ocalhd)
   406                   end
   407          end 
   408     end
   409   | input_icalhd pt ((p,_), hdf, imodel, _(*Met*), spec as (dI,pI,mI)) =
   410     error "input_icalhd Met not impl.";
   411 
   412 
   413 (***. handle an input formula .***)
   414 (*
   415 Untersuchung zur Formeleingabe (appendFormula, replaceFormla) zu einer Anregung von Alan Krempler:
   416 Welche RICHTIGEN Formeln koennen NICHT abgeleitet werden, 
   417 wenn Abteilungen nur auf gleichem Level gesucht werden ?
   418 WN.040216 
   419 
   420 Beispiele zum Equationsolver von Richard Lang aus /src/sml/kbtest/rlang.sml
   421 
   422 ------------------------------------------------------------------------------
   423 "Schalk I s.87 Bsp 52a ((5*x)/(x - 2) - x/(x+2)=4)";
   424 ------------------------------------------------------------------------------
   425 1. "5 * x / (x - 2) - x / (x + 2) = 4"
   426 ...
   427 4. "12 * x + 4 * x ^^^ 2 = 4 * (-4 + x ^^^ 2)",Subproblem["normalize", "poly"..
   428 ...
   429 4.3. "16 + 12 * x = 0", Subproblem["degree_1", "polynomial", "univariate"..
   430 ...
   431 4.3.3. "[x = -4 / 3]")), Check_elementwise "Assumptions"
   432 ...
   433 "[x = -4 / 3]"
   434 ------------------------------------------------------------------------------
   435 (1)..(6): keine 'richtige' Eingabe kann abgeleitet werden, die einen Summanden auf die andere Seite verschiebt [Ableitung ware in 4.3.n]
   436 
   437 (4.1)..(4.3): keine 'richtige' Eingabe kann abgeleitet werden, die einen Summanden auf die andere Seite verschiebt [Ableitung ware in 4.3.n]
   438 ------------------------------------------------------------------------------
   439 
   440 
   441 ------------------------------------------------------------------------------
   442 "Schalk I s.87 Bsp 55b (x/(x^^^2 - 6*x+9) - 1/(x^^^2 - 3*x) =1/x)";
   443 ------------------------------------------------------------------------------
   444 1. "x / (x ^^^ 2 - 6 * x + 9) - 1 / (x ^^^ 2 - 3 * x) = 1 / x"
   445 ...
   446 4. "(3 + (-1 * x + x ^^^ 2)) * x = 1 * (9 * x + (x ^^^ 3 + -6 * x ^^^ 2))"
   447                          Subproblem["normalize", "polynomial", "univariate"..
   448 ...
   449 4.4. "-6 * x + 5 * x ^^^ 2 = 0", Subproblem["bdv_only", "degree_2", "poly"..
   450 ...
   451 4.4.4. "[x = 0, x = 6 / 5]", Check_elementwise "Assumptions"
   452 4.4.5. "[x = 0, x = 6 / 5]"
   453 ...
   454 5. "[x = 0, x = 6 / 5]", Check_elementwise "Assumptions"
   455    "[x = 6 / 5]"
   456 ------------------------------------------------------------------------------
   457 (1)..(4): keine 'richtige' Eingabe kann abgeleitet werden, die einen Summanden auf die andere Seite schiebt [Ableitung waere in 4.4.x]
   458 
   459 (4.1)..(4.4.5): keine 'richtige' Eingabe kann abgeleitet werden, die dem Ergebnis "[x = 6 / 5]" aequivalent ist [Ableitung waere in 5.]
   460 ------------------------------------------------------------------------------
   461 
   462 
   463 ------------------------------------------------------------------------------
   464 "Schalk II s.56 Bsp 73b (sqrt(x+1)+sqrt(4*x+4)=sqrt(9*x+9))";
   465 ------------------------------------------------------------------------------
   466 1. "sqrt (x + 1) + sqrt (4 * x + 4) = sqrt (9 * x + 9)"
   467 ...
   468 6. "13 + 13 * x + -2 * sqrt ((4 + 4 * x) * (9 + 9 * x)) = 1 + x"
   469                              Subproblem["sq", "root'", "univariate", "equation"]
   470 ...
   471 6.6. "144 + 288 * x + 144 * x ^^^ 2 = 144 + x ^^^ 2 + 288 * x + 143 * x ^^^ 2"
   472                 Subproblem["normalize", "polynomial", "univariate", "equation"]
   473 ...
   474 6.6.3 "0 = 0"    Subproblem["degree_0", "polynomial", "univariate", "equation"]
   475 ...                                       Or_to_List
   476 6.6.3.2 "UniversalList"
   477 ------------------------------------------------------------------------------
   478 (1)..(6): keine 'richtige' Eingabe kann abgeleitet werden, die eine der Wurzeln auf die andere Seite verschieb [Ableitung ware in 6.6.n]
   479 
   480 (6.1)..(6.3): keine 'richtige' Eingabe kann abgeleitet werden, die einen Summanden auf die andere Seite verschiebt [Ableitung ware in 6.6.n]
   481 ------------------------------------------------------------------------------
   482 *)
   483 (*sh. comments auf 498*)
   484 
   485 fun equal a b = a=b;
   486 
   487 (*the lists contain eq-al elem-pairs at the beginning;
   488   return first list reverted (again) - ie. in order as required subsequently*)
   489 fun dropwhile' equal (f1::f2::fs) (i1::i2::is) =
   490     if equal f1 i1 then
   491 	 if equal f2 i2 then dropwhile' equal (f2::fs) (i2::is)
   492 	 else (rev (f1::f2::fs), i1::i2::is)
   493     else error "dropwhile': did not start with equal elements"
   494   | dropwhile' equal (f::fs) [i] =
   495     if equal f i then (rev (f::fs), [i])
   496     else error "dropwhile': did not start with equal elements"
   497   | dropwhile' equal [f] (i::is) =
   498     if equal f i then ([f], i::is)
   499     else error "dropwhile': did not start with equal elements";
   500 (*
   501  fun equal a b = a=b;
   502  val foder = [0,1,2,3,4,5]; val ifoder = [11,12,3,4,5];
   503  val r_foder = rev foder;  val r_ifoder = rev ifoder;
   504  dropwhile' equal r_foder r_ifoder;
   505 > vval it = ([0, 1, 2, 3], [3, 12, 11]) : int list * int list
   506 
   507  val foder = [3,4,5]; val ifoder = [11,12,3,4,5];
   508  val r_foder = rev foder;  val r_ifoder = rev ifoder;
   509  dropwhile' equal r_foder r_ifoder;
   510 > val it = ([3], [3, 12, 11]) : int list * int list
   511 
   512  val foder = [5]; val ifoder = [11,12,3,4,5];
   513  val r_foder = rev foder;  val r_ifoder = rev ifoder;
   514  dropwhile' equal r_foder r_ifoder;
   515 > val it = ([5], [5, 4, 3, 12, 11]) : int list * int list
   516 
   517  val foder = [10,11,12,13,14,15]; val ifoder = [11,12,3,4,5];
   518  val r_foder = rev foder;  val r_ifoder = rev ifoder;
   519  dropwhile' equal r_foder r_ifoder;
   520 > *** dropwhile': did not start with equal elements*)
   521 
   522 (*040214: version for concat_deriv*)
   523 fun rev_deriv' (t, r, (t', a)) = (t', sym_rule r, (t, a));
   524 
   525 fun mk_tacis ro erls (t, r as Thm (id, thm), (t', a)) = 
   526       (Rewrite (id, thm), 
   527          Rewrite' ("Isac", fst ro, erls, false, Lucin.rule2thm'' r, t, (t', a)),
   528        (e_pos'(*to be updated before generate tacis!!!*), (Uistate, e_ctxt)))
   529   | mk_tacis _ _ (t, r as Rls_ rls, (t', a)) = 
   530       (Rewrite_Set (Lucin.rule2rls' r), 
   531          Rewrite_Set' ("Isac", false, rls, t, (t', a)),
   532        (e_pos'(*to be updated before generate tacis!!!*), (Uistate, e_ctxt)))
   533   | mk_tacis _ _ (t, r, _) = error ("mk_tacis: not impl. for " ^ rule2str r ^ " at " ^ term2str t);
   534 
   535 (*fo = ifo excluded already in inform*)
   536 fun concat_deriv rew_ord erls rules fo ifo =
   537   let 
   538     fun derivat ([]:(term * rule * (term * term list)) list) = e_term
   539       | derivat dt = (#1 o #3 o last_elem) dt
   540     fun equal (_,_,(t1, _)) (_,_,(t2, _)) = t1=t2
   541     val  fod = make_deriv (Isac"") erls rules (snd rew_ord) NONE  fo
   542     val ifod = make_deriv (Isac"") erls rules (snd rew_ord) NONE ifo
   543   in 
   544     case (fod, ifod) of
   545       ([], []) => if fo = ifo then (true, []) else (false, [])
   546     | (fod, []) => if derivat fod = ifo then (true, fod) (*ifo is normal form*) else (false, [])
   547     | ([], ifod) => if fo = derivat ifod then (true, ((map rev_deriv') o rev) ifod) else (false, [])
   548     | (fod, ifod) =>
   549       if derivat fod = derivat ifod (*common normal form found*)
   550       then
   551         let 
   552           val (fod', rifod') = dropwhile' equal (rev fod) (rev ifod)
   553         in (true, fod' @ (map rev_deriv' rifod')) end
   554       else (false, [])
   555   end;
   556 (*
   557  val ({rew_ord, erls, rules,...}, fo, ifo) = 
   558      (rep_rls Test_simplify, str2term "x+1+ -1*2=0", str2term "-2*1+(x+1)=0");
   559  (tracing o trtas2str) fod';
   560 > ["
   561 (x + 1 + -1 * 2 = 0, Thm ("radd_commute","?m + ?n = ?n + ?m"), (-1 * 2 + (x + 1) = 0, []))","
   562 (-1 * 2 + (x + 1) = 0, Thm ("radd_commute","?m + ?n = ?n + ?m"), (-1 * 2 + (1 + x) = 0, []))","
   563 (-1 * 2 + (1 + x) = 0, Thm ("radd_left_commute","?x + (?y + ?z) = ?y + (?x + ?z)"), (1 + (-1 * 2 + x) = 0, []))","
   564 (1 + (-1 * 2 + x) = 0, Thm ("#mult_Float ((~1,0), (0,0)) __ ((2,0), (0,0))","-1 * 2 = -2"), (1 + (-2 + x) = 0, []))"]
   565 val it = () : unit
   566  (tracing o trtas2str) (map rev_deriv' rifod');
   567 > ["
   568 (1 + (-2 + x) = 0, Thm ("sym_#mult_Float ((~2,0), (0,0)) __ ((1,0), (0,0))","-2 = -2 * 1"), (1 + (-2 * 1 + x) = 0, []))","
   569 (1 + (-2 * 1 + x) = 0, Thm ("sym_radd_left_commute","?y + (?x + ?z) = ?x + (?y + ?z)"), (-2 * 1 + (1 + x) = 0, []))","
   570 (-2 * 1 + (1 + x) = 0, Thm ("sym_radd_commute","?n + ?m = ?m + ?n"), (-2 * 1 + (x + 1) = 0, []))"]
   571 val it = () : unit
   572 *)
   573 
   574 
   575 (* compare inform with ctree.form at current pos by nrls;
   576    if found, embed the derivation generated during comparison
   577    if not, let the mat-engine compute the next ctree.form *)
   578 (*structure copied from complete_solve
   579   CAUTION: tacis in returned calcstate' do NOT construct resulting ptp --
   580            all_modspec etc. has to be inserted at Subproblem'*)
   581 fun compare_step ((tacis, c, ptp as (pt, pos as (p,p_))): calcstate') ifo =
   582   let
   583     val fo =
   584       case p_ of
   585         Frm => get_obj g_form pt p
   586 			| Res => (fst o (get_obj g_result pt)) p
   587 			| _ => e_term (*on PblObj is fo <> ifo*);
   588 	  val {nrls, ...} = get_met (get_obj g_metID pt (par_pblobj pt p))
   589 	  val {rew_ord, erls, rules, ...} = rep_rls nrls
   590 	  val (found, der) = concat_deriv rew_ord erls rules fo ifo; (*<---------------*)
   591   in
   592     if found
   593     then
   594        let
   595          val tacis' = map (mk_tacis rew_ord erls) der;
   596 		     val (c', ptp) = embed_deriv tacis' ptp;
   597 	     in ("ok", (tacis (*@ tacis'?WN050408*), c @ c', ptp)) end
   598      else 
   599 	     if pos = ([], Res) (*TODO: we should stop earlier with trying subproblems *)
   600 	     then ("no derivation found", (tacis, c, ptp): calcstate') 
   601 	     else
   602          let
   603            val cs' as (tacis, c', ptp) = nxt_solve_ ptp; (*<---------------------*)
   604 		       val cs' as (tacis, c'', ptp) = 
   605 			       case tacis of
   606 			         ((Subproblem _, _, _)::_) => 
   607 			           let
   608                    val ptp as (pt, (p,_)) = all_modspec ptp (*<------------------*)
   609 				           val mI = get_obj g_metID pt p
   610 			           in
   611 			             nxt_solv (Apply_Method' (mI, NONE, e_istate, e_ctxt)) (e_istate, e_ctxt) ptp
   612                  end
   613 			       | _ => cs';
   614 		     in compare_step (tacis, c @ c' @ c'', ptp) ifo end
   615   end;
   616 
   617 (* check if (agreed result, input formula) matches the error pattern "pat" modulo simplifier rls *)
   618 fun check_err_patt (res, inf) (subst: subst) (errpatID: errpatID, pat) rls =
   619   let 
   620     val (res', _, _, rewritten) =
   621       rew_sub (Isac()) 1 subst e_rew_ord e_rls false [] (Trueprop $ pat) res;
   622   in
   623     if rewritten
   624     then 
   625       let
   626         val norm_res = case rewrite_set_inst_ (Isac()) false subst rls  res' of
   627           NONE => res'
   628         | SOME (norm_res, _) => norm_res
   629         val norm_inf = case rewrite_set_inst_ (Isac()) false subst rls inf of
   630           NONE => inf
   631         | SOME (norm_inf, _) => norm_inf
   632       in if norm_res = norm_inf then SOME errpatID else NONE
   633       end
   634     else NONE
   635   end;
   636 
   637 (* check if (agreed result, input formula) matches SOME error pattern modulo simplifier rls;
   638    (prog, env) for retrieval of casual substitution for bdv in the pattern. *)
   639 fun check_error_patterns (res, inf) (prog, env) (errpats, rls) =
   640   let
   641     val (_, subst) = get_bdv_subst prog env
   642     fun scan (_, [], _) = NONE
   643       | scan (errpatID, errpat :: errpats, _) =
   644           case check_err_patt (res, inf) (subst: subst) (errpatID, errpat) rls of
   645             NONE => scan (errpatID, errpats, [])
   646           | SOME errpatID => SOME errpatID
   647     fun scans [] = NONE
   648       | scans (group :: groups) =
   649           case scan group of
   650             NONE => scans groups
   651           | SOME errpatID => SOME errpatID
   652   in scans errpats end;
   653 
   654 (*.handle a user-input formula, which may be a CAS-command, too.
   655 CAS-command:
   656    create a calchead, and do 1 step
   657    TOOODO.WN0602 works only for the root-problem !!!
   658 formula, which is no CAS-command:
   659    compare iform with calc-tree.form at pos by equ_nrls and all subsequent pos;
   660    collect all the tacs applied by the way;
   661    if "no derivation found" then check_error_patterns.
   662    ALTERNATIVE: check_error_patterns _within_ compare_step seems too expensive.*)
   663 fun inform (cs as (_, _, ptp as (pt, pos as (p, p_))): calcstate') istr =
   664   case parse (assoc_thy "Isac") istr of
   665 	  SOME f_in =>
   666 	    let
   667 	      val f_in = Thm.term_of f_in
   668 	      val f_succ = get_curr_formula (pt, pos);
   669 			in
   670 			  if f_succ = f_in
   671 			  then ("same-formula", cs) (* ctree not cut with replaceFormula *)
   672 			  else
   673 			    case cas_input f_in of
   674 			      SOME (pt, _) => ("ok",([], [], (pt, (p, Met))))
   675 			    | NONE =>
   676 			        let
   677 			          val pos_pred = lev_back' pos
   678 			          (* f_pred ---"step pos cs"---> f_succ in appendFormula *)
   679 			          val f_pred = get_curr_formula (pt, pos_pred)
   680 			          val msg_calcstate' = compare_step ([], [], (pt, pos_pred)) f_in (*<<=====*)
   681 			          (*last step re-calc in compare_step TODO before WN09*)
   682 			        in
   683 			          case msg_calcstate' of
   684 			            ("no derivation found", calcstate') => 
   685 			               let
   686 			                 val pp = par_pblobj pt p
   687 			                 val {errpats, nrls, scr = Prog prog, ...} = get_met (get_obj g_metID pt pp)
   688 			                 val ScrState (env, _, _, _, _, _) = get_istate pt pos
   689 			               in
   690 			                 case check_error_patterns (f_pred, f_in) (prog, env) (errpats, nrls) of
   691 			                   SOME errpatID => ("error pattern #" ^ errpatID ^ "#", calcstate')
   692 			                 | NONE => msg_calcstate'
   693 			               end
   694 			          | _ => msg_calcstate'
   695 			        end
   696 			end
   697     | NONE => ("syntax error in '" ^ istr ^ "'", e_calcstate');
   698 
   699 (* fill-in patterns an forms.
   700   returns thm required by "fun in_fillform *)
   701 fun get_fillform (subs_opt, subst) (thm, form) errpatID ((fillpatID, pat, erpaID): fillpat) =
   702   let
   703     val (form', _, _, rewritten) =
   704       rew_sub (Isac()) 1 subst e_rew_ord e_rls false [] (Trueprop $ pat) form;
   705   in (*the fillpat of the thm must be dedicated to errpatID*)
   706     if errpatID = erpaID andalso rewritten
   707     then SOME (fillpatID, HOLogic.mk_eq (form, form'), thm, subs_opt) else NONE end;
   708 
   709 fun get_fillpats subst form errpatID thm =
   710       let
   711         val thmDeriv = Thm.get_name_hint thm
   712         val (part, thyID) = thy_containing_thm thmDeriv
   713         val theID = [part, thyID, "Theorems", thmID_of_derivation_name thmDeriv]
   714         val Hthm {fillpats, ...} = get_the theID
   715         val some = map (get_fillform subst (thm, form) errpatID) fillpats
   716       in some |> filter is_some |> map the end;
   717 
   718 fun find_fillpatterns (pt, pos as (p, _): pos') errpatID =
   719   let 
   720     val f_curr = get_curr_formula (pt, pos);
   721     val pp = par_pblobj pt p
   722 			    val {errpats, scr = Prog prog, ...} = get_met (get_obj g_metID pt pp)
   723     val ScrState (env, _, _, _, _, _) = get_istate pt pos
   724     val subst = get_bdv_subst prog env
   725     val errpatthms = errpats
   726       |> filter ((curry op = errpatID) o (#1: errpat -> errpatID))
   727       |> map (#3: errpat -> thm list)
   728       |> flat
   729   in map (get_fillpats subst f_curr errpatID) errpatthms |> flat end;
   730 
   731 (* check if an input formula is exactly equal the rewrite from a rule
   732    which is stored at the pos where the input is stored of "ok". *)
   733 fun is_exactly_equal (pt, pos as (p, _)) istr =
   734   case parseNEW (assoc_thy "Isac" |> thy2ctxt) istr of
   735     NONE => ("syntax error in '" ^ istr ^ "'", Tac "")
   736   | SOME ifo => 
   737       let
   738         val p' = lev_on p;
   739         val tac = get_obj g_tac pt p';
   740       in 
   741         case applicable_in pos pt tac of
   742           Notappl msg => (msg, Tac "")
   743         | Appl rew =>
   744             let
   745               val res = case rew of
   746                   Rewrite_Inst' (_, _, _, _, _, _, _, (res, _)) => res
   747                 | Rewrite' (_, _, _, _, _, _, (res, _)) => res
   748             in 
   749               if not (ifo = res)
   750               then ("input does not exactly fill the gaps", Tac "")
   751               else ("ok", tac)
   752             end
   753       end
   754 
   755 (* fetch errpatIDs from an arbitrary tactic *)
   756 fun fetchErrorpatterns tac =
   757   let
   758     val rlsID =
   759       case tac of
   760         Rewrite_Set rlsID => rlsID
   761       | Rewrite_Set_Inst (_, rlsID) => rlsID
   762       | _ => "e_rls"
   763     val (part, thyID) = thy_containing_rls "Isac" rlsID;
   764     val Hrls {thy_rls = (_, rls), ...} = get_the [part, thyID, "Rulesets", rlsID]
   765   in case rls of
   766         Rls {errpatts, ...} => errpatts
   767       | Seq {errpatts, ...} => errpatts
   768       | Rrls {errpatts, ...} => errpatts
   769       | Erls => []
   770   end
   771 
   772 (*------------------------------------------------------------------(**)
   773 end
   774 open inform; 
   775 (**)------------------------------------------------------------------*)