src/Tools/isac/ME/rewtools.sml
author Walther Neuper <neuper@ist.tugraz.at>
Thu, 19 Aug 2010 15:02:06 +0200
branchisac-update-Isa09-2
changeset 37930 f2b8d1b3fcc2
parent 37926 e6fc98fbcb85
child 37935 27d365c3dd31
permissions -rw-r--r--
infix mem union --> member union op = ...

\\ --> subtract op = [4,5,6,7] [1,2,3,4,5] -> [1, 2, 3]
missed due to problem with grep '\\'
     1 (* tools for rewriting, reverse rewriting, context to thy concerning rewriting
     2    authors: Walther Neuper 2002, 2006
     3   (c) due to copyright terms
     4 
     5 use"ME/rewtools.sml";
     6 use"rewtools.sml";
     7 *)
     8 
     9 
    10 
    11 (***.reverse rewriting.***)
    12 
    13 (*.derivation for insertin one level of nodes into the calctree.*)
    14 type deriv  = (term * rule * (term *term list)) list;
    15 
    16 fun trta2str (t,r,(t',a)) = "\n("^(term2str t)^", "^(rule2str' r)^", ("^
    17 			    (term2str t')^", "^(terms2str a)^"))";
    18 fun trtas2str trtas = (strs2str o (map trta2str)) trtas;
    19 val deriv2str = trtas2str;
    20 fun rta2str (r,(t,a)) = "\n("^(rule2str' r)^", ("^
    21 			    (term2str t)^", "^(terms2str a)^"))";
    22 fun rtas2str rtas = (strs2str o (map rta2str)) rtas;
    23 val deri2str = rtas2str;
    24 
    25 
    26 (*.A1==>...==>An==>(Lhs = Rhs) goes to A1==>...==>An==>(Rhs = Lhs).*)
    27 fun sym_thm thm =
    28   let 
    29     val {sign_ref = sign_ref, der = der, maxidx = maxidx,
    30 	    shyps = shyps, hyps = hyps, (*tpairs = tpairs,*) prop = prop} = 
    31 	rep_thm_G thm;
    32     val (lhs,rhs) = (dest_equals' o strip_trueprop 
    33 		     o Logic.strip_imp_concl) prop;
    34     val prop' = case strip_imp_prems' prop of
    35 		   NONE => Trueprop $ (mk_equality (rhs, lhs))
    36 		 | SOME cs => 
    37 		   ins_concl cs (Trueprop $ (mk_equality (rhs, lhs)));
    38   in assbl_thm sign_ref der maxidx shyps hyps (*tpairs*) prop' end;
    39 (*
    40   (sym RS real_mult_div_cancel1) handle e => print_exn e;
    41 Exception THM 1 raised:
    42 RSN: no unifiers
    43 "?s = ?t ==> ?t = ?s"
    44 "?k ~= 0 ==> ?k * ?m / (?k * ?n) = ?m / ?n"
    45 
    46   val thm = real_mult_div_cancel1;
    47   val prop = (#prop o rep_thm) thm;
    48   atomt prop;
    49   val ppp = Logic.strip_imp_concl prop;
    50   atomt ppp;
    51   ((#prop o rep_thm o sym_thm o sym_thm) thm) = (#prop o rep_thm) thm;
    52 val it = true : bool
    53   ((sym_thm o sym_thm) thm) = thm;
    54 val it = true : bool
    55 
    56   val thm = real_le_anti_sym;
    57   ((sym_thm o sym_thm) thm) = thm;
    58 val it = true : bool
    59 
    60   val thm = real_minus_zero;
    61   ((sym_thm o sym_thm) thm) = thm;
    62 val it = true : bool
    63 *)
    64 
    65 
    66 
    67 (*.derive normalform of a rls, or derive until SOME goal,
    68    and record rules applied and rewrites.
    69 val it = fn
    70   : theory
    71     -> rls
    72     -> rule list
    73     -> rew_ord       : the order of this rls, which 1 theorem of is used 
    74                        for rewriting 1 single step (?14.4.03)
    75     -> term option   : 040214 ??? nonsense ??? 
    76     -> term 
    77     -> (term *       : to this term ...
    78         rule * 	     : ... this rule is applied yielding ...
    79         (term *      : ... this term ...
    80          term list)) : ... under these assumptions.
    81        list          :
    82 returns empty list for a normal form
    83 FIXME.WN040214: treats rules as in Rls, _not_ as in Seq
    84 
    85 WN060825 too complicated for the intended use by cancel_, common_nominator_
    86 and unreflectedly adapted to extion of rules by Rls_: returns Rls_("sym_simpl..
    87  -- replaced below*)
    88 (* val (thy, erls, rs, ro, goal, tt) = (thy, erls, rs, ro, goal, t);
    89    val (thy, erls, rs, ro, goal, tt) = (thy, Atools_erls, rules, ro, NONE, tt);
    90    *)
    91 fun make_deriv thy erls (rs:rule list) ro(*rew_ord*) goal tt = 
    92     let datatype switch = Appl | Noap
    93 	fun rew_once lim rts t Noap [] = 
    94 	    (case goal of 
    95 		 NONE => rts
    96 	       | SOME g => 
    97 		 raise error ("make_deriv: no derivation for "^(term2str t)))
    98 	  | rew_once lim rts t Appl [] = 
    99 	    (*(case rs of Rls _ =>*) rew_once lim rts t Noap rs
   100 	  (*| Seq _ => rts) FIXXXXXME 14.3.03*)
   101 	  | rew_once lim rts t apno rs' =
   102 	    (case goal of 
   103 		 NONE => rew_or_calc lim rts t apno rs'
   104 	       | SOME g =>
   105 		 if g = t then rts
   106 		 else rew_or_calc lim rts t apno rs')
   107 	and rew_or_calc lim rts t apno (rrs' as (r::rs')) =
   108 	    if lim < 0 
   109 	    then (writeln ("make_deriv exceeds " ^ int2str (!lim_deriv) ^
   110 			   "with deriv =\n"); writeln (deriv2str rts); rts)
   111 	    else
   112 	    case r of
   113 		Thm (thmid, tm) =>
   114 		(if not (!trace_rewrite) then () else
   115 		 writeln ("### trying thm '" ^ thmid ^ "'");
   116 		 case rewrite_ thy ro erls true tm t of
   117 		     NONE => rew_once lim rts t apno rs'
   118 		   | SOME (t',a') =>
   119 		     (if ! trace_rewrite 
   120 		      then writeln ("### rewrites to: "^(term2str t')) else();
   121 		      rew_once (lim-1) (rts@[(t,r,(t',a'))]) t' Appl rrs'))
   122 	      | Calc (c as (op_,_)) => 
   123 		let val _ = if not (!trace_rewrite) then () else
   124 			    writeln ("### trying calc. '" ^ op_ ^ "'")
   125 		    val t = uminus_to_string t
   126 		in case get_calculation_ thy c t of
   127 		       NONE => rew_once lim rts t apno rs'
   128 		     | SOME (thmid, tm) => 
   129 		       (let val SOME (t',a') = rewrite_ thy ro erls true tm t
   130 			    val _ = if not (!trace_rewrite) then () else
   131 				    writeln("### calc. to: " ^ (term2str t'))
   132 			    val r' = Thm (thmid, tm)
   133 			in rew_once (lim-1) (rts@[(t,r',(t',a'))]) t' Appl rrs'
   134 			end) 
   135 		       handle _ => raise error "derive_norm, Calc: no rewrite"
   136 		end
   137 (* TODO.WN080222: see rewrite__set_
   138    @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
   139       | Cal1 (cc as (op_,_)) => 
   140 	  (let val _= if !trace_rewrite andalso i < ! depth then
   141 		      writeln((idt"#"(i+1))^" try cal1: "^op_^"'") else ();
   142 	     val ct = uminus_to_string ct
   143 	   in case get_calculation_ thy cc ct of
   144 	     NONE => (ct, asm)
   145 	   | SOME (thmid, thm') =>
   146 	       let 
   147 		 val pairopt = 
   148 		   rewrite__ thy (i+1) bdv ((snd o #rew_ord o rep_rls) rls)
   149 		   ((#erls o rep_rls) rls) put_asm thm' ct;
   150 		 val _ = if pairopt <> NONE then () 
   151 			 else raise error("rewrite_set_, rewrite_ \""^
   152 			 (string_of_thmI thm')^"\" "^(term2str ct)^" = NONE")
   153 		 val _ = if ! trace_rewrite andalso i < ! depth 
   154 			   then writeln((idt"="(i+1))^" cal1. to: "^
   155 					(term2str ((fst o the) pairopt)))
   156 			 else()
   157 	       in the pairopt end
   158 	   end)
   159 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@*)
   160 	      | Rls_ rls => 
   161 		(case rewrite_set_ thy true rls t of
   162 		     NONE => rew_once lim rts t apno rs'
   163 		   | SOME (t',a') =>
   164 		     rew_once (lim-1) (rts @ [(t,r,(t',a'))]) t' Appl rrs');
   165 (*WN060829    | Rls_ rls => 
   166 		(case rewrite_set_ thy true rls t of
   167 		     NONE => rew_once lim rts t apno rs'
   168 		   | SOME (t',a') =>
   169 		     if ro [] (t, t') then rew_once lim rts t apno rs'
   170 		     else rew_once (lim-1) (rts@[(t,r,(t',a'))]) t' Appl rrs');
   171 ...lead to deriv = [] with make_polynomial.
   172 THERE IS SOMETHING DIFFERENT beetween rewriting with the code above
   173 and between rewriting with rewrite_set: with rules from make_polynomial and 
   174 t = "(a^^^2 + -1*b^^^2) / (a^^^2 + -2*a*b + b^^^2)" the actual code
   175 leads to cycling  Rls_ order_mult_rls_..Rls_ discard_parentheses_..Rls_ order..
   176 *)
   177     in rew_once (!lim_deriv) [] tt Noap rs end;
   178 
   179 
   180 (*.toggles the marker for 'fun sym_thm'.*)
   181 fun sym_thmID (thmID : thmID) =
   182     case explode thmID of
   183 	"s"::"y"::"m"::"_"::id => implode id : thmID
   184       | id => "sym_"^thmID;
   185 (* 
   186 > val thmID = "sym_real_mult_2";
   187 > sym_thmID thmID;
   188 val it = "real_mult_2" : string
   189 > val thmID = "real_num_collect";
   190 > sym_thmID thmID;
   191 val it = "sym_real_num_collect" : string*)
   192 fun sym_drop (thmID : thmID) =
   193     case explode thmID of
   194 	"s"::"y"::"m"::"_"::id => implode id : thmID
   195       | id => thmID;
   196 fun is_sym (thmID : thmID) =
   197     case explode thmID of
   198 	"s"::"y"::"m"::"_"::id => true
   199       | id => false;
   200 
   201 
   202 (*FIXXXXME.040219: detail has to handle Rls id="sym_..." 
   203   by applying make_deriv, rev_deriv'; see concat_deriv*)
   204 fun sym_rls Erls = Erls
   205   | sym_rls (Rls {id, scr, calc, erls, srls, rules, rew_ord, preconds}) =
   206     Rls {id="sym_"^id, scr=scr, calc=calc, erls=erls, srls=srls, 
   207 	 rules=rules, rew_ord=rew_ord, preconds=preconds}
   208   | sym_rls (Seq {id, scr, calc, erls, srls, rules, rew_ord, preconds}) =
   209     Seq {id="sym_"^id, scr=scr, calc=calc, erls=erls, srls=srls, 
   210 	 rules=rules, rew_ord=rew_ord, preconds=preconds}
   211   | sym_rls (Rrls {id, scr, calc, erls, prepat, rew_ord}) = 
   212     Rrls {id="sym_"^id, scr=scr, calc=calc, erls=erls, prepat=prepat, 
   213 	  rew_ord=rew_ord};
   214 
   215 fun sym_Thm (Thm (thmID, thm)) = Thm (sym_thmID thmID, sym_thm thm)
   216   | sym_Thm (Rls_ rls) = Rls_ (*WN060825?!?*) (sym_rls rls)
   217   | sym_Thm r = raise error ("sym_Thm: not for "^(rule2str r));
   218 (*
   219   val th =  Thm ("real_one_collect",num_str real_one_collect);
   220   sym_Thm th;
   221 val th =
   222   Thm ("real_one_collect","?m is_const ==> ?n + ?m * ?n = (1 + ?m) * ?n")
   223   : rule
   224 ML> val it =
   225   Thm ("sym_real_one_collect","?m is_const ==> (1 + ?m) * ?n = ?n + ?m * ?n")*)
   226 
   227 
   228 (*version for reverse rewrite used before 040214*)
   229 fun rev_deriv (t, r, (t', a)) = (sym_Thm r, (t, a));
   230 (* val (thy, erls, rs, ro, goal, t) = (thy, eval_rls, rules, ro, NONE, t');
   231    *)
   232 fun reverse_deriv thy erls (rs:rule list) ro(*rew_ord*) goal t =
   233     (rev o (map rev_deriv)) (make_deriv thy erls (rs:rule list) ro goal t);
   234 (*
   235   val rev_rew = reverse_deriv thy e_rls ; 
   236   writeln(rtas2str rev_rew);
   237 *)
   238 
   239 fun eq_Thm (Thm (id1,_), Thm (id2,_)) = id1 = id2
   240   | eq_Thm (Thm (id1,_), _) = false
   241   | eq_Thm (Rls_ r1, Rls_ r2) = id_rls r1 = id_rls r2
   242   | eq_Thm (Rls_ r1, _) = false
   243   | eq_Thm (r1, r2) = raise error ("eq_Thm: called with '"^
   244 				(rule2str r1)^"' '"^(rule2str r2)^"'");
   245 fun distinct_Thm r = gen_distinct eq_Thm r;
   246 
   247 fun eq_Thms thmIDs thm = (member op = (id_of_thm thm) thmIDs)
   248     handle _ => false;
   249 
   250 
   251 (***. context to thy concerning rewriting .***)
   252 
   253 (*.create the unique handles and filenames for the theory-data.*)
   254 fun part2guh ([str]:theID) =
   255     (case str of
   256 	"Isabelle" => "thy_isab_" ^ str ^ "-part" : guh
   257       | "IsacScripts" => "thy_scri_" ^ str ^ "-part"
   258       | "IsacKnowledge" => "thy_isac_" ^ str ^ "-part"
   259       | str => raise error ("thy2guh: called with '"^str^"'"))
   260   | part2guh theID = raise error ("part2guh called with theID = "
   261 				  ^ theID2str theID);
   262 fun part2filename str = part2guh str ^ ".xml" : filename;
   263 
   264 
   265 fun thy2guh ([part, thyID]:theID) =
   266     (case part of
   267 	"Isabelle" => "thy_isab_" ^ thyID : guh
   268       | "IsacScripts" => "thy_scri_" ^ thyID
   269       | "IsacKnowledge" => "thy_isac_" ^ thyID
   270       | str => raise error ("thy2guh: called with '"^str^"'"))
   271   | thy2guh theID = raise error ("thy2guh called with '"^strs2str' theID^"'");
   272 fun thy2filename thy' = thy2guh thy' ^ ".xml" : filename;
   273 fun thypart2guh ([part, thyID, thypart]:theID) = 
   274     case part of
   275 	"Isabelle" => "thy_isab_" ^ thyID ^ "-" ^ thypart : guh
   276       | "IsacScripts" => "thy_scri_" ^ thyID ^ "-" ^ thypart
   277       | "IsacKnowledge" => "thy_isac_" ^ thyID ^ "-" ^ thypart
   278       | str => raise error ("thypart2guh: called with '"^str^"'");
   279 fun thypart2filename thy' = thypart2guh thy' ^ ".xml" : filename;
   280 
   281 (*.convert the data got via contextToThy to a globally unique handle
   282    there is another way to get the guh out of the 'theID' in the hierarchy.*)
   283 fun thm2guh (isa, thyID:thyID) (thmID:thmID) =
   284     case isa of
   285 	"Isabelle" => 
   286 	"thy_isab_" ^ theory'2thyID thyID ^ "-thm-" ^ strip_thy thmID : guh
   287     | "IsacKnowledge" =>
   288 	"thy_isac_" ^ theory'2thyID thyID ^ "-thm-" ^ strip_thy thmID
   289     | "IsacScripts" =>
   290 	"thy_scri_" ^ theory'2thyID thyID ^ "-thm-" ^ strip_thy thmID
   291     | str => raise error ("thm2guh called with isa = '"^isa^
   292 			  "' for thm = "^thmID^"'");
   293 fun thm2filename (isa_thyID: string * thyID) thmID =
   294     (thm2guh isa_thyID thmID) ^ ".xml" : filename;
   295 
   296 fun rls2guh (isa, thyID:thyID) (rls':rls') =
   297     case isa of
   298 	"Isabelle" => 
   299 	    "thy_isab_" ^ theory'2thyID thyID ^ "-rls-" ^ rls' : guh
   300     | "IsacKnowledge" =>
   301 	    "thy_isac_" ^ theory'2thyID thyID ^ "-rls-" ^ rls'
   302     | "IsacScripts" =>
   303 	    "thy_scri_" ^ theory'2thyID thyID ^ "-rls-" ^ rls'
   304     | str => raise error ("rls2guh called with isa = '"^isa^
   305 			  "' for rls = '"^rls'^"'");
   306 	fun rls2filename (isa, thyID) rls' =
   307     rls2guh (isa, thyID) rls' ^ ".xml" : filename;
   308 
   309 fun cal2guh (isa, thyID:thyID) calID =
   310     case isa of
   311 	"Isabelle" => 
   312 	"thy_isab_" ^ theory'2thyID thyID ^ "-cal-" ^ calID : guh
   313       | "IsacKnowledge" =>
   314 	"thy_isac_" ^ theory'2thyID thyID ^ "-cal-" ^ calID
   315       | "IsacScripts" =>
   316 	"thy_scri_" ^ theory'2thyID thyID ^ "-cal-" ^ calID
   317       | str => raise error ("cal2guh called with isa = '"^isa^
   318 			  "' for cal = '"^calID^"'");
   319 fun cal2filename (isa, thyID:thyID) calID = 
   320     cal2guh (isa, thyID:thyID) calID ^ ".xml" : filename;
   321 
   322 fun ord2guh (isa, thyID:thyID) (rew_ord':rew_ord') =
   323     case isa of
   324 	"Isabelle" => 
   325 	"thy_isab_" ^ theory'2thyID thyID ^ "-ord-" ^ rew_ord' : guh
   326       | "IsacKnowledge" =>
   327 	"thy_isac_" ^ theory'2thyID thyID ^ "-ord-" ^ rew_ord'
   328       | "IsacScripts" =>
   329 	"thy_scri_" ^ theory'2thyID thyID ^ "-ord-" ^ rew_ord'
   330       | str => raise error ("ord2guh called with isa = '"^isa^
   331 			  "' for ord = '"^rew_ord'^"'");
   332 fun ord2filename (isa, thyID:thyID) (rew_ord':rew_ord') =
   333     ord2guh (isa, thyID:thyID) (rew_ord':rew_ord') ^ ".xml" : filename;
   334 
   335 
   336 (**.set up isab_thm_thy in Isac.ML.**)
   337 
   338 fun rearrange (thyID, (thmID, thm)) = (thmID, (thyID, thm));
   339 fun rearrange_inv (thmID, (thyID, thm)) = (thyID, (thmID, thm));
   340 
   341 (*.lookup the missing theorems in some thy (of Isabelle).*)
   342 fun make_isa missthms thy =
   343     map (pair (theory2thyID thy)) 
   344 	(curry (gen_inter eq_thmI) missthms (thms_of thy))
   345 	: (thyID * (thmID * Thm.thm)) list;
   346 
   347 (*.separate handling of sym_thms.*)
   348 fun make_isab rlsthmsNOTisac isab_thys = 
   349     let fun les ((s1,_), (s2,_)) = (s1 : string) < s2
   350 	val notsym = filter_out (is_sym o #1) rlsthmsNOTisac
   351 	val notsym_isab = (flat o (map (make_isa notsym))) isab_thys
   352 			  
   353 	val sym = filter (is_sym o #1) rlsthmsNOTisac
   354 		  
   355 	val symsym = map ((apfst sym_drop) o (apsnd sym_thm)) sym
   356 	val symsym_isab = (flat o (map (make_isa symsym))) isab_thys
   357 			  
   358 	val sym_isab = map (((apsnd o apfst) sym_drop) o 
   359 			    ((apsnd o apsnd) sym_thm)) symsym_isab
   360 		       
   361 	val isab = notsym_isab @ symsym_isab @ sym_isab
   362     in ((map rearrange) o (gen_sort les)) isab 
   363        : (thmID * (thyID * Thm.thm)) list
   364     end;
   365 
   366 (*.which theory below thy' contains a theorem; this can be in isabelle !
   367 get the occurence _after_ in the _list_ (is up to asking TUM) theory'.*)
   368 (* val (str, (_, thy)) = ("real_diff_minus", ("Root.thy", Root.thy));
   369    val (str, (_, thy)) = ("real_diff_minus", ("Poly.thy", Poly.thy));
   370    *)
   371 fun thy_contains_thm (str:xstring) (_, thy) = 
   372     member str (map (strip_thy o fst) (thms_of thy));
   373 (* val (thy', str) = ("Isac.thy", "real_mult_minus1");
   374    val (thy', str) = ("PolyMinus.thy", "klammer_minus_plus");
   375    *)
   376 fun thy_containing_thm (thy':theory') (str:xstring) =
   377     let val thy' = thyID2theory' thy'
   378 	val str = sym_drop str
   379 	val startsearch = dropuntil ((curry op= thy') o 
   380 				     (#1:theory' * theory -> theory')) 
   381 				    (rev (!theory'))
   382     in case find_first (thy_contains_thm str) startsearch of
   383 	   SOME (thy',_) => ("IsacKnowledge", thy')
   384 	 | NONE => (case assoc (!isab_thm_thy (*see Isac.ML*), str) of
   385 		     SOME (thyID,_) => ("Isabelle", thyID)
   386 		   | NONE => 
   387 		     raise error ("thy_containing_thm: theorem '"^str^
   388 				  "' not in !theory' above thy '"^thy'^"'"))
   389     end;
   390 
   391 
   392 (*.which theory below thy' contains a ruleset;
   393 get the occurence _after_ in the _list_ (is up to asking TUM) theory'.*)
   394 (* val (thy', rls') = ("PolyEq.thy", "separate_bdv");
   395    *)
   396 fun thy_containing_rls (thy':theory') (rls':rls') =
   397     let val rls' = strip_thy rls'
   398 	val thy' = thyID2theory' thy'
   399 	(*take thys between "Isac" and thy' not to search #1#*)
   400 	val dropthys = takewhile [] (not o (curry op= thy') o 
   401 				     (#1:theory' * theory -> theory')) 
   402 				 (rev (!theory'))
   403 	val dropthy's = map (get_thy o (#1 : (theory' * theory) -> theory'))
   404 			    dropthys
   405 	(*drop those rulesets which are generated in a theory found in #1#*)
   406 	val startsearch = filter_out ((curry ((op mem) o swap) dropthy's) o
   407 				      ((#1 o #2) : rls' * (theory' * rls) 
   408 						   -> theory'))
   409 				     (rev (!ruleset'))
   410     in case assoc (startsearch, rls') of
   411 	   SOME (thy', _) => ("IsacKnowledge", thyID2theory' thy')
   412 	 | _ => raise error ("thy_containing_rls : rls '"^rls'^
   413 			     "' not in !rulset' above thy '"^thy'^"'")
   414     end;
   415 (* val (thy', termop) = (thyID, termop);
   416    *)
   417 fun thy_containing_cal (thy':theory') termop =
   418     let val thy' = thyID2theory' thy'
   419 	val dropthys = takewhile [] (not o (curry op= thy') o 
   420 				     (#1:theory' * theory -> theory')) 
   421 				 (rev (!theory'))
   422 	val dropthy's = map (get_thy o (#1 : (theory' * theory) -> theory'))
   423 			    dropthys
   424 	val startsearch = filter_out ((curry ((op mem) o swap) dropthy's) o
   425 				      (#1 : calc -> string)) (rev (!calclist'))
   426     in case assoc (startsearch, strip_thy termop) of
   427 	   SOME (th_termop, _) => ("IsacKnowledge", strip_thy th_termop)
   428 	 | _ => raise error ("thy_containing_rls : rls '"^termop^
   429 			     "' not in !calclist' above thy '"^thy'^"'")
   430     end;
   431 	
   432 (* print_depth 99; map #1 startsearch; print_depth 3;
   433    *)
   434 
   435 (*.packing return-values to matchTheory, contextToThy for xml-generation.*)
   436 datatype contthy =  (*also an item from KEStore on Browser ......#*)
   437 	 EContThy   (*not from KEStore ...........................*)
   438        | ContThm of (*a theorem in contex =============*)
   439 	 {thyID   : thyID,         (*for *2guh in sub-elems here .*)
   440 	  thm     : guh,           (*theorem in the context      .*)
   441 	  applto  : term,	   (*applied to formula ...      .*)
   442 	  applat  : term,	   (*...  with lhs inserted      .*)
   443 	  reword  : rew_ord',      (*order used for rewrite      .*)
   444 	  asms    : (term          (*asumption instantiated      .*)
   445 		     * term) list, (*asumption evaluated         .*)
   446 	  lhs     : term           (*lhs of the theorem ...      #*)
   447 		    * term,        (*... instantiated            .*)
   448 	  rhs     : term           (*rhs of the theorem ...      #*)
   449 		    * term,        (*... instantiated            .*)
   450 	  result  : term,	   (*resulting from the rewrite  .*)
   451 	  resasms : term list,     (*... with asms stored        .*)
   452 	  asmrls  : rls'           (*ruleset for evaluating asms .*)
   453 		    }						 
   454 	| ContThmInst of (*a theorem with bdvs in contex ======== *)
   455 	 {thyID   : thyID,         (*for *2guh in sub-elems here .*)
   456 	  thm     : guh,           (*theorem in the context      .*)
   457 	  bdvs    : subst,         (*bound variables to modify....*)
   458 	  thminst : term,          (*... theorem instantiated    .*)
   459 	  applto  : term,	   (*applied to formula ...      .*)
   460 	  applat  : term,	   (*...  with lhs inserted      .*)
   461 	  reword  : rew_ord',      (*order used for rewrite      .*)
   462 	  asms    : (term          (*asumption instantiated      .*)
   463 		     * term) list, (*asumption evaluated         .*)
   464 	  lhs     : term           (*lhs of the theorem ...      #*)
   465 		    * term,        (*... instantiated            .*)
   466 	  rhs     : term           (*rhs of the theorem ...      #*)
   467 		    * term,        (*... instantiated            .*)
   468 	  result  : term,	   (*resulting from the rewrite  .*)
   469 	  resasms : term list,     (*... with asms stored        .*)
   470 	  asmrls  : rls'           (*ruleset for evaluating asms .*)
   471 		      }						 
   472 	| ContRls of (*a rule set in contex ===================== *)
   473 	 {thyID   : thyID,         (*for *2guh in sub-elems here .*)
   474 	  rls     : guh,           (*rule set in the context     .*)
   475 	  applto  : term,	   (*rewrite this formula        .*)
   476 	  result  : term,	   (*resulting from the rewrite  .*)
   477 	  asms    : term list      (*... with asms stored        .*)
   478 		    }						 
   479 	| ContRlsInst of (*a rule set with bdvs in contex ======= *)
   480 	 {thyID   : thyID,         (*for *2guh in sub-elems here .*)
   481 	  rls     : guh,           (*rule set in the context     .*)
   482 	  bdvs    : subst,         (*for bound variables in thms .*)
   483 	  applto  : term,	   (*rewrite this formula        .*)
   484 	  result  : term,	   (*resulting from the rewrite  .*)
   485 	  asms    : term list      (*... with asms stored        .*)
   486 		    }
   487 	| ContNOrew of (*no rewrite for thm or rls ============== *)
   488 	 {thyID   : thyID,         (*for *2guh in sub-elems here .*)
   489 	  thm_rls : guh,           (*thm or rls in the context   .*)
   490 	  applto  : term	   (*rewrite this formula        .*)
   491 		    }						 
   492 	| ContNOrewInst of (*no rewrite for some instantiation == *)
   493 	 {thyID   : thyID,         (*for *2guh in sub-elems here .*)
   494 	  thm_rls : guh,           (*thm or rls in the context   .*)
   495 	  bdvs    : subst,         (*for bound variables in thms .*)
   496 	  thminst : term,          (*... theorem instantiated    .*)
   497 	  applto  : term	   (*rewrite this formula        .*)
   498 		    };
   499 
   500 (*.check a rewrite-tac for bdv (RL always used *_Inst !) TODO.WN060718
   501    pass other tacs unchanged.*)
   502 fun get_tac_checked pt ((p,p_) : pos') = get_obj g_tac pt p;
   503 
   504 (*..*)
   505 
   506 
   507 
   508 (*.get the formula f at ptp rewritten by the Rewrite_* already applied to f.*)
   509 (* val (Rewrite' (thy', ord', erls, _, (thmID,_), f, (res,asm))) = tac';
   510    *)
   511 fun context_thy (pt, pos as (p,p_)) (tac as Rewrite (thmID,_)) = 
   512     (case applicable_in pos pt tac of
   513 	Appl (Rewrite' (thy', ord', erls, _, (thmID,_), f, (res,asm))) =>
   514 	let val thy = assoc_thy thy'
   515 	    val thm = (norm o #prop o rep_thm o (get_thm thy)) thmID
   516     (*WN060616 the following must be done on subterm found _IN_ rew_sub
   517 	val (lhs,rhs) = (dest_equals' o strip_trueprop 
   518 			 o Logic.strip_imp_concl) thm
   519 	val insts = Pattern.match (Sign.tsig_of (sign_of thy)) (lhs, f)
   520 	val thm' = ren_inst (insts, thm, lhs, f)
   521 	val (lhs',rhs') = (dest_equals' o strip_trueprop 
   522 			   o Logic.strip_imp_concl) thm'
   523 	val asms = map strip_trueprop (Logic.strip_imp_prems thm)
   524 	val asms' = map strip_trueprop (Logic.strip_imp_prems thm')
   525      *)
   526 	in ContThm {thyID   = theory'2thyID thy',
   527 		    thm     = thm2guh (thy_containing_thm thy' thmID) thmID,
   528 		    applto  = f,
   529 		    applat  = e_term,
   530 		    reword  = ord',
   531 		    asms    = [](*asms ~~ asms'*),
   532 		    lhs     = (e_term, e_term)(*(lhs, lhs')*),
   533 		    rhs     = (e_term, e_term)(*(rhs, rhs')*),
   534 		    result  = res,
   535 		    resasms = asm,
   536 		    asmrls  = id_rls erls}
   537 	end
   538       | Notappl _ =>
   539 	let val pp = par_pblobj pt p
   540 	    val thy' = get_obj g_domID pt pp
   541 	    val f = case p_ of
   542 			Frm => get_obj g_form pt p
   543 		      | Res => (fst o (get_obj g_result pt)) p
   544 	in ContNOrew {thyID   = theory'2thyID thy',
   545 		    thm_rls = thm2guh (thy_containing_thm thy' thmID) thmID,
   546 		      applto = f}
   547 	end)
   548     
   549 (* val ((pt,p), tac as Rewrite_Inst (subs, (thmID,_))) = ((pt,pos), tac);
   550    *)
   551       | context_thy (pt, pos as (p,p_)) 
   552 		    (tac as Rewrite_Inst (subs, (thmID,_))) =
   553 	(case applicable_in pos pt tac of
   554 (* val Appl (Rewrite_Inst' (thy', ord', erls, _, subst, (thmID,_), 
   555 			    f, (res,asm))) = applicable_in p pt tac;
   556    *)
   557 	     Appl (Rewrite_Inst' (thy', ord', erls, _, subst, (thmID,_), 
   558 				  f, (res,(*path to subterm,*)asm))) =>
   559 	     let val thm = (norm o #prop o rep_thm o 
   560 			    (get_thm (assoc_thy thy'))) thmID
   561 	    val thminst = inst_bdv subst thm
   562     (*WN060616 the following must be done on subterm found _IN_ rew_sub
   563 	val (lhs,rhs) = (dest_equals' o strip_trueprop 
   564 			 o Logic.strip_imp_concl) thminst
   565 	val insts = Pattern.match (Sign.tsig_of (sign_of thy)) (lhs, f)
   566 	val thm' = ren_inst (insts, thminst, lhs, f)
   567 	val (lhs',rhs') = (dest_equals' o strip_trueprop 
   568 			   o Logic.strip_imp_concl) thm'
   569 	val asms = map strip_trueprop (Logic.strip_imp_prems thminst)
   570 	val asms' = map strip_trueprop (Logic.strip_imp_prems thm')
   571      *)
   572 	     in ContThmInst {thyID   = theory'2thyID thy',
   573 		    thm     = thm2guh (thy_containing_thm 
   574 						    thy' thmID) thmID,
   575 			     bdvs    = subst,
   576 			     thminst = thminst,
   577 			     applto  = f,
   578 			     applat  = e_term,
   579 			     reword  = ord',
   580 			     asms    = [](*asms ~~ asms'*),
   581 			     lhs     = (e_term, e_term)(*(lhs, lhs')*),
   582 			     rhs     = (e_term, e_term)(*(rhs, rhs')*),
   583 			     result  = res,
   584 			     resasms = asm,
   585 			     asmrls  = id_rls erls}
   586 	     end
   587       | Notappl _ =>
   588 	let val pp = par_pblobj pt p
   589 	    val thy' = get_obj g_domID pt pp
   590 	    val subst = subs2subst (assoc_thy thy') subs
   591 	    val thm = (norm o #prop o rep_thm o 
   592 			    (get_thm (assoc_thy thy'))) thmID
   593 	    val thminst = inst_bdv subst thm
   594 	    val f = case p_ of
   595 			Frm => get_obj g_form pt p
   596 		      | Res => (fst o (get_obj g_result pt)) p
   597 	in ContNOrewInst {thyID   = theory'2thyID thy',
   598 			  thm_rls = thm2guh (thy_containing_thm 
   599 						 thy' thmID) thmID, 
   600 			  bdvs    = subst,
   601 			  thminst = thminst,
   602 			  applto = f}
   603 	end)
   604   | context_thy (pt,p) (tac as Rewrite_Set rls') =
   605     (case applicable_in p pt tac of
   606 	 Appl (Rewrite_Set' (thy', _, rls, f, (res,asm))) =>
   607 	 ContRls {thyID   = theory'2thyID thy',
   608 		  rls     = rls2guh (thy_containing_rls thy' rls') rls',
   609 		  applto  = f,	  
   610 		  result  = res,	  
   611 		  asms    = asm})
   612   | context_thy (pt,p) (tac as Rewrite_Set_Inst (subs, rls')) = 
   613     (case applicable_in p pt tac of
   614 	 Appl (Rewrite_Set_Inst' (thy', _, subst, rls, f, (res,asm))) =>
   615 	 ContRlsInst {thyID   = theory'2thyID thy',
   616 		      rls     = rls2guh (thy_containing_rls thy' rls') rls',
   617 		      bdvs    = subst,
   618 		      applto  = f,	  
   619 		      result  = res,	  
   620 		      asms    = asm});
   621 
   622 (*.get all theorems in a rule set (recursivley containing rule sets).*)
   623 fun thm_of_rule Erule = []
   624   | thm_of_rule (thm as Thm _) = [thm]
   625   | thm_of_rule (Calc _) = []
   626   | thm_of_rule (Cal1 _) = []
   627   | thm_of_rule (Rls_ rls) = thms_of_rls rls
   628 and thms_of_rls Erls = []
   629   | thms_of_rls (Rls {rules,...}) = (flat o (map  thm_of_rule)) rules
   630   | thms_of_rls (Seq {rules,...}) = (flat o (map  thm_of_rule)) rules
   631   | thms_of_rls (Rrls _) = [];
   632 (* val Hrls {thy_rls = (_, rls),...} =
   633        get_the ["IsacKnowledge", "Test", "Rulesets", "expand_binomtest"];
   634 > thms_of_rls rls;
   635    *)
   636 
   637 (*. check if a rule is contained in a rule-set (recursivley down in Rls_);
   638     this rule can even be a rule-set itself.*)
   639 fun contains_rule r rls = 
   640     let fun find (r, Rls_ rls) = finds (get_rules rls)
   641 	  | find r12 = eq_rule r12
   642 	and finds [] = false
   643 	  | finds (r1 :: rs) = if eq_rule (r, r1) then true else finds rs;
   644     in 
   645     (*writeln ("### contains_rule: r = "^rule2str r^", rls = "^rls2str rls);*)
   646     finds (get_rules rls) 
   647     end;
   648 
   649 (*. try if a rewrite-rule is applicable to a given formula; 
   650     in case of rule-sets (recursivley) collect all _atomic_ rewrites .*) 
   651 fun try_rew thy ((_, ro):rew_ord) erls (subst:subst) f (thm' as Thm(id, thm)) =
   652     if contains_bdv thm
   653     then case rewrite_inst_ thy ro erls false subst thm f of
   654 	      SOME (f',_) =>[rule2tac subst thm']
   655 	    | NONE => []
   656     else (case rewrite_ thy ro erls false thm f of
   657 	SOME (f',_) => [rule2tac [] thm']
   658 	    | NONE => [])
   659   | try_rew thy _ _ _ f (cal as Calc c) = 
   660     (case get_calculation_ thy c f of
   661 	SOME (str, _) => [rule2tac [] cal]
   662       | NONE => [])
   663   | try_rew thy _ _ _ f (cal as Cal1 c) = 
   664     (case get_calculation_ thy c f of
   665 	SOME (str, _) => [rule2tac [] cal]
   666       | NONE => [])
   667   | try_rew thy _ _ subst f (Rls_ rls) = filter_appl_rews thy subst f rls
   668 and filter_appl_rews thy subst f (Rls {rew_ord = ro, erls, rules,...}) = 
   669     distinct (flat (map (try_rew thy ro erls subst f) rules))
   670   | filter_appl_rews thy subst f (Seq {rew_ord = ro, erls, rules,...}) = 
   671     distinct (flat (map (try_rew thy ro erls subst f) rules))
   672   | filter_appl_rews thy subst f (Rrls _) = [];
   673 
   674 (*. decide if a tactic is applicable to a given formula; 
   675     in case of Rewrite_Set* go down to _atomic_ rewrite-tactics .*)
   676 (* val 
   677    *)
   678 fun atomic_appl_tacs thy _ _ f (Calculate scrID) =
   679     try_rew thy e_rew_ordX e_rls [] f (Calc (snd(assoc1 (!calclist', scrID))))
   680   | atomic_appl_tacs thy ro erls f (Rewrite (thm' as (thmID, _))) =
   681     try_rew thy (ro, assoc_rew_ord ro) erls [] f 
   682 	    (Thm (thmID, assoc_thm' thy thm'))
   683   | atomic_appl_tacs thy ro erls f (Rewrite_Inst (subs, thm' as (thmID, _))) =
   684     try_rew thy (ro, assoc_rew_ord ro) erls (subs2subst thy subs) f 
   685 	    (Thm (thmID, assoc_thm' thy thm'))
   686 
   687   | atomic_appl_tacs thy _ _ f (Rewrite_Set rls') =
   688     filter_appl_rews thy [] f (assoc_rls rls')
   689   | atomic_appl_tacs thy _ _ f (Rewrite_Set_Inst (subs, rls')) =
   690     filter_appl_rews thy (subs2subst thy subs) f (assoc_rls rls')
   691   | atomic_appl_tacs _ _ _ _ tac = 
   692     (writeln ("### atomic_appl_tacs: not impl. for tac = '"^ tac2str tac ^"'");
   693      []);
   694 
   695 
   696 
   697 
   698 
   699 (*.not only for thydata, but also for thy's etc.*)
   700 fun theID2guh (theID:theID) =
   701     case length theID of
   702 	0 => raise error ("theID2guh: called with theID = "^strs2str' theID)
   703       | 1 => part2guh theID
   704       | 2 => thy2guh theID
   705       | 3 => thypart2guh theID
   706       | 4 => let val [isa, thyID, typ, elemID] = theID
   707 	     in case typ of
   708 		    "Theorems" => thm2guh (isa, thyID) elemID
   709 		  | "Rulesets" => rls2guh (isa, thyID) elemID
   710 		  | "Calculations" => cal2guh (isa, thyID) elemID
   711 		  | "Orders" => ord2guh (isa, thyID) elemID
   712 		  | "Theorems" => thy2guh [isa, thyID]
   713 		  | str => raise error ("theID2guh: called with theID = "^
   714 					strs2str' theID)
   715 	     end
   716       | n => raise error ("theID2guh called with theID = "^strs2str' theID);
   717 (*.filenames not only for thydata, but also for thy's etc.*)
   718 fun theID2filename (theID:theID) = theID2guh theID ^ ".xml" : filename;
   719 
   720 fun guh2theID (guh:guh) =
   721     let val guh' = explode guh
   722 	val part = implode (take_fromto 1 4 guh')
   723 	val isa = implode (take_fromto 5 9 guh')
   724     in if not (member op = part ["exp_", "thy_", "pbl_", "met_"])
   725        then raise error ("guh '"^guh^"' does not begin with \
   726 				     \exp_ | thy_ | pbl_ | met_")
   727        else let val chap = case isa of
   728 				"isab_" => "Isabelle"
   729 			      | "scri_" => "IsacScripts"
   730 			      | "isac_" => "IsacKnowledge"
   731 			      | _ => 
   732 				raise error ("guh2theID: '"^guh^
   733 					     "' does not have isab_ | scri_ | \
   734 					     \isac_ at position 5..9")
   735 		val rest = takerest (9, guh') 
   736 		val thyID = takewhile [] (not o (curry op= "-")) rest
   737 		val rest' = dropuntil (curry op= "-") rest
   738 	    in case implode rest' of
   739 		   "-part" => [chap] : theID
   740 		 | "" => [chap, implode thyID]
   741 		 | "-Theorems" => [chap, implode thyID, "Theorems"]
   742 		 | "-Rulesets" => [chap, implode thyID, "Rulesets"]
   743 		 | "-Operations" => [chap, implode thyID, "Operations"]
   744 		 | "-Orders" => [chap, implode thyID, "Orders"]
   745 		 | _ => 
   746 		   let val sect = implode (take_fromto 1 5 rest')
   747 		       val sect' = 
   748 			   case sect of
   749 			       "-thm-" => "Theorems"
   750 			     | "-rls-" => "Rulesets"
   751 			     | "-cal-" => "Operations"
   752 			     | "-ord-" => "Orders"
   753 			     | str => 
   754 			       raise error ("guh2theID: '"^guh^"' has '"^sect^
   755 					    "' instead -thm- | -rls- | \
   756 					    \-cal- | -ord-")
   757 		   in [chap, implode thyID, sect', implode 
   758 						       (takerest (5, rest'))]
   759 		   end
   760 	    end	
   761     end;
   762 (*> guh2theID "thy_isac_Biegelinie-Theorems";
   763 val it = ["IsacKnowledge", "Biegelinie", "Theorems"] : theID
   764 > guh2theID "thy_scri_ListG-thm-zip_Nil";
   765 val it = ["IsacScripts", "ListG", "Theorems", "zip_Nil"] : theID*)
   766 
   767 fun guh2filename (guh : guh) = guh ^ ".xml" : filename;
   768 
   769 
   770 (*..*)
   771 fun guh2rewtac (guh:guh) ([] : subs) =
   772     let val [isa, thy, sect, xstr] = guh2theID guh
   773     in case sect of
   774 	   "Theorems" => Rewrite (xstr, "")
   775 	 | "Rulesets" => Rewrite_Set xstr
   776 	 | str => raise error ("guh2rewtac: not impl. for '"^xstr^"'") 
   777     end
   778   | guh2rewtac (guh:guh) subs =
   779     let val [isa, thy, sect, xstr] = guh2theID guh
   780     in case sect of
   781 	   "Theorems" => Rewrite_Inst (subs, (xstr, ""))
   782 	 | "Rulesets" => Rewrite_Set_Inst (subs,  xstr)
   783 	 | str => raise error ("guh2rewtac: not impl. for '"^xstr^"'") 
   784     end;
   785 (*> guh2rewtac "thy_isac_Test-thm-constant_mult_square" [];
   786 val it = Rewrite ("constant_mult_square", "") : tac
   787 > guh2rewtac "thy_isac_Test-thm-risolate_bdv_add" ["(bdv, x)"];
   788 val it = Rewrite_Inst (["(bdv, x)"], ("risolate_bdv_add", "")) : tac
   789 > guh2rewtac "thy_isac_Test-rls-Test_simplify" [];
   790 val it = Rewrite_Set "Test_simplify" : tac
   791 > guh2rewtac "thy_isac_Test-rls-isolate_bdv" ["(bdv, x)"];
   792 val it = Rewrite_Set_Inst (["(bdv, x)"], "isolate_bdv") : tac*)
   793 
   794 
   795 (*.the front-end may request a context for any element of the hierarchy.*)
   796 (* val guh = "thy_isac_Test-rls-Test_simplify";
   797    *)
   798 fun no_thycontext (guh : guh) = (guh2theID guh; false)
   799     handle _ => true;
   800 
   801 (*> has_thycontext  "thy_isac_Test";
   802 if has_thycontext  "thy_isac_Test" then "OK" else "NOTOK";
   803  *)
   804 
   805 
   806 
   807 (*.get the substitution of bound variables for matchTheory:
   808    # lookup the thm|rls' in the script
   809    # take the [(bdv, v_),..] from the respective Rewrite_(Set_)Inst
   810    # instantiate this subs with the istates env to [(bdv, x),..]
   811    # otherwise [].*)
   812 (*WN060617 hack assuming that all scripts use only one bound variable
   813 and use 'v_' as the formal argument for this bound variable*)
   814 (* val (ScrState (env,_,_,_,_,_), _, guh) = (is, "dummy", guh);
   815    *)
   816 fun subs_from (ScrState (env,_,_,_,_,_)) _(*:Script sc*) (guh:guh) =
   817     let val theID as [isa, thyID, sect, xstr] = guh2theID guh
   818     in case sect of
   819 	   "Theorems" => 
   820 	   let val thm = get_thm (assoc_thy (thyID2theory' thyID)) xstr
   821 	   in if contains_bdv thm
   822 	      then let val formal_arg = str2term "v_"
   823 		       val value = subst_atomic env formal_arg
   824 		   in ["(bdv," ^ term2str value ^ ")"]:subs end
   825 	      else []
   826 	   end
   827 	 | "Rulesets" => 
   828 	   let val rules = (get_rules o assoc_rls) xstr
   829 	   in if contain_bdv rules
   830 	      then let val formal_arg = str2term"v_"
   831 		       val value = subst_atomic env formal_arg
   832 		   in ["(bdv,"^term2str value^")"]:subs end
   833 	      else []
   834 	   end
   835     end;
   836 
   837 (* use"ME/rewtools.sml";
   838    *)
   839