src/sml/ME/ctree.sml
author wneuper
Wed, 26 Jul 2006 14:16:47 +0200
branchstart_Take
changeset 611 4f4d4c7d55b5
parent 607 117904920570
child 615 96dbf1ca6e27
permissions -rw-r--r--
sml: improved initContext Thy_
     1 (* use"../ME/ctree.sml";
     2    use"ME/ctree.sml";
     3    use"ctree.sml";
     4    W.N.26.10.99
     5 
     6 writeln (pr_ptree pr_short pt); 
     7 
     8 val Nd ( _, ns) = pt;
     9 
    10 *)
    11 
    12 (*structure Ptree (**): PTREE (**) = ###### outcommented ######*)
    13 signature PTREE =
    14 sig
    15   type ptree
    16   type envp
    17   val e_ptree : ptree
    18   exception PTREE of string
    19   type branch
    20   type ostate
    21   type cellID
    22   type cid
    23   type posel
    24   type pos
    25   type pos'
    26   type loc
    27   type domID
    28   type pblID
    29   type metID
    30   type spec
    31   type 'a ppc
    32   type con
    33   type subs
    34   type subst
    35   type env
    36   type ets
    37   val ets2str : ets -> string
    38   type item
    39   type tac
    40   type tac_
    41   val tac_2str : tac_ -> string
    42   type safe
    43   val safe2str : safe -> string
    44 
    45   type meth
    46   val cappend_atomic : ptree -> pos -> loc -> cterm' -> tac
    47     -> cterm' -> ostate -> cid -> ptree * posel list * cid
    48   val cappend_form : ptree
    49     -> pos -> loc -> cterm' -> cid -> ptree * pos * cid
    50   val cappend_parent : ptree -> pos -> loc -> cterm' -> tac
    51     -> branch -> cid -> ptree * int list * cid
    52   val cappend_problem : ptree -> posel list(*FIXME*) -> loc
    53     -> cterm' list * spec -> cid -> ptree * int list * cellID list
    54   val append_result : ptree -> pos -> cterm' -> ostate -> ptree * pos
    55 
    56   type ppobj
    57   val g_branch : ppobj -> branch
    58   val g_cell : ppobj -> cid
    59   val g_args : ppobj -> (int * (term list)) list (*args of scr*)
    60   val g_form : ppobj -> cterm'
    61   val g_loc : ppobj -> loc
    62   val g_met : ppobj -> meth
    63   val g_domID : ppobj -> domID
    64   val g_metID : ppobj -> metID
    65   val g_model : ppobj -> cterm' ppc
    66   val g_tac : ppobj -> tac
    67   val g_origin : ppobj -> cterm' list * spec
    68   val g_ostate : ppobj -> ostate
    69   val g_pbl : ppobj -> pblID * item ppc
    70   val g_result : ppobj -> cterm'
    71   val g_spec : ppobj -> spec
    72 (*  val get_all : (ppobj -> 'a) -> ptree -> 'a list
    73   val get_alls : (ppobj -> 'a) -> ptree list -> 'a list *)
    74   val get_obj : (ppobj -> 'a) -> ptree -> pos -> 'a     
    75   val gpt_cell : ptree -> cid
    76   val par_pblobj : ptree -> pos -> pos
    77   val pre_pos : pos -> pos
    78   val lev_dn : int list -> int list
    79   val lev_on : pos -> posel list
    80   val lev_pred : pos -> pos
    81   val lev_up : pos -> pos
    82 (*  val pr_cell : pos -> ppobj -> string
    83   val pr_pos : int list -> string        *)
    84   val pr_ptree : (pos -> ppobj -> string) -> ptree -> string
    85   val pr_short : pos -> ppobj -> string
    86 (*  val repl : 'a list -> int -> 'a -> 'a list
    87   val repl_app : 'a list -> int -> 'a -> 'a list
    88   val repl_branch : branch -> ppobj -> ppobj
    89   val repl_domID : domID -> ppobj -> ppobj
    90   val repl_form : cterm' -> ppobj -> ppobj
    91   val repl_met : item ppc -> ppobj -> ppobj
    92   val repl_metID : metID -> ppobj -> ppobj
    93   val repl_model : cterm' list -> ppobj -> ppobj
    94   val repl_tac : tac -> ppobj -> ppobj
    95   val repl_pbl : item ppc -> ppobj -> ppobj
    96   val repl_pblID : pblID -> ppobj -> ppobj
    97   val repl_result : cterm' -> ostate -> ppobj -> ppobj
    98   val repl_spec : spec -> ppobj -> ppobj
    99   val repl_subs : (string * string) list -> ppobj -> ppobj     *)
   100   val rootthy : ptree -> domID
   101 (*  val test_trans : ppobj -> bool
   102   val uni__asm : (string * pos) list -> ppobj -> ppobj
   103   val uni__cid : cellID list -> ppobj -> ppobj                 *)
   104   val union_asm : ptree -> pos -> (string * pos) list -> ptree
   105   val union_cid : ptree -> pos -> cellID list -> ptree
   106   val update_branch : ptree -> pos -> branch -> ptree
   107   val update_domID : ptree -> pos -> domID -> ptree
   108   val update_met : ptree -> pos -> meth -> ptree
   109   val update_metppc : ptree -> pos -> item ppc -> ptree
   110   val update_metID : ptree -> pos -> metID -> ptree
   111   val update_tac : ptree -> pos -> tac -> ptree
   112   val update_pbl : ptree -> pos -> pblID * item ppc -> ptree
   113   val update_pblppc : ptree -> pos -> item ppc -> ptree
   114   val update_pblID : ptree -> pos -> pblID -> ptree
   115   val update_spec : ptree -> pos -> spec -> ptree
   116   val update_subs : ptree -> pos -> (string * string) list -> ptree
   117 
   118   val rep_pblobj : ppobj
   119     -> {branch:branch, cell:cid, env:envp, loc:loc, meth:meth, model:cterm' ppc,
   120         origin:cterm' list * spec, ostate:ostate, probl:pblID * item ppc,
   121         result:cterm', spec:spec}
   122   val rep_prfobj : ppobj
   123     -> {branch:branch, cell:cid, form:cterm', loc:loc, tac:tac,
   124         ostate:ostate, result:cterm'}
   125 end 
   126 
   127 (* -------------- 
   128 structure Ptree (**): PTREE (**) =
   129 struct
   130  -------------- *)
   131 
   132 type env = (term * term) list;
   133 
   134    
   135 datatype branch = 
   136 	 NoBranch | AndB | OrB 
   137        | TransitiveB  (* FIXXXME.8.03: set branch from met in Apply_Method
   138                          FIXXXME.0402: -"- in Begin_Trans'*)
   139        | SequenceB | IntersectB | CollectB | MapB;
   140 fun branch2str NoBranch = "NoBranch"
   141   | branch2str AndB = "AndB"
   142   | branch2str OrB = "OrB"
   143   | branch2str TransitiveB = "TransitiveB" 
   144   | branch2str SequenceB = "SequenceB"
   145   | branch2str IntersectB = "IntersectB"
   146   | branch2str CollectB = "CollectB"
   147   | branch2str MapB = "MapB";
   148 
   149 datatype ostate = 
   150     Incomplete | Complete | Inconsistent(*WN041020 latter unused*);
   151 fun ostate2str Incomplete = "Incomplete"
   152   | ostate2str Complete = "Complete"
   153   | ostate2str Inconsistent = "Inconsistent";
   154 
   155 type cellID = int;     
   156 type cid = cellID list;
   157 
   158 type posel = int;     (* roundabout for (some of) nice signatures *)
   159 type pos = posel list;
   160 val pos2str = ints2str';
   161 datatype pos_ = 
   162     Pbl    (*PblObj-position: problem-type*)
   163   | Met    (*PblObj-position: method*)
   164   | Frm    (*PblObj-position: -> Pbl in ME (not by moveDown !)
   165            | PrfObj-position: formula*)
   166   | Res    (*PblObj | PrfObj-position: result*)
   167   | Und;   (*undefined*)
   168 fun pos_2str Pbl = "Pbl"
   169   | pos_2str Met = "Met"
   170   | pos_2str Frm = "Frm"
   171   | pos_2str Res = "Res"
   172   | pos_2str Und = "Und";
   173 
   174 type pos' = pos * pos_;
   175 (*WN.12.03 remembering interator (pos * pos_) for ptree 
   176 	   pos : lev_on, lev_dn, lev_up, 
   177                  lev_onFrm, lev_dnRes (..see solve Apply_Method !) 
   178            pos_:
   179 # generate1 sets pos_ if possible  ...?WN0502?NOT...
   180 # generate1 does NOT set pos, because certain nodes can be lev_on OR lev_dn
   181                      exceptions: Begin/End_Trans
   182 # thus generate(1) called in
   183 .# assy, locate_gen 
   184 .# nxt_solv (tac_ -cases); general case: 
   185   val pos' = case pos' of (p,Res) => (lev_on p',Res) | _ => pos'
   186 # WN050220, S(604):
   187   generate1...(Rewrite(f,..,res))..(pos, pos_)
   188      cappend_atomic.................pos //////  gets f+res always!!!
   189         cut_tree....................pos, pos_ 
   190 *)
   191 fun pos'2str (p,p_) = pair2str (ints2str' p, pos_2str p_);
   192 fun pos's2str ps = (strs2str' o (map pos'2str)) ps;
   193 val e_pos' = ([],Und):pos';
   194 
   195 fun res2str (t, ts) = pair2str (term2str t, terms2str ts);
   196 fun asm2str (t, p:pos) = pair2str (term2str t, ints2str' p);
   197 fun asms2str asms = (strs2str' o (map asm2str)) asms;
   198 
   199 
   200 
   201 datatype lrd = (*elements of a path (=loc_) into an Isabelle term*)
   202 	 L     (*go left at $*) 
   203        | R     (*go right at $*)
   204        | D;     (*go down at Abs*)
   205 type loc_ = lrd list;
   206 fun ldr2str L = "L"
   207   | ldr2str R = "R"
   208   | ldr2str D = "D";
   209 fun loc_2str (k:loc_) = (strs2str' o (map ldr2str)) k;
   210 
   211 (*26.4.02: never used after introduction of scripts !!!
   212 type loc =  loc_ *        (* + interpreter-state          *)
   213 	    (loc_ * rls') (* -"- for script of the ruleset*)
   214 		option;
   215 val e_loc = ([],None):loc;
   216 val ee_loc = (e_loc,e_loc);*)
   217 
   218 
   219 datatype safe = Sundef | Safe | Unsafe | Helpless;
   220 fun safe2str Sundef   = "Sundef"
   221   | safe2str Safe     = "Safe"
   222   | safe2str Unsafe   = "Unsafe" 
   223   | safe2str Helpless = "Helpless";
   224 
   225 type subs = cterm' list; (*16.11.00 for FE-KE*)
   226 val e_subs = ["(bdv, x)"];
   227 
   228 (*._sub_stitution as strings of _e_qualities.*)
   229 type sube = cterm' list;
   230 val e_sube = []:cterm' list;
   231 fun sube2str s = strs2str s;
   232 
   233 (*._sub_stitution as _t_erms of _e_qualities.*)
   234 type subte = term list;
   235 val e_subte = []:term list;
   236 fun subte2str ss = terms2str ss;
   237 
   238 fun subte2sube ss = map term2str ss;
   239 
   240 (*fun subst2str' thy' (s:subst) =
   241   (strs2str o 
   242    (map (pair2str o
   243 	 (apsnd (Sign.string_of_term (sign_of (assoc_thy thy')))) o 
   244 	 (apfst (Sign.string_of_term (sign_of (assoc_thy thy'))))))) s;*)
   245 fun subst2subs s = map (pair2str o 
   246 			(apfst (Sign.string_of_term (sign_of thy))) o
   247 			(apsnd (Sign.string_of_term (sign_of thy)))) s;
   248 fun subst2subs' s = map ((apfst (Sign.string_of_term (sign_of thy))) o
   249 			 (apsnd (Sign.string_of_term (sign_of thy)))) s;
   250 fun subs2subst thy s = map (isapair2pair o term_of o the o (parse thy)) s;
   251 (*> subs2subst thy ["(bdv,x)","(err,#0)"];
   252 val it =
   253   [(Free ("bdv","RealDef.real"),Free ("x","RealDef.real")),
   254    (Free ("err","RealDef.real"),Free ("#0","RealDef.real"))] 
   255    : (term * term) list*)
   256 fun sube2subte ss = map str2term ss;
   257 
   258 
   259 fun isasub2subst isasub = ((map isapair2pair) o isalist2list) isasub;
   260 
   261 
   262 type scrstate =       (*state for script interpreter*)
   263 	 env(*stack*) (*used to instantiate tac for checking assod
   264 		       12.03.noticed: e_ not updated during execution ?!?*)
   265 	 * loc_       (*location of tac in script*)
   266 	 * term option(*argument of curried functions*)
   267 	 * term       (*value obtained by tac executed
   268 		       updated also after a derivation by 'new_val'*)
   269 	 * safe       (*estimation of how result will be obtained*)
   270 	 * bool;      (*true = strongly .., false = weakly associated: 
   271 					    only used during ass_dn/up*)
   272 val e_scrstate = ([],[],None,e_term,Sundef,false):scrstate;
   273 
   274 
   275 (*21.8.02 ---> definitions.sml for datatype scr 
   276 type rrlsstate =      (*state for reverse rewriting*)
   277      (term *          (*the current formula*)
   278       rule list      (*of reverse rewrite set (#1#)*)
   279 	    list *    (*may be serveral, eg. in norm_rational*)
   280       (rule *         (*Thm (+ Thm generated from Calc) resulting in ...*)
   281        (term *        (*... rewrite with ...*)
   282 	term list))   (*... assumptions*)
   283 	  list);      (*derivation from given term to normalform
   284 		       in reverse order with sym_thm; 
   285                        (#1#) could be extracted from here #1*) --------*)
   286      
   287 datatype istate =     (*interpreter state*)
   288 	 Uistate                 (*undefined in modspec, in '_deriv'ation*)
   289        | ScrState of scrstate    (*for script interpreter*)
   290        | RrlsState of rrlsstate; (*for reverse rewriting*)
   291 val e_istate = (ScrState ([],[],None,e_term,Sundef,false)):istate;
   292 
   293 type iist = istate option * istate option;
   294 (*val e_iist = (e_istate, e_istate); --- sinnlos f"ur NICHT-equality-type*) 
   295 
   296 
   297 fun rta2str (r,(t,a)) = "\n("^(rule2str r)^",("^(term2str t)^", "^
   298 		      (terms2str a)^"))";
   299 fun istate2str Uistate = "Uistate"
   300   | istate2str (ScrState (e,l,to,t,s,b):istate) =
   301     "ScrState ("^ subst2str e ^",\n "^ 
   302     loc_2str l ^", "^ termopt2str to ^",\n "^
   303     term2str t ^", "^ safe2str s ^", "^ bool2str b ^")"
   304   | istate2str (RrlsState (t,t1,rss,rtas)) = 
   305     "RrlsState ("^(term2str t)^", "^(term2str t1)^", "^
   306     ((strs2str o (map (strs2str o (map rule2str)))) rss)^", "^
   307     ((strs2str o (map rta2str)) rtas)^")";
   308 fun istates2str (None, None) = "(#None, #None)"
   309   | istates2str (None, Some ist) = "(#None,\n#Some "^istate2str ist^")"
   310   | istates2str (Some ist, None) = "(#Some "^istate2str ist^",\n #None)"
   311   | istates2str (Some i1, Some i2) = "(#Some "^istate2str i1^",\n #Some "^
   312 				     istate2str i2^")";
   313 
   314 fun new_val v (ScrState (env, loc_, topt, _, safe, bool)) =
   315     (ScrState (env, loc_, topt, v, safe, bool))
   316   | new_val _ _ = raise error "new_val: only for ScrState";
   317 
   318 datatype con = land | lor;
   319 
   320 
   321 type spec = 
   322      domID * (*WN.12.03: is replaced by thy from get_met ?FIXME? in:
   323 	      specify (Init_Proof..), nxt_specify_init_calc,
   324 	      assod (.SubProblem...), stac2tac (.SubProblem...)*)
   325      pblID * 
   326      metID;
   327 fun spec2str ((dom,pbl,met)(*:spec*)) = 
   328   "(" ^ (quote dom) ^ ", " ^ (strs2str pbl) ^ 
   329   ", " ^ (strs2str met) ^ ")";
   330 (*> spec2str empty_spec;
   331 val it = "(\"\", [], (\"\", \"\"))" : string *)
   332 val empty_spec = (e_domID,e_pblID,e_metID):spec;
   333 val e_spec = empty_spec;
   334 
   335 
   336 
   337 (*.tactics propagate the construction of the calc-tree;
   338    there are
   339    (a) 'specsteps' for the specify-phase, and others for the solve-phase
   340    (b) those of the solve-phase are 'initac's and others;
   341        initacs start with a formula different from the preceding formula.
   342    see 'type tac_' for the internal representation of tactics.*)
   343 datatype tac = 
   344   Init_Proof of ((cterm' list) * spec)
   345 (*'specsteps'...*)
   346 | Model_Problem
   347 | Refine_Problem of pblID              | Refine_Tacitly of pblID
   348 
   349 | Add_Given of cterm'                  | Del_Given of cterm'
   350 | Add_Find of cterm'                   | Del_Find of cterm'
   351 | Add_Relation of cterm'               | Del_Relation of cterm'
   352 
   353 | Specify_Theory of domID              | Specify_Problem of pblID
   354 | Specify_Method of metID
   355 (*...'specsteps'*)
   356 | Apply_Method of metID 
   357 (*.creates an 'istate' in PblObj.env; in case of 'init_form' 
   358    creates a formula at ((lev_on o lev_dn) p, Frm) and in this ppobj.'loc' 
   359    'Some istate' (at fst of 'loc').
   360    As each step (in the solve-phase) has a resulting formula (at the front-end)
   361    Apply_Method also does the 1st step in the script (an 'initac') if there
   362    is no 'init_form' .*)
   363 | Check_Postcond of pblID
   364 | Free_Solve
   365 
   366 | Rewrite_Inst of ( subs * thm')       | Rewrite of thm'
   367                                        | Rewrite_Asm of thm'
   368 | Rewrite_Set_Inst of ( subs * rls')   | Rewrite_Set of rls'        
   369 | Detail_Set_Inst of ( subs * rls')    | Detail_Set of rls'
   370 | End_Detail  (*end of script from next_tac, 
   371                 in solve: switches back to parent script WN0509 drop!*)
   372 | Derive of rls' (*an input formula using rls WN0509 drop!*)
   373 | Calculate of string (* plus | minus | times | cancel | pow | sqrt *)
   374 | End_Ruleset
   375 | Substitute of sube                   | Apply_Assumption of cterm' list
   376 
   377 | Take of cterm'      (*an 'initac'*)
   378 | Take_Inst of cterm'  
   379 | Group of (con * int list ) 
   380 | Subproblem of (domID * pblID) (*an 'initac'*)
   381 | CAScmd of cterm'  (*6.6.02 URD: Function formula; WN0509 drop!*)
   382 | End_Subproblem    (*WN0509 drop!*)
   383 
   384 | Split_And                            | Conclude_And
   385 | Split_Or                             | Conclude_Or
   386 | Begin_Trans                          | End_Trans
   387 | Begin_Sequ                           | End_Sequ(* substitute root.env *)
   388 | Split_Intersect                      | End_Intersect
   389 | Check_elementwise of cterm'          | Collect_Trues
   390 | Or_to_List
   391 
   392 | Empty_Tac (*TODO.11.6.03 ... of string: could carry msg of (Notappl msg)
   393 	       in 'helpless'*)
   394 | Tac of string(* eg.'repeat'*WN0509 drop!*)
   395 | User                                 (*internal, for ets*WN0509 drop!*)
   396 | End_Proof';(* inout*)
   397 
   398 (* tac2str /--> library.sml: needed in dialog.sml for 'separable *)
   399 fun tac2str (ma:tac) = case ma of
   400     Init_Proof (ppc, spec)  => 
   401       "Init_Proof "^(pair2str (strs2str ppc, spec2str spec))
   402   | Model_Problem           => "Model_Problem "
   403   | Refine_Tacitly pblID    => "Refine_Tacitly "^(strs2str pblID)
   404   | Refine_Problem pblID    => "Refine_Problem "^(strs2str pblID)
   405   | Add_Given cterm'        => "Add_Given "^cterm'
   406   | Del_Given cterm'        => "Del_Given "^cterm'
   407   | Add_Find cterm'         => "Add_Find "^cterm'
   408   | Del_Find cterm'         => "Del_Find "^cterm'
   409   | Add_Relation cterm'     => "Add_Relation "^cterm'
   410   | Del_Relation cterm'     => "Del_Relation "^cterm'
   411 
   412   | Specify_Theory domID    => "Specify_Theory "^(quote domID    )
   413   | Specify_Problem pblID   => "Specify_Problem "^(strs2str pblID )
   414   | Specify_Method metID    => "Specify_Method "^(strs2str metID)
   415   | Apply_Method metID      => "Apply_Method "^(strs2str metID)
   416   | Check_Postcond pblID    => "Check_Postcond "^(strs2str pblID)
   417   | Free_Solve              => "Free_Solve"
   418 
   419   | Rewrite_Inst (subs,thm')=> 
   420       "Rewrite_Inst "^(pair2str (subs2str subs, spair2str thm'))
   421   | Rewrite thm'            => "Rewrite "^(spair2str thm')
   422   | Rewrite_Asm thm'        => "Rewrite_Asm "^(spair2str thm')
   423   | Rewrite_Set_Inst (subs, rls) => 
   424       "Rewrite_Set_Inst "^(pair2str (subs2str subs, quote rls))
   425   | Rewrite_Set rls         => "Rewrite_Set "^(quote rls    )
   426   | Detail_Set rls          => "Detail_Set "^(quote rls    )
   427   | Detail_Set_Inst (subs, rls) => 
   428       "Detail_Set_Inst "^(pair2str (subs2str subs, quote rls))
   429   | End_Detail              => "End_Detail"
   430   | Derive rls'             => "Derive "^rls' 
   431   | Calculate op_           => "Calculate "^op_ 
   432   | Substitute sube         => "Substitute "^sube2str sube	     
   433   | Apply_Assumption ct's   => "Apply_Assumption "^(strs2str ct's)
   434 
   435   | Take cterm'             => "Take "^(quote cterm'	)
   436   | Take_Inst cterm'        => "Take_Inst "^(quote cterm' )
   437   | Group (con, ints)       => 
   438       "Group "^(pair2str (con2str con, ints2str ints))
   439   | Subproblem (domID, pblID) => 
   440       "Subproblem "^(pair2str (domID, strs2str pblID))
   441 (*| Subproblem_Full (spec, cts') => 
   442       "Subproblem_Full "^(pair2str (spec2str spec, strs2str cts'))*)
   443   | End_Subproblem          => "End_Subproblem"
   444   | CAScmd cterm'           => "CAScmd "^(quote cterm')
   445 
   446   | Check_elementwise cterm'=> "Check_elementwise "^(quote cterm') 
   447   | Or_to_List              => "Or_to_List "
   448   | Collect_Trues           => "Collect_Trues"
   449 
   450   | Empty_Tac             => "Empty_Tac"
   451   | Tac string            => "Tac "^string
   452   | User                    => "User"
   453   | End_Proof'              => "tac End_Proof'"
   454   | _                       => "tac2str not impl. for ?!";
   455 
   456 fun is_rewset (Rewrite_Set_Inst _) = true
   457   | is_rewset (Rewrite_Set _) = true 
   458   | is_rewset _ = false;
   459 fun is_rewtac (Rewrite _) = true
   460   | is_rewtac (Rewrite_Inst _) = true
   461   | is_rewtac (Rewrite_Asm _) = true
   462   | is_rewtac tac = is_rewset tac;
   463 
   464 fun tac2IDstr (ma:tac) = case ma of
   465     Model_Problem           => "Model_Problem"
   466   | Refine_Tacitly pblID    => "Refine_Tacitly"
   467   | Refine_Problem pblID    => "Refine_Problem"
   468   | Add_Given cterm'        => "Add_Given"
   469   | Del_Given cterm'        => "Del_Given"
   470   | Add_Find cterm'         => "Add_Find"
   471   | Del_Find cterm'         => "Del_Find"
   472   | Add_Relation cterm'     => "Add_Relation"
   473   | Del_Relation cterm'     => "Del_Relation"
   474 
   475   | Specify_Theory domID    => "Specify_Theory"
   476   | Specify_Problem pblID   => "Specify_Problem"
   477   | Specify_Method metID    => "Specify_Method"
   478   | Apply_Method metID      => "Apply_Method"
   479   | Check_Postcond pblID    => "Check_Postcond"
   480   | Free_Solve              => "Free_Solve"
   481 
   482   | Rewrite_Inst (subs,thm')=> "Rewrite_Inst"
   483   | Rewrite thm'            => "Rewrite"
   484   | Rewrite_Asm thm'        => "Rewrite_Asm"
   485   | Rewrite_Set_Inst (subs, rls) => "Rewrite_Set_Inst"
   486   | Rewrite_Set rls         => "Rewrite_Set"
   487   | Detail_Set rls          => "Detail_Set"
   488   | Detail_Set_Inst (subs, rls) => "Detail_Set_Inst"
   489   | Derive rls'             => "Derive "
   490   | Calculate op_           => "Calculate "
   491   | Substitute subs         => "Substitute" 
   492   | Apply_Assumption ct's   => "Apply_Assumption"
   493 
   494   | Take cterm'             => "Take"
   495   | Take_Inst cterm'        => "Take_Inst"
   496   | Group (con, ints)       => "Group"
   497   | Subproblem (domID, pblID) => "Subproblem"
   498   | End_Subproblem          => "End_Subproblem"
   499   | CAScmd cterm'           => "CAScmd"
   500 
   501   | Check_elementwise cterm'=> "Check_elementwise"
   502   | Or_to_List              => "Or_to_List "
   503   | Collect_Trues           => "Collect_Trues"
   504 
   505   | Empty_Tac             => "Empty_Tac"
   506   | Tac string            => "Tac "
   507   | User                    => "User"
   508   | End_Proof'              => "End_Proof'"
   509   | _                       => "tac2str not impl. for ?!";
   510 
   511 fun thm_of_rew (Rewrite_Inst (subs,(thmID,_))) = 
   512     (thmID, Some ((subs2subst (assoc_thy "Isac.thy") subs):subst))
   513   | thm_of_rew (Rewrite  (thmID,_)) = (thmID, None)
   514   | thm_of_rew (Rewrite_Asm (thmID,_)) = (thmID, None);
   515 
   516 fun rls_of_rewset (Rewrite_Set_Inst (subs,rls)) = 
   517     (rls, Some ((subs2subst (assoc_thy "Isac.thy") subs):subst))
   518   | rls_of_rewset (Rewrite_Set rls) = (rls, None)
   519   | rls_of_rewset (Detail_Set rls) = (rls, None)
   520   | rls_of_rewset (Detail_Set_Inst (subs, rls)) = 
   521     (rls, Some ((subs2subst (assoc_thy "Isac.thy") subs):subst));
   522 
   523 
   524 
   525 type fmz_ = cterm' list;
   526 
   527 (*.a formalization of an example containing data 
   528    sufficient for mechanically finding the solution for the example.*)
   529 (*FIXME.WN051014: dont store fmz = (_,spec) in the PblObj, 
   530   this is done in origin*)
   531 type fmz = fmz_ * spec;
   532 val e_fmz = ([],e_spec);
   533 
   534 (*tac_ is made from tac in applicable_in,
   535   and carries all data necessary for generate;*)
   536 datatype tac_ = 
   537 (* datatype tac = *)
   538   Init_Proof' of ((cterm' list) * spec)
   539                 (* ori list !: code specify -> applicable*)
   540 | Model_Problem' of pblID * 
   541 		    itm list *  (*the 'untouched' pbl*)
   542 		    itm list    (*the casually completed met*)
   543 | Refine_Tacitly' of pblID *    (*input*)
   544 		     pblID *    (*the refined from applicable_in*)
   545 		     domID *    (*from new pbt?! filled in specify*)
   546 		     metID *    (*from new pbt?! filled in specify*)
   547 		     itm list   (*drop ! 9.03: remains [] for
   548                                   Model_Problem recognizing its activation*)
   549 | Refine_Problem' of (pblID * (itm list * (bool * Term.term) list))
   550  (*FIXME?040215 drop: done automatically in init_proof + Subproblem'*)
   551 | Add_Given'    of cterm' *
   552 		   itm list (*updated with input in fun specify_additem*)
   553 | Add_Find'     of cterm' *
   554 		   itm list (*updated with input in fun specify_additem*)
   555 | Add_Relation' of cterm' *
   556 		 itm list (*updated with input in fun specify_additem*)
   557 | Del_Given' of cterm'   | Del_Find' of cterm'   | Del_Relation' of cterm'
   558   (*4.00.: all..    term: in applicable_in ..? Syn ?only for FormFK?*)
   559 
   560 | Specify_Theory' of domID              
   561 | Specify_Problem' of (pblID *        (*               *)
   562 		       (bool *        (* matches	     *)
   563 			(itm list *   (* ppc	     *)
   564 			 (bool * term) list))) (* preconditions *)
   565 | Specify_Method' of metID *
   566 		     ori list * (*repl. "#undef"*)
   567 		     itm list   (*... updated from pbl to met*)
   568 | Apply_Method' of metID * 
   569 		   (term option) * (*init_form*)
   570 		   istate		        
   571 | Check_Postcond' of 
   572   pblID * 
   573   (term *      (*returnvalue of script in solve*)
   574    cterm' list)(*collect by get_assumptions_ in applicable_in, except if 
   575                  butlast tac is Check_elementwise: take only these asms*)
   576 | Free_Solve'
   577 
   578 | Rewrite_Inst' of theory' * rew_ord' * rls
   579 		   * bool * subst * thm' * term * (term  * term list)
   580 | Rewrite' of theory' * rew_ord' * rls * bool * thm' * 
   581 	      term * (term * term list)
   582 | Rewrite_Asm' of theory' * rew_ord' * rls * bool * thm' * 
   583   term * (term * term list)
   584 | Rewrite_Set_Inst' of theory' * bool * subst * rls * 
   585 		       term * (term * term list)
   586 | Detail_Set_Inst' of theory' * bool * subst * rls * 
   587 		      term * (term * term list)
   588 | Rewrite_Set' of theory' * bool * rls * term * (term * term list)
   589 | Detail_Set' of theory' * bool * rls * term * (term * term list)
   590 | End_Detail' of (term * (term list)) (*see End_Trans'*)
   591 | End_Ruleset' of term
   592 | Derive' of rls
   593 | Calculate' of theory' * string * term * (term * thm') 
   594 	      (*WN.29.4.03 asm?: * term list??*)
   595 | Substitute' of subte  (*the 'substitution': terms of type bool*) 
   596 		 * term (*to be substituted in*)
   597 		 * term (*resulting from the substitution*)
   598 | Apply_Assumption' of term list * term
   599 
   600 | Take' of term                         | Take_Inst' of term  
   601 | Group' of (con * int list * term)
   602 | Subproblem' of (spec * 
   603 		  (ori list) * (*filled in assod Subproblem'*)
   604 		  term *       (*-"-, headline of calc-head *)
   605 		  fmz_ * 
   606 		  term)        (*Subproblem(dom,pbl)*)  
   607 | CAScmd' of term
   608 | End_Subproblem' of term (*???*)
   609 | Split_And' of term                    | Conclude_And' of term
   610 | Split_Or' of term                     | Conclude_Or' of term
   611 | Begin_Trans' of term                  | End_Trans' of (term * (term list))
   612 | Begin_Sequ'                           | End_Sequ'(* substitute root.env*)
   613 | Split_Intersect' of term              | End_Intersect' of term
   614 | Check_elementwise' of (*special case:*)
   615   term *   (*(1)the current formula: [x=1,x=...]*)
   616   string * (*(2)the pred from Check_elementwise   *)
   617   (term *  (*(3)composed from (1) and (2): {x. pred}*)
   618    term list) (*20.5.03 assumptions*)
   619 
   620 | Or_to_List' of term * term            (* (a | b, [a,b]) *)
   621 | Collect_Trues' of term
   622 
   623 | Empty_Tac_                          | Tac_ of  (*for dummies*)
   624                                             theory *
   625                                             string * (*form*)
   626 					    string * (*in Tac*)
   627 					    string   (*result of Tac".."*)
   628 | User' (*internal for ets*)            | End_Proof'';(*End_Proof:inout*)
   629 
   630 fun tac_2str ma = case ma of
   631     Init_Proof' (ppc, spec)  => 
   632       "Init_Proof' "^(pair2str (strs2str ppc, spec2str spec))
   633   | Model_Problem' (pblID,_,_)     => "Model_Problem' "^(strs2str pblID )
   634   | Refine_Tacitly'(p,prefin,domID,metID,itms)=> 
   635     "Refine_Tacitly' ("
   636     ^(strs2str p)^", "^(strs2str prefin)^", "
   637     ^domID^", "^(strs2str metID)^", pbl-itms)"
   638   | Refine_Problem' ms       => "Refine_Problem' ("^(*matchs2str ms*)"..."^")"
   639 (*| Match_Problem' (pI, (ok, (itms, pre))) => 
   640     "Match_Problem' "^(spair2str (strs2str pI,
   641 				  spair2str (bool2str ok,
   642 					     spair2str ("itms2str itms", 
   643 							"items2str pre"))))*)
   644   | Add_Given' cterm'        => "Add_Given' "(*^cterm'*)
   645   | Del_Given' cterm'        => "Del_Given' "(*^cterm'*)
   646   | Add_Find' cterm'         => "Add_Find' "(*^cterm'*)
   647   | Del_Find' cterm'         => "Del_Find' "(*^cterm'*)
   648   | Add_Relation' cterm'     => "Add_Relation' "(*^cterm'*)
   649   | Del_Relation' cterm'     => "Del_Relation' "(*^cterm'*)
   650 
   651   | Specify_Theory' domID    => "Specify_Theory' "^(quote domID    )
   652   | Specify_Problem' (pI, (ok, (itms, pre))) => 
   653     "Specify_Problem' "^(spair2str (strs2str pI,
   654 				  spair2str (bool2str ok,
   655 					     spair2str ("itms2str itms", 
   656 							"items2str pre"))))
   657   | Specify_Method' (pI,oris,itms) => 
   658     "Specify_Method' ("^metID2str pI^", "^oris2str oris^", )"
   659 
   660   | Apply_Method' (metID,_,_)      => "Apply_Method' "^(strs2str metID)
   661   | Check_Postcond' (pblID,(scval,asm)) => 
   662       "Check_Postcond' "^(spair2str(strs2str pblID, 
   663 				    spair2str (term2str scval, strs2str asm)))
   664 
   665   | Free_Solve'              => "Free_Solve'"
   666 
   667   | Rewrite_Inst' (*subs,thm'*) _ => 
   668       "Rewrite_Inst' "(*^(pair2str (subs2str subs, spair2str thm'))*)
   669   | Rewrite' thm'            => "Rewrite' "(*^(spair2str thm')*)
   670   | Rewrite_Asm' thm'        => "Rewrite_Asm' "(*^(spair2str thm')*)
   671   | Rewrite_Set_Inst' (*subs,thm'*) _ => 
   672       "Rewrite_Set_Inst' "(*^(pair2str (subs2str subs, quote rls))*)
   673   | Rewrite_Set'(thy',pasm,rls',f,(f',asm))          
   674     => "Rewrite_Set' ("^thy'^","^(bool2str pasm)^","^(id_rls rls')^","
   675     ^(Sign.string_of_term (sign_of thy) f)^",("^(Sign.string_of_term (sign_of thy) f')
   676     ^","^((strs2str o (map (Sign.string_of_term (sign_of thy)))) asm)^"))"
   677 
   678   | End_Detail' _             => "End_Detail' xxx"
   679   | Detail_Set' _             => "Detail_Set' xxx"
   680   | Detail_Set_Inst' _        => "Detail_Set_Inst' xxx"
   681 
   682   | Derive' rls              => "Derive' "^id_rls rls
   683   | Calculate'  _            => "Calculate' "
   684   | Substitute' subs         => "Substitute' "(*^(subs2str subs)*)    
   685   | Apply_Assumption' ct's   => "Apply_Assumption' "(*^(strs2str ct's)*)
   686 
   687   | Take' cterm'             => "Take' "(*^(quote cterm'	)*)
   688   | Take_Inst' cterm'        => "Take_Inst' "(*^(quote cterm' )*)
   689   | Group' (con, ints, _)     => 
   690       "Group' "^(pair2str (con2str con, ints2str ints))
   691   | Subproblem' (spec, oris, _,_,pbl_form) => 
   692       "Subproblem' "(*^(pair2str (domID, strs2str ,...))*)
   693   | End_Subproblem'  _       => "End_Subproblem'"
   694   | CAScmd' cterm'           => "CAScmd' "(*^(quote cterm')*)
   695 
   696   | Empty_Tac_             => "Empty_Tac_"
   697   | User'                    => "User'"
   698   | Tac_ (_,form,id,result) => "Tac_ (thy,"^form^","^id^","^result^")"
   699   | _                       => "tac_2str not impl. for arg";
   700 
   701 (*'executed tactics' (tac_s) with local environment etc.;
   702   used for continuing eval script + for generate*)
   703 type ets =
   704     (loc_ *      (* of tactic in scr, tactic (weakly) associated with tac_*)
   705      (tac_ * 	 (* (for generate)  *)
   706       env *      (* with 'tactic=result' as a rule, tactic ev. _not_ ready:
   707 		  for handling 'parallel let'*)
   708       env *      (* with results of (ready) tacs        *)
   709       term *     (* itr_arg of tactic, for upd. env at Repeat, Try*)
   710       term * 	 (* result value of the tac         *)
   711       safe))
   712     list;
   713 val Ets = []:ets;
   714 
   715 
   716 fun ets2s (l,(m,eno,env,iar,res,s)) = 
   717   "\n("^(loc_2str l)^",("^(tac_2str m)^
   718   ",\n  ens= "^(subst2str eno)^
   719   ",\n  env= "^(subst2str env)^
   720   ",\n  iar= "^(Sign.string_of_term (sign_of thy) iar)^
   721   ",\n  res= "^(Sign.string_of_term (sign_of thy) res)^
   722   ",\n  "^(safe2str s)^"))";
   723 fun ets2str (ets:ets) = (strs2str o (map ets2s)) ets;
   724 
   725 
   726 type envp =(*9.5.03: unused, delete with field in ptree.PblObj FIXXXME*)
   727    (int * term list) list * (*assoc-list: args of met*)
   728    (int * rls) list *       (*assoc-list: tacs already done ///15.9.00*)
   729    (int * ets) list *       (*assoc-list: tacs etc. already done*)
   730    (string * pos) list;     (*asms * from where*)
   731 val empty_envp = ([],[],[],[]):envp; 
   732 
   733 datatype ppobj = 
   734     PrfObj of {cell  : lrd option, (*where in form tac has been applied*)
   735 	       (*^^^FIXME.WN0607 rename this field*)
   736 	       form  : term,    
   737 	       tac   : tac,         (* also in istate*)
   738 	       loc   : istate option * istate option, (*for form, result 
   739 13.8.02: (None,None) <==> e_istate ! see update_loc, get_loc*)
   740 	       branch: branch,
   741 	       result: term * term list,    
   742 	       ostate: ostate}    (*Complete <=> result is OK*)
   743   | PblObj of {cell  : lrd option,(*unused: meaningful only for some _Prf_Obj*)
   744 	       fmz   : fmz,       (*from init:FIXME never use this spec;-drop*)
   745 	       origin: (ori list) * (*representation from fmz+pbt
   746                                   for efficiently adding items in probl, meth*)
   747 		       spec *     (*updated by Refine_Tacitly*)
   748 		       term,      (*headline of calc-head, as calculated 
   749 							      initially(!)*)
   750 		       (*# the origin of a root-pbl is created from fmz
   751                            (thus providing help for input to the user),
   752 			 # the origin of a sub-pbl is created from the argument
   753 			   -list of a script-tac 'SubProblem (spec) [arg-list]'
   754 			   by 'match_ags'*)
   755 	       spec  : spec,      (*explicitly input*)
   756 	       probl : itm list,  (*itms explicitly input*)
   757 	       meth  : itm list,  (*itms automatically added to copy of probl
   758 				   TODO: input like to 'probl'*)
   759 	       env   : istate option,(*for problem with initac in script*)
   760 	       loc   : istate option * istate option, (*for pbl+met * result*)
   761 	       branch: branch,
   762 	       result: term * term list,
   763 	       ostate: ostate};   (*Complete <=> result is _proven_ OK*)
   764 
   765 (*.this tree contains isac's calculations; TODO.WN03 rename to ctree;
   766    the structure has been copied from an early version of Theorema(c);
   767    it has the disadvantage, that there is no space 
   768    for the first tactic in a script generating the first formula at (p,Frm);
   769    this trouble has been covered by 'init_form' and 'Take' so far,
   770    but it is crucial if the first tactic in a script is eg. 'Subproblem';
   771    see 'type tac ', Apply_Method.
   772 .*)
   773 datatype ptree = 
   774     EmptyPtree
   775   | Nd of ppobj * (ptree list);
   776 val e_ptree = EmptyPtree;
   777 
   778 fun rep_prfobj (PrfObj {cell,form,tac,loc,branch,result,ostate}) =
   779   {cell=cell,form=form,tac=tac,loc=loc,branch=branch,result=result,ostate=ostate};
   780 fun rep_pblobj (PblObj {cell,origin,fmz,spec,probl,meth,env,
   781 			loc,branch,result,ostate}) =
   782   {cell=cell,origin=origin,fmz=fmz,spec=spec,probl=probl,meth=meth,
   783    env=env,loc=loc,branch=branch,result=result,ostate=ostate};
   784 fun is_prfobj (PrfObj _) = true
   785   | is_prfobj _ =false;
   786 (*val is_prfobj' = get_obj is_prfobj; *)
   787 fun is_pblobj (PblObj _) = true
   788   | is_pblobj _ = false;
   789 (*val is_pblobj' = get_obj is_pblobj; 'Error: unbound constructor get_obj'*)
   790 
   791 
   792 exception PTREE of string;
   793 fun nth _ []      = raise PTREE "nth _ []"
   794   | nth 1 (x::xs) = x
   795   | nth n (x::xs) = nth (n-1) xs;
   796 (*> nth 2 [11,22,33]; -->> val it = 22 : int*)
   797 
   798 fun lev_up ([]:pos) = raise PTREE "lev_up []"
   799   | lev_up p = (drop_last p):pos;
   800 fun lev_on ([]:pos) = raise PTREE "lev_on []"
   801   | lev_on pos = 
   802     let val len = length pos
   803     in (drop_last pos) @ [(nth len pos)+1] end;
   804 fun lev_onFrm ((p,_):pos') = (lev_on p,Frm):pos'
   805   | lev_onFrm p = raise PTREE ("*** lev_onFrm: pos'="^(pos'2str p));
   806 (*040216: for inform --> embed_deriv: remains on same level*)
   807 fun lev_back (([],_):pos') = raise PTREE "lev_on_back: called by ([],_)"
   808   | lev_back (p,_) =
   809     if last_elem p <= 1 then (p, Frm):pos' 
   810     else ((drop_last p) @ [(nth (length p) p) - 1], Res);
   811 (*.increase pos by n within a level.*)
   812 fun pos_plus 0 pos = pos
   813   | pos_plus n ((p,Frm):pos') = pos_plus (n-1) (p, Res)
   814   | pos_plus n ((p,  _):pos') = pos_plus (n-1) (lev_on p, Res);
   815 
   816 
   817 
   818 fun lev_pred ([]:pos) = raise PTREE "lev_pred []"
   819   | lev_pred (pos:pos) = 
   820     let val len = length pos
   821     in ((drop_last pos) @ [(nth len pos)-1]):pos end;
   822 (*lev_pred [1,2,3];
   823 val it = [1,2,2] : pos
   824 > lev_pred [1];
   825 val it = [0] : pos          *)
   826 
   827 fun lev_dn p = p @ [0];
   828 (*> (lev_dn o lev_on) [1,2,3];
   829 val it = [1,2,4,0] : pos    *)
   830 (*fun lev_dn' ((p,p_):pos') = (lev_dn p, Frm):pos'; WN.3.12.03: never used*)
   831 fun lev_dnRes ((p,_):pos') = (lev_dn p, Res):pos';
   832 
   833 (*4.4.00*)
   834 fun lev_up_ ((p,Res):pos') = (lev_up p,Res):pos'
   835   | lev_up_ p' = raise error ("lev_up_: called for "^(pos'2str p'));
   836 fun lev_dn_ ((p,_):pos') = (lev_dn p,Res):pos'
   837 fun ind ((p,_):pos') = length p; (*WN050108 deprecated in favour of lev_of*)
   838 fun lev_of ((p,_):pos') = length p;
   839 
   840 
   841 (** convert ptree to a string **)
   842 
   843 (* convert a pos from list to string *)
   844 fun pr_pos ps = (space_implode "." (map string_of_int ps))^".   ";
   845 (* show hd origin or form only *)
   846 fun pr_short (p:pos) (PblObj {origin = (ori,_,_),...}) = 
   847   ((pr_pos p) ^ " ----- pblobj -----\n")
   848 (*   ((((Sign.string_of_term (sign_of thy)) o #4 o hd) ori)^" "^
   849     (((Sign.string_of_term (sign_of thy)) o hd(*!?!*) o #5 o hd) ori))^
   850    "\n") *)
   851   | pr_short p (PrfObj {form = form,...}) =
   852   ((pr_pos p) ^ (term2str form) ^ "\n");
   853 (*
   854 fun pr_cell (p:pos) (PblObj {cell = c, origin = (ori,_,_),...}) = 
   855   ((ints2str c) ^"   "^ 
   856    ((((Sign.string_of_term (sign_of thy)) o #4 o hd) ori)^" "^
   857     (((Sign.string_of_term (sign_of thy)) o hd(*!?!*) o #5 o hd) ori))^
   858    "\n")
   859   | pr_cell p (PrfObj {cell = c, form = form,...}) =
   860   ((ints2str c) ^"   "^ (term2str form) ^ "\n");
   861 *)
   862 
   863 (* convert ptree *)
   864 fun pr_ptree f pt =
   865   let
   866     fun pr_pt pfn _  EmptyPtree = ""
   867       | pr_pt pfn ps (Nd (b, [])) = pfn ps b
   868       | pr_pt pfn ps (Nd (b, ts)) = (pfn ps b)^
   869       (prts pfn (ps:pos) 1 ts)
   870     and prts pfn ps p [] = ""
   871       | prts pfn ps p (t::ts) = (pr_pt pfn (ps @ [p]) t)^
   872       (prts pfn ps (p+1) ts)
   873   in pr_pt f [] pt end;
   874 (*
   875 > fun prfn ps b = (pr_pos ps)^"   "^b(*TODO*)^"\n";
   876 > val pt = ref EmptyPtree;
   877 > pt:=Nd("root",
   878        [Nd("xx1",[]),
   879 	Nd("xx2",
   880 	   [Nd("xx2.1.",[]),
   881 	    Nd("xx2.2.",[])]),
   882 	Nd("xx3",[])]);
   883 > writeln (pr_ptree prfn (!pt));
   884 *)
   885 
   886 
   887 (** access the branches of ptree **)
   888 
   889 fun ins_nth 1 e l  = e::l
   890   | ins_nth n e [] = raise PTREE "ins_nth n e []"
   891   | ins_nth n e (l::ls) = l::(ins_nth (n-1) e ls);
   892 fun repl []      _ _ = raise PTREE "repl [] _ _"
   893   | repl (l::ls) 1 e = e::ls
   894   | repl (l::ls) n e = l::(repl ls (n-1) e);
   895 fun repl_app ls n e = 
   896     let val lim = 1 + length ls
   897     in if n > lim then raise PTREE "repl_app: n > lim"
   898        else if n = lim then ls @ [e]
   899 	    else repl ls n e end;
   900 (*  
   901 > repl [1,2,3] 2 22222;
   902 val it = [1,22222,3] : int list
   903 > repl_app [1,2,3,4] 5 5555;
   904 val it = [1,2,3,4,5555] : int list
   905 > repl_app [1,2,3] 2 22222;
   906 val it = [1,22222,3] : int list
   907 > repl_app [1] 2 22222 ;
   908 val it = [1,22222] : int list
   909 *)
   910 
   911 
   912 (*.get from obj at pos by f : ppobj -> 'a.*)
   913 fun get_obj f EmptyPtree  (_:pos)  = raise PTREE "get_obj f EmptyPtree"
   914   | get_obj f (Nd (b,  _)) []      = f b
   915   | get_obj f (Nd (b, bs)) (p::ps) =
   916 (* val (f, Nd (b, bs), (p::ps)) = (I, pt, p);
   917    *)
   918   let val _ = (nth p bs) handle _ => raise PTREE ("get_obj: pos = "^
   919 			   (ints2str' (p::ps))^" does not exist");
   920   in (get_obj f (nth p bs) (ps:pos)) 
   921       (*before WN050419: 'wrong type..' raised also if pos doesn't exist*)
   922     handle _ => raise PTREE (*"get_obj: at pos = "^
   923 			     (ints2str' (p::ps))^" wrong type of ppobj"*)
   924 			  ("get_obj: pos = "^
   925 			   (ints2str' (p::ps))^" does not exist")
   926   end;
   927 fun get_nd EmptyPtree _ = raise PTREE "get_nd EmptyPtree"
   928   | get_nd n [] = n
   929   | get_nd (Nd (_,nds)) (pos as p::(ps:pos)) = (get_nd (nth p nds) ps)
   930     handle _ => raise PTREE ("get_nd: not existent pos = "^(ints2str' pos));
   931 
   932 
   933 (* for use by get_obj *)
   934 fun g_cell   (PblObj {cell = c,...}) = None
   935   | g_cell   (PrfObj {cell = c,...}) = c;(*WN0607 hack for quick introduction of lrd + rewrite-at (thms, calcs)*)
   936 fun g_form   (PrfObj {form = f,...}) = f
   937   | g_form   (PblObj {origin=(_,_,f),...}) = f;
   938 fun g_form' (Nd (PrfObj {form = f,...}, _)) = f
   939   | g_form' (Nd (PblObj {origin=(_,_,f),...}, _)) = f;
   940 (*  | g_form   _ = raise PTREE "g_form not for PblObj";*)
   941 fun g_origin (PblObj {origin = ori,...}) = ori
   942   | g_origin _ = raise PTREE "g_origin not for PrfObj";
   943 fun g_fmz (PblObj {fmz = f,...}) = f
   944   | g_fmz _ = raise PTREE "g_fmz not for PrfObj";
   945 fun g_spec   (PblObj {spec = s,...}) = s
   946   | g_spec _   = raise PTREE "g_spec not for PrfObj";
   947 fun g_pbl    (PblObj {probl = p,...}) = p
   948   | g_pbl  _   = raise PTREE "g_pbl not for PrfObj";
   949 fun g_met    (PblObj {meth = p,...}) = p
   950   | g_met  _   = raise PTREE "g_met not for PrfObj";
   951 fun g_domID  (PblObj {spec = (d,_,_),...}) = d
   952   | g_domID  _ = raise PTREE "g_metID not for PrfObj";
   953 fun g_metID  (PblObj {spec = (_,_,m),...}) = m
   954   | g_metID  _ = raise PTREE "g_metID not for PrfObj";
   955 fun g_env    (PblObj {env,...}) = env
   956   | g_env    _ = raise PTREE "g_env not for PrfObj"; 
   957 fun g_loc    (PblObj {loc = l,...}) = l
   958   | g_loc    (PrfObj {loc = l,...}) = l;
   959 fun g_branch (PblObj {branch = b,...}) = b
   960   | g_branch (PrfObj {branch = b,...}) = b;
   961 fun g_tac  (PblObj {spec = (d,p,m),...}) = Apply_Method m
   962   | g_tac  (PrfObj {tac = m,...}) = m;
   963 fun g_result (PblObj {result = r,...}) = r
   964   | g_result (PrfObj {result = r,...}) = r;
   965 fun g_res (PblObj {result = (r,_),...}) = r
   966   | g_res (PrfObj {result = (r,_),...}) = r;
   967 fun g_res' (Nd (PblObj {result = (r,_),...}, _)) = r
   968   | g_res' (Nd (PrfObj {result = (r,_),...}, _)) = r;
   969 fun g_ostate (PblObj {ostate = r,...}) = r
   970   | g_ostate (PrfObj {ostate = r,...}) = r;
   971 fun g_ostate' (Nd (PblObj {ostate = r,...}, _)) = r
   972   | g_ostate' (Nd (PrfObj {ostate = r,...}, _)) = r;
   973 
   974 fun gpt_cell (Nd (PblObj {cell = c,...},_)) = None
   975   | gpt_cell (Nd (PrfObj {cell = c,...},_)) = c;
   976 
   977 (*in CalcTree/Subproblem an 'just_created_' model is created;
   978   this is filled to 'untouched' by Model/Refine_Problem*)
   979 fun just_created_ (PblObj {meth, probl, spec, ...}) = 
   980     null meth andalso null probl andalso spec = e_spec;
   981 val e_origin = ([],e_spec,e_term): (ori list) * spec * term;
   982 
   983 fun just_created (pt,(p,_):pos') =
   984     let val ppobj = get_obj I pt p
   985     in is_pblobj ppobj andalso just_created_ ppobj end;
   986 
   987 (*.does the pos in the ctree exist ?.*)
   988 fun existpt pos pt = can (get_obj I pt) pos;
   989 (*.does the pos' in the ctree exist, ie. extra check for result in the node.*)
   990 fun existpt' ((p,p_):pos') pt = 
   991     if can (get_obj I pt) p 
   992     then case p_ of 
   993 	     Res => get_obj g_ostate pt p = Complete
   994 	   | _ => true
   995     else false;
   996 
   997 (*.is this position appropriate for calculating intermediate steps?.*)
   998 fun is_interpos ((_, Res):pos') = true
   999   | is_interpos _ = false;
  1000 
  1001 fun last_onlev pt pos = not (existpt (lev_on pos) pt);
  1002 
  1003 
  1004 (*.find the position of the next parent which is a PblObj in ptree.*)
  1005 fun par_pblobj pt ([]:pos) = ([]:pos)
  1006   | par_pblobj pt p =
  1007     let fun par pt [] = []
  1008 	  | par pt p = if is_pblobj (get_obj I pt p) then p
  1009 		       else par pt (lev_up p)
  1010     in par pt (lev_up p) end; 
  1011 (* lev_up for hard_gen operating with pos = [...,0] *)
  1012 
  1013 (*.find the position and the children of the next parent which is a PblObj.*)
  1014 fun par_children (Nd (PblObj _, children)) ([]:pos) = (children, []:pos)
  1015   | par_children (pt as Nd (PblObj _, children)) p =
  1016     let fun par [] = (children, [])
  1017 	  | par p = let val Nd (obj, children) = get_nd pt p
  1018 		    in if is_pblobj obj then (children, p) else par (lev_up p)
  1019 		    end;
  1020     in par (lev_up p) end; 
  1021 
  1022 (*.get the children of a node in ptree.*)
  1023 fun children (Nd (PblObj _, cn)) = cn
  1024   | children (Nd (PrfObj _, cn)) = cn;
  1025 
  1026 
  1027 (*.find the next parent, which is either a PblObj (return true)
  1028   or a PrfObj with tac = Detail_Set (return false).*)
  1029 (*FIXME.3.4.03:re-organize par_pbl_det after rls' --> rls*)
  1030 fun par_pbl_det pt ([]:pos) = (true, []:pos, Erls)
  1031   | par_pbl_det pt p =
  1032     let fun par pt [] = (true, [], Erls)
  1033 	  | par pt p = if is_pblobj (get_obj I pt p) then (true, p, Erls)
  1034 		       else case get_obj g_tac pt p of
  1035 				(*Detail_Set rls' => (false, p, assoc_rls rls')
  1036 			      (*^^^--- before 040206 after ---vvv*)
  1037 			      |*)Rewrite_Set rls' => (false, p, assoc_rls rls')
  1038 			      | Rewrite_Set_Inst (_, rls') => 
  1039 				(false, p, assoc_rls rls')
  1040 			      | _ => par pt (lev_up p)
  1041     in par pt (lev_up p) end; 
  1042 
  1043 
  1044 
  1045 
  1046 (*.get from the whole ptree by f : ppobj -> 'a.*)
  1047 fun get_all f EmptyPtree   = []
  1048   | get_all f (Nd (b, [])) = [f b]
  1049   | get_all f (Nd (b, bs)) = [f b] @ (get_alls f bs)
  1050 and get_alls f [] = []
  1051   | get_alls f pts = flat (map (get_all f) pts);
  1052 
  1053 
  1054 (*.insert obj b into ptree at pos, ev.overwriting this pos.*)
  1055 fun insert b EmptyPtree   ([]:pos)  = Nd (b, [])
  1056   | insert b EmptyPtree    _        = raise PTREE "insert b Empty _"
  1057   | insert b (Nd ( _,  _)) []       = raise PTREE "insert b _ []"
  1058   | insert b (Nd (b', bs)) (p::[])  = 
  1059      Nd (b', repl_app bs p (Nd (b,[]))) 
  1060   | insert b (Nd (b', bs)) (p::ps)  =
  1061      Nd (b', repl_app bs p (insert b (nth p bs) ps));
  1062 (*
  1063 > type ppobj = string;
  1064 > writeln (pr_ptree prfn (!pt));
  1065   val pt = ref Empty;
  1066   pt:= insert ("root":ppobj) EmptyPtree [];
  1067   pt:= insert ("xx1":ppobj) (!pt) [1];
  1068   pt:= insert ("xx2":ppobj) (!pt) [2];
  1069   pt:= insert ("xx3":ppobj) (!pt) [3];
  1070   pt:= insert ("xx2.1":ppobj) (!pt) [2,1];
  1071   pt:= insert ("xx2.2":ppobj) (!pt) [2,2];
  1072   pt:= insert ("xx2.1.1":ppobj) (!pt) [2,1,1];
  1073   pt:= insert ("xx2.1.2":ppobj) (!pt) [2,1,2];
  1074   pt:= insert ("xx2.1.3":ppobj) (!pt) [2,1,3];
  1075 *)
  1076 
  1077 (*.insert children to a node without children.*)
  1078 (*compare: fun insert*)
  1079 fun ins_chn _  EmptyPtree   (_:pos) = raise PTREE "ins_chn: EmptyPtree"
  1080   | ins_chn ns (Nd _)       []      = raise PTREE "ins_chn: pos = []"
  1081   | ins_chn ns (Nd (b, bs)) (p::[]) =
  1082     if p > length bs then raise PTREE "ins_chn: pos not existent"
  1083     else let val Nd (b', bs') = nth p bs
  1084 	 in if null bs' then Nd (b, repl_app bs p (Nd (b', ns)))
  1085 	    else raise PTREE "ins_chn: pos mustNOT be overwritten" end
  1086   | ins_chn ns (Nd (b, bs)) (p::ps) =
  1087      Nd (b, repl_app bs p (ins_chn ns (nth p bs) ps));
  1088 
  1089 print_depth 11;ins_chn;print_depth 3 (*###insert#########################*);
  1090 
  1091 
  1092 (** apply f to obj at pos, f: ppobj -> ppobj **)
  1093 
  1094 fun appl_to_node f (Nd (b,bs)) = Nd (f b, bs);
  1095 fun appl_obj f EmptyPtree    []      = EmptyPtree
  1096   | appl_obj f EmptyPtree    _       = raise PTREE "appl_obj f Empty _"
  1097   | appl_obj f (Nd (b, bs)) []       = Nd (f b, bs)
  1098   | appl_obj f (Nd (b, bs)) (p::[])  = 
  1099      Nd (b, repl_app bs p (((appl_to_node f) o (nth p)) bs))
  1100   | appl_obj f (Nd (b, bs)) (p::ps)  =
  1101      Nd (b, repl_app bs p (appl_obj f (nth p bs) (ps:pos)));
  1102  
  1103 (* for use by appl_obj *) 
  1104 fun repl_form f (PrfObj {cell=c,form= _,tac=tac,loc=loc,
  1105 			 branch=branch,result=result,ostate=ostate}) =
  1106     PrfObj {cell=c,form= f,tac=tac,loc=loc,
  1107 	    branch=branch,result=result,ostate=ostate}
  1108   | repl_form _ _ = raise PTREE "repl_form takes no PblObj";
  1109 fun repl_pbl x    (PblObj {cell=cell,origin=origin,fmz=fmz,
  1110 			   spec=spec,probl=_,meth=meth,env=env,loc=loc,
  1111 			   branch=branch,result=result,ostate=ostate}) =
  1112   PblObj {cell=cell,origin=origin,fmz=fmz,spec=spec,probl= x,
  1113 	  meth=meth,env=env,loc=loc,branch=branch,result=result,ostate=ostate}
  1114   | repl_pbl _ _ = raise PTREE "repl_pbl takes no PrfObj";
  1115 fun repl_met x    (PblObj {cell=cell,origin=origin,fmz=fmz,
  1116 			   spec=spec,probl=probl,meth=_,env=env,loc=loc,
  1117 			   branch=branch,result=result,ostate=ostate}) =
  1118   PblObj {cell=cell,origin=origin,fmz=fmz,spec=spec,probl=probl,
  1119 	  meth= x,env=env,loc=loc,branch=branch,result=result,ostate=ostate}
  1120   | repl_met _ _ = raise PTREE "repl_pbl takes no PrfObj";
  1121 
  1122 fun repl_spec  x    (PblObj {cell=cell,origin=origin,fmz=fmz,
  1123 			   spec= _,probl=probl,meth=meth,env=env,loc=loc,
  1124 			   branch=branch,result=result,ostate=ostate}) =
  1125   PblObj {cell=cell,origin=origin,fmz=fmz,spec= x,probl=probl,
  1126 	  meth=meth,env=env,loc=loc,branch=branch,result=result,ostate=ostate}
  1127   | repl_spec  _ _ = raise PTREE "repl_domID takes no PrfObj";
  1128 fun repl_domID x    (PblObj {cell=cell,origin=origin,fmz=fmz,
  1129 			   spec=(_,p,m),probl=probl,meth=meth,env=env,loc=loc,
  1130 			   branch=branch,result=result,ostate=ostate}) =
  1131   PblObj {cell=cell,origin=origin,fmz=fmz,spec=(x,p,m),probl=probl,
  1132 	  meth=meth,env=env,loc=loc,branch=branch,result=result,ostate=ostate}
  1133   | repl_domID _ _ = raise PTREE "repl_domID takes no PrfObj";
  1134 fun repl_pblID x    (PblObj {cell=cell,origin=origin,fmz=fmz,
  1135 			   spec=(d,_,m),probl=probl,meth=meth,env=env,loc=loc,
  1136 			   branch=branch,result=result,ostate=ostate}) =
  1137   PblObj {cell=cell,origin=origin,fmz=fmz,spec=(d,x,m),probl=probl,
  1138 	  meth=meth,env=env,loc=loc,branch=branch,result=result,ostate=ostate}
  1139   | repl_pblID _ _ = raise PTREE "repl_pblID takes no PrfObj";
  1140 fun repl_metID x (PblObj {cell=cell,origin=origin,fmz=fmz,
  1141 			   spec=(d,p,_),probl=probl,meth=meth,env=env,loc=loc,
  1142 			   branch=branch,result=result,ostate=ostate}) =
  1143   PblObj {cell=cell,origin=origin,fmz=fmz,spec=(d,p,x),probl=probl,
  1144 	  meth=meth,env=env,loc=loc,branch=branch,result=result,ostate=ostate}
  1145   | repl_metID _ _ = raise PTREE "repl_metID takes no PrfObj";
  1146 
  1147 fun repl_result l f' s (PrfObj {cell=cell,form=form,tac=tac,loc=_,
  1148 			     branch=branch,result = _ ,ostate = _}) =
  1149     PrfObj {cell=cell,form=form,tac=tac,loc= l,
  1150 	    branch=branch,result = f',ostate = s}
  1151   | repl_result l f' s (PblObj {cell=cell,origin=origin,fmz=fmz,
  1152 			     spec=spec,probl=probl,meth=meth,env=env,loc=_,
  1153 			     branch=branch,result= _ ,ostate= _}) =
  1154     PblObj {cell=cell,origin=origin,fmz=fmz,
  1155 	    spec=spec,probl=probl,meth=meth,env=env,loc= l,
  1156 	    branch=branch,result= f',ostate= s};
  1157 
  1158 fun repl_tac x (PrfObj {cell=cell,form=form,tac= _,loc=loc,
  1159 			  branch=branch,result=result,ostate=ostate}) =
  1160     PrfObj {cell=cell,form=form,tac= x,loc=loc,
  1161 	    branch=branch,result=result,ostate=ostate}
  1162   | repl_tac _ _ = raise PTREE "repl_tac takes no PblObj";
  1163 
  1164 fun repl_branch b (PblObj {cell=cell,origin=origin,fmz=fmz,
  1165 			   spec=spec,probl=probl,meth=meth,env=env,loc=loc,
  1166 			   branch= _,result=result,ostate=ostate}) =
  1167   PblObj {cell=cell,origin=origin,fmz=fmz,spec=spec,probl=probl,
  1168 	  meth=meth,env=env,loc=loc,branch= b,result=result,ostate=ostate}
  1169   | repl_branch b (PrfObj {cell=cell,form=form,tac=tac,loc=loc,
  1170 			  branch= _,result=result,ostate=ostate}) =
  1171     PrfObj {cell=cell,form=form,tac=tac,loc=loc,
  1172 	    branch= b,result=result,ostate=ostate};
  1173 
  1174 fun repl_env e
  1175   (PblObj {cell=cell,origin=origin,fmz=fmz,
  1176 	   spec=spec,probl=probl,meth=meth,env=_,loc=loc,
  1177 	   branch=branch,result=result,ostate=ostate}) =
  1178   PblObj {cell=cell,origin=origin,fmz=fmz,spec=spec,probl=probl,
  1179 	  meth=meth,env=e,loc=loc,branch=branch,
  1180 	  result=result,ostate=ostate}
  1181   | repl_env _ _ = raise PTREE "repl_ets takes no PrfObj";
  1182 
  1183 fun repl_oris oris
  1184   (PblObj {cell=cell,origin=(_,spe,hdf),fmz=fmz,
  1185 	   spec=spec,probl=probl,meth=meth,env=env,loc=loc,
  1186 	   branch=branch,result=result,ostate=ostate}) =
  1187   PblObj{cell=cell,origin=(oris,spe,hdf),fmz=fmz,spec=spec,probl=probl,
  1188 	  meth=meth,env=env,loc=loc,branch=branch,
  1189 	  result=result,ostate=ostate}
  1190   | repl_oris _ _ = raise PTREE "repl_oris takes no PrfObj";
  1191 fun repl_orispec spe
  1192   (PblObj {cell=cell,origin=(oris,_,hdf),fmz=fmz,
  1193 	   spec=spec,probl=probl,meth=meth,env=env,loc=loc,
  1194 	   branch=branch,result=result,ostate=ostate}) =
  1195   PblObj{cell=cell,origin=(oris,spe,hdf),fmz=fmz,spec=spec,probl=probl,
  1196 	  meth=meth,env=env,loc=loc,branch=branch,
  1197 	  result=result,ostate=ostate}
  1198   | repl_orispec _ _ = raise PTREE "repl_orispec takes no PrfObj";
  1199 
  1200 fun repl_loc l (PblObj {cell=cell,origin=origin,fmz=fmz,
  1201 			spec=spec,probl=probl,meth=meth,env=env,loc=_,
  1202 			branch=branch,result=result,ostate=ostate}) =
  1203   PblObj {cell=cell,origin=origin,fmz=fmz,spec=spec,probl=probl,
  1204 	  meth=meth,env=env,loc=l,branch=branch,result=result,ostate=ostate}
  1205   | repl_loc l (PrfObj {cell=cell,form=form,tac=tac,loc=_,
  1206 			branch=branch,result=result,ostate=ostate}) =
  1207   PrfObj {cell=cell,form=form,tac=tac,loc= l,
  1208 	  branch=branch,result=result,ostate=ostate};
  1209 (*
  1210 fun uni__cid cell' 
  1211   (PblObj {cell=cell,origin=origin,fmz=fmz,
  1212 	   spec=spec,probl=probl,meth=meth,env=env,loc=loc,
  1213 	   branch=branch,result=result,ostate=ostate}) =
  1214   PblObj {cell=cell union cell',origin=origin,fmz=fmz,spec=spec,probl=probl,
  1215 	  meth=meth,env=env,loc=loc,branch=branch,
  1216 	  result=result,ostate=ostate}
  1217   | uni__cid cell'
  1218   (PrfObj {cell=cell,form=form,tac=tac,loc=loc,
  1219 	   branch=branch,result=result,ostate=ostate}) =
  1220   PrfObj {cell=cell union cell',form=form,tac=tac,loc=loc,
  1221 	  branch=branch,result=result,ostate=ostate};
  1222 *)
  1223 
  1224 (*WN050219 put here for interpreting code for cut_tree below...*)
  1225 type ocalhd =
  1226      bool *                (*ALL itms+preconds true*)
  1227      pos_ *                (*model belongs to Problem | Method*)
  1228      term *                (*header: Problem... or Cas
  1229 				FIXXXME.12.03: item! for marking syntaxerrors*)
  1230      itm list *            (*model: given, find, relate*)
  1231      ((bool * term) list) *(*model: preconds*)
  1232      spec;                 (*specification*)
  1233 val e_ocalhd = (false, Und, e_term, [e_itm], [(false, e_term)], e_spec);
  1234 
  1235 datatype ptform =
  1236 	 Form of term
  1237        | ModSpec of ocalhd;
  1238 val e_ptform = Form e_term;
  1239 val e_ptform' = ModSpec e_ocalhd;
  1240 
  1241 
  1242 
  1243 (*.applies (snd f) to the branches at a pos if ((fst f) b),
  1244    f : (ppobj -> bool) * (int -> ptree list -> ptree list).*)
  1245 
  1246 fun appl_branch f EmptyPtree [] = (EmptyPtree, false)
  1247   | appl_branch f EmptyPtree _  = raise PTREE "appl_branch f Empty _"
  1248   | appl_branch f (Nd ( _, _)) [] = raise PTREE "appl_branch f _ []"
  1249   | appl_branch f (Nd (b, bs)) (p::[]) = 
  1250     if (fst f) b then (Nd (b, (snd f) (p:posel) bs), true)
  1251     else (Nd (b, bs), false)
  1252   | appl_branch f (Nd (b, bs)) (p::ps) =
  1253 	let val (b',bool) = appl_branch f (nth p bs) ps
  1254 	in (Nd (b, repl_app bs p b'), bool) end;
  1255 
  1256 (* for cut_level;  appl_branch(deprecated) *)
  1257 fun test_trans (PrfObj{branch = Transitive,...}) = true
  1258   | test_trans (PblObj{branch = Transitive,...}) = true
  1259   | test_trans _ = false;
  1260 
  1261 fun is_pblobj' pt (p:pos) =
  1262     let val ppobj = get_obj I pt p
  1263     in is_pblobj ppobj end;
  1264 
  1265 
  1266 fun delete_result pt (p:pos) =
  1267     (appl_obj (repl_result (fst (get_obj g_loc pt p), None) 
  1268 			   (e_term,[]) Incomplete) pt p);
  1269 
  1270 fun del_res (PblObj {cell, fmz, origin, spec, probl, meth, 
  1271 		     env, loc=(l1,_), branch, result, ostate}) =
  1272     PblObj {cell=cell,fmz=fmz,origin=origin,spec=spec,probl=probl,meth=meth,
  1273 	    env=env, loc=(l1,None), branch=branch, result=(e_term,[]), 
  1274 	    ostate=Incomplete}
  1275 
  1276   | del_res (PrfObj {cell, form, tac, loc=(l1,_), branch, result, ostate}) =
  1277     PrfObj {cell=cell,form=form,tac=tac, loc=(l1,None), branch=branch, 
  1278 	    result=(e_term,[]), ostate=Incomplete};
  1279 
  1280 
  1281 (*
  1282 fun update_fmz  pt pos x = appl_obj (repl_fmz  x) pt pos;
  1283                                        1.00 not used anymore*)
  1284 
  1285 (*FIXME.WN.12.03: update_X X pos pt -> pt could be chained by o (efficiency?)*)
  1286 fun update_env    pt pos x = appl_obj (repl_env    x) pt pos;
  1287 fun update_domID  pt pos x = appl_obj (repl_domID  x) pt pos;
  1288 fun update_pblID  pt pos x = appl_obj (repl_pblID  x) pt pos;
  1289 fun update_metID  pt pos x = appl_obj (repl_metID  x) pt pos;
  1290 fun update_spec   pt pos x = appl_obj (repl_spec   x) pt pos;
  1291 
  1292 fun update_pbl    pt pos x = appl_obj (repl_pbl    x) pt pos;
  1293 fun update_pblppc pt pos x = appl_obj (repl_pbl    x) pt pos;
  1294 
  1295 fun update_met    pt pos x = appl_obj (repl_met    x) pt pos;
  1296 (*1.09.01 ----
  1297 fun update_metppc pt pos x = 
  1298   let val {rew_ord'=od,rls'=rs,asm_thm=at,asm_rls=ar,...} =
  1299     get_obj g_met pt pos
  1300   in appl_obj (repl_met 
  1301      {rew_ord'=od,rls'=rs,asm_thm=at,asm_rls=ar,ppc=x}) 
  1302     pt pos end;*)
  1303 fun update_metppc pt pos x = appl_obj (repl_met    x) pt pos;
  1304 			 			   
  1305 (*fun union_cid     pt pos x = appl_obj (uni__cid    x) pt pos;*)
  1306 
  1307 fun update_branch pt pos x = appl_obj (repl_branch x) pt pos;
  1308 fun update_tac  pt pos x = appl_obj (repl_tac  x) pt pos;
  1309 
  1310 fun update_oris   pt pos x = appl_obj (repl_oris   x) pt pos;
  1311 fun update_orispec   pt pos x = appl_obj (repl_orispec   x) pt pos;
  1312 
  1313  (*done by append_* !! 3.5.02;  ununsed WN050305 thus outcommented
  1314 fun update_loc pt (p,_) (ScrState ([],[],None,
  1315 				   Const ("empty",_),Sundef,false)) = 
  1316     appl_obj (repl_loc (None,None)) pt p
  1317   | update_loc pt (p,Res) x =  
  1318     let val (lform,_) = get_obj g_loc pt p
  1319     in appl_obj (repl_loc (lform,Some x)) pt p end
  1320 
  1321   | update_loc pt (p,_) x = 
  1322     let val (_,lres) = get_obj g_loc pt p
  1323     in appl_obj (repl_loc (Some x,lres)) pt p end;-------------*)
  1324 
  1325 (*WN050305 for handling cut_tree in cappend_atomic -- TODO redesign !*)
  1326 fun update_loc' pt p iss = appl_obj (repl_loc iss) pt p;
  1327 
  1328 (*13.8.02---------------------------
  1329 fun get_loc EmptyPtree _ = None
  1330   | get_loc pt (p,Res) =
  1331   let val (lfrm,lres) = get_obj g_loc pt p
  1332   in if lres = e_istate then lfrm else lres end
  1333   | get_loc pt (p,_) =
  1334   let val (lfrm,lres) = get_obj g_loc pt p
  1335   in if lfrm = e_istate then lres else lfrm end;  5.10.00: too liberal ?*)
  1336 (*13.8.02: options, because istate is no equalitype any more*)
  1337 fun get_loc EmptyPtree _ = e_istate
  1338   | get_loc pt (p,Res) =
  1339     (case get_obj g_loc pt p of
  1340 	 (Some i, None) => i
  1341        | (None  , None) => e_istate
  1342        | (_     , Some i) => i)
  1343   | get_loc pt (p,_) =
  1344     (case get_obj g_loc pt p of
  1345 	 (None  , Some i) => i (*13.8.02 just copied from ^^^: too liberal ?*)
  1346        | (None  , None) => e_istate
  1347        | (Some i, _) => i);
  1348 val get_istate = get_loc; (*3.5.02*)
  1349 
  1350 (*.collect the assumptions within a problem up to a certain position.*)
  1351 type asms = (term * pos) list;(*WN0502 should be (pos' * term) list
  1352 				       ...........===^===*)
  1353 
  1354 fun get_asm (b:pos, p:pos) (Nd (PblObj {result=(_,asm),...},_)) = 
  1355     ((*writeln ("### get_asm PblObj:(b,p)= "^
  1356 		(pair2str(ints2str b, ints2str p)));*)
  1357      (map (rpair b) asm):asms)
  1358   | get_asm (b, p) (Nd (PrfObj {result=(_,asm),...}, [])) = 
  1359     ((*writeln ("### get_asm PrfObj []:(b,p)= "^
  1360 	      (pair2str(ints2str b, ints2str p)));*)
  1361      (map (rpair b) asm))
  1362   | get_asm (b, p:pos) (Nd (PrfObj _, nds)) = 
  1363     let (*val _= writeln ("### get_asm PrfObj nds:(b,p)= "^
  1364 	      (pair2str(ints2str b, ints2str p)));*)
  1365 	val levdn = 
  1366 	    if p <> [] then (b @ [hd p]:pos, tl p:pos) 
  1367 	    else (b @ [1], [99999]) (*_deeper_ nesting is always _before_ p*)
  1368     in gets_asm levdn 1 nds end
  1369 and gets_asm _ _ [] = []
  1370   | gets_asm (b, p' as p::ps) i (nd::nds) = 
  1371     if p < i then [] 
  1372     else ((*writeln ("### gets_asm: (b,p')= "^(pair2str(ints2str b,
  1373 						      ints2str p')));*)
  1374 	  (get_asm (b @ [i], ps) nd) @ (gets_asm (b, p') (i + 1) nds));
  1375 
  1376 fun get_assumptions_ (Nd (PblObj {result=(r,asm),...}, cn)) (([], _):pos') = 
  1377     if r = e_term then gets_asm ([], [99999]) 1 cn
  1378     else map (rpair []) asm
  1379   | get_assumptions_ pt (p,p_) =
  1380     let val (cn, base) = par_children pt p
  1381 	val offset = drop (length base, p)
  1382 	val base' = replicate (length base) 1
  1383 	val offset' = case p_ of 
  1384 			 Frm => let val (qs,q) = split_last offset
  1385 				in qs @ [q - 1] end
  1386 		       | _ => offset
  1387         (*val _= writeln ("... get_assumptions: (b,o)= "^
  1388 			(pair2str(ints2str base',ints2str offset)))*)
  1389     in gets_asm (base', offset) 1 cn end;
  1390 
  1391 
  1392 (*---------
  1393 end
  1394 
  1395 open Ptree;
  1396 ----------*)
  1397 
  1398 (*pos of the formula on FE relative to the current pos,
  1399   which is the next writepos*)
  1400 fun pre_pos ([]:pos) = []:pos
  1401   | pre_pos pp =
  1402   let val (ps,p) = split_last pp
  1403   in case p of 1 => ps | n => ps @ [n-1] end;
  1404 
  1405 (*WN.20.5.03 ... but not used*)
  1406 fun posless [] (_::_) = true
  1407   | posless (_::_) [] = false
  1408   | posless (p::ps) (q::qs) = if p = q then posless ps qs else p < q;
  1409 (* posless [2,3,4] [3,4,5];
  1410 true
  1411 >  posless [2,3,4] [1,2,3];
  1412 false
  1413 >  posless [2,3] [2,3,4];
  1414 true
  1415 >  posless [2,3,4] [2,3];
  1416 false                    
  1417 >  posless [6] [6,5,2];
  1418 true
  1419 +++ see Isabelle/../library.ML*)
  1420 
  1421 
  1422 (**.development for extracting an 'interval' from ptree.**)
  1423 
  1424 (*version 1 stopped 8.03 in favour of get_interval with !!!move_dn
  1425   actually used (inefficient) version with move_dn: see modspec.sml*)
  1426 local
  1427 
  1428 fun hdp [] = 1     | hdp [0] = 1     | hdp x = hd x;(*start with first*)
  1429 fun hdq	[] = 99999 | hdq [0] = 99999 | hdq x = hd x;(*take until last*)
  1430 fun tlp [] = [0]     | tlp [_] = [0]     | tlp x = tl x;
  1431 fun tlq [] = [99999] | tlq [_] = [99999] | tlq x = tl x;
  1432 
  1433 fun getnd i (b,p) q (Nd (po, nds)) =
  1434     (if  i <= 0 then [[b]] else []) @
  1435     (getnds (i-1) true (b@[hdp p], tlp p) (tlq q)
  1436 	   (take_fromto (hdp p) (hdq q) nds))
  1437 
  1438 and getnds _ _ _ _ [] = []                         (*no children*)
  1439   | getnds i _ (b,p) q [nd] = (getnd i (b,p) q nd) (*l+r-margin*)
  1440 
  1441   | getnds i true (b,p) q [n1, n2] =               (*l-margin,  r-margin*)
  1442     (getnd i      (       b, p ) [99999] n1) @
  1443     (getnd ~99999 (lev_on b,[0]) q       n2)
  1444 
  1445   | getnds i _    (b,p) q [n1, n2] =               (*intern,  r-margin*)
  1446     (getnd i      (       b,[0]) [99999] n1) @
  1447     (getnd ~99999 (lev_on b,[0]) q       n2)
  1448 
  1449   | getnds i true (b,p) q (nd::(nds as _::_)) =    (*l-margin, intern*)
  1450     (getnd i             (       b, p ) [99999] nd) @
  1451     (getnds ~99999 false (lev_on b,[0]) q nds)
  1452 
  1453   | getnds i _ (b,p) q (nd::(nds as _::_)) =       (*intern, ...*)
  1454     (getnd i             (       b,[0]) [99999] nd) @
  1455     (getnds ~99999 false (lev_on b,[0]) q nds); 
  1456 in
  1457 (*get an 'interval from to' from a ptree as 'intervals f t' of respective nodes
  1458   where 'from' are pos, i.e. a key as int list, 'f' an int (to,t analoguous)
  1459 (1) the 'f' are given 
  1460 (1a) by 'from' if 'f' = the respective element of 'from' (left margin)
  1461 (1b) -inifinity, if 'f' > the respective element of 'from' (internal node)
  1462 (2) the 't' ar given
  1463 (2a) by 'to' if 't' = the respective element of 'to' (right margin)
  1464 (2b) inifinity, if 't' < the respective element of 'to (internal node)'
  1465 the 'f' and 't' are set by hdp,... *)
  1466 fun get_trace pt p q =
  1467     (flat o (getnds ((length p) -1) true ([hdp p], tlp p) (tlq q))) 
  1468 	(take_fromto (hdp p) (hdq q) (children pt));
  1469 end;
  1470 (*WN0510 stoppde this development;
  1471  actually used (inefficient) version with move_dn: getFormulaeFromTo*)
  1472 
  1473 
  1474 
  1475 
  1476 fun get_somespec ((dI,pI,mI):spec) ((dI',pI',mI'):spec) =
  1477     let val domID = if dI = e_domID
  1478 		    then if dI' = e_domID 
  1479 			 then raise error"pt_extract: no domID in probl,origin"
  1480 			 else dI'
  1481 		    else dI
  1482 	val pblID = if pI = e_pblID
  1483 		    then if pI' = e_pblID 
  1484 			 then raise error"pt_extract: no pblID in probl,origin"
  1485 			 else pI'
  1486 		    else pI
  1487 	val metID = if mI = e_metID
  1488 		    then if pI' = e_metID 
  1489 			 then raise error"pt_extract: no metID in probl,origin"
  1490 			 else mI'
  1491 		    else mI
  1492     in (domID, pblID, metID):spec end;
  1493 fun get_somespec' ((dI,pI,mI):spec) ((dI',pI',mI'):spec) =
  1494     let val domID = if dI = e_domID then dI' else dI
  1495 	val pblID = if pI = e_pblID then pI' else pI
  1496 	val metID = if mI = e_metID then mI' else mI
  1497     in (domID, pblID, metID):spec end;
  1498 
  1499 (*extract a formula or model from ptree for itms2itemppc or model2xml*)
  1500 fun preconds2str bts = 
  1501     (strs2str o (map (linefeed o pair2str o
  1502 		      (apsnd term2str) o 
  1503 		      (apfst bool2str)))) bts;
  1504 fun ocalhd2str ((b, p, hdf, itms, prec, spec):ocalhd) =
  1505     "("^bool2str b^", "^pos_2str p^", "^term2str hdf^
  1506     ", "^itms2str (assoc_thy "Isac.thy") itms^
  1507     ", "^preconds2str prec^", \n"^spec2str spec^" )";
  1508 
  1509 
  1510 
  1511 fun is_pblnd (Nd (ppobj, _)) = is_pblobj ppobj;
  1512 
  1513 
  1514 (**.functions for the 'ptree iterator' as seen from the FE-Kernel interface.**)
  1515 
  1516 (*move one step down into existing nodes of ptree; regard TransitiveB
  1517 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~##################
  1518 fun move_dn _ (Nd (c, ns)) ([],p_) = (*root problem*)
  1519 (* val (Nd (c, ns), ([],p_)) = (pt, get_pos cI uI);
  1520    *)
  1521     if is_pblobj c 
  1522     then case p_ of (*Frm => ([], Pbl) 1.12.03
  1523 		  |*) Res => raise PTREE "move_dn: end of calculation"
  1524 		  | _ => if null ns (*go down from Pbl + Met*)
  1525 			 then raise PTREE "move_dn: solve problem not started"
  1526 			 else ([1], Frm)
  1527     else (case p_ of Res => raise PTREE "move_dn: end of (sub-)tree"
  1528 		  | _ => if null ns
  1529 			 then raise PTREE "move_dn: pos not existent 1"
  1530 			 else ([1], Frm))
  1531 
  1532   (*iterate towards end of pos*)
  1533 (* val (P,(Nd (_, ns)),(p::(ps as (_::_)),p_)) = ([]:pos, pt, get_pos cI uI);
  1534    val (P,(Nd (_, ns)),(p::(ps as (_::_)),p_)) = ((P@[p]),(nth p ns),(ps, p_));
  1535    *) 
  1536  | move_dn P  (Nd (_, ns)) (p::(ps as (_::_)),p_) =
  1537     if p > length ns then raise PTREE "move_dn: pos not existent 2"
  1538     else move_dn ((P@[p]): pos) (nth p ns) (ps, p_)
  1539 (* val (P, (Nd (c, ns)), ([p], p_)) = ((P@[p]), (nth p ns), (ps, p_));
  1540    val (P, (Nd (c, ns)), ([p], p_)) = ([],pt,get_pos cI uI);
  1541    *)
  1542   | move_dn P (Nd (c, ns)) ([p], p_) = (*act on last element of pos*)
  1543     if p > length ns then raise PTREE "move_dn: pos not existent 3"
  1544     else if is_pblnd (nth p ns)  then
  1545 	((*writeln("### move_dn: is_pblnd (nth p ns), P= "^ints2str' P^", \n"^
  1546 		 "length ns= "^((string_of_int o length) ns)^
  1547 		 ", p= "^string_of_int p^", p_= "^pos_2str p_);*)
  1548 	 case p_ of Res => if p = length ns 
  1549 			   then if g_ostate c = Complete then (P, Res)
  1550 				else raise PTREE (ints2str' P^" not complete")
  1551 			   (*FIXME here handle not-sequent-branches*)
  1552 			   else if g_branch c = TransitiveB 
  1553 				   andalso (not o is_pblnd o (nth (p+1))) ns
  1554 			   then (P@[p+1], Res)
  1555 			   else (P@[p+1], if is_pblnd (nth (p+1) ns) 
  1556 					  then Pbl else Frm)
  1557 		  | _ => if (null o children o (nth p)) ns (*go down from Pbl*)
  1558 			 then raise PTREE "move_dn: solve subproblem not started"
  1559 			 else (P @ [p, 1], 
  1560 			       if (is_pblnd o hd o children o (nth p)) ns
  1561 			       then Pbl else Frm)
  1562 			      )
  1563     (* val (P, Nd (c, ns), ([p], p_)) = ([], pt, ([1], Frm));
  1564         *)
  1565     else case p_ of Frm => if (null o children o (nth p)) ns 
  1566 			 (*then if g_ostate c = Complete then (P@[p],Res)*)
  1567 			   then if g_ostate' (nth p ns) = Complete 
  1568 				then (P@[p],Res)
  1569 				else raise PTREE "move_dn: pos not existent 4"
  1570 			   else (P @ [p, 1], (*go down*) 
  1571 				 if (is_pblnd o hd o children o (nth p)) ns
  1572 				 then Pbl else Frm)
  1573 		  | Res => if p = length ns 
  1574 			   then 
  1575 			      if g_ostate c = Complete then (P, Res)
  1576 			      else raise PTREE (ints2str' P^" not complete")
  1577 			   else 
  1578 			       if g_branch c = TransitiveB 
  1579 				  andalso (not o is_pblnd o (nth (p+1))) ns
  1580 			       then if (null o children o (nth (p+1))) ns
  1581 				    then (P@[p+1], Res)
  1582 				    else (P@[p+1,1], Frm)(*040221*)
  1583 			       else (P@[p+1], if is_pblnd (nth (p+1) ns) 
  1584 					      then Pbl else Frm); 
  1585 *)
  1586 (*.move one step down into existing nodes of ptree; skip Res = Frm.nxt;
  1587    move_dn at the end of the calc-tree raises PTREE.*)
  1588 fun move_dn _ (Nd (c, ns)) ([],p_) = (*root problem*)
  1589     (case p_ of 
  1590 	     Res => raise PTREE "move_dn: end of calculation"
  1591 	   | _ => if null ns (*go down from Pbl + Met*)
  1592 		  then raise PTREE "move_dn: solve problem not started"
  1593 		  else ([1], Frm))
  1594   | move_dn P  (Nd (_, ns)) (p::(ps as (_::_)),p_) =(*iterate to end of pos*)
  1595     if p > length ns then raise PTREE "move_dn: pos not existent 2"
  1596     else move_dn ((P@[p]): pos) (nth p ns) (ps, p_)
  1597 
  1598   | move_dn P (Nd (c, ns)) ([p], p_) = (*act on last element of pos*)
  1599     if p > length ns then raise PTREE "move_dn: pos not existent 3"
  1600     else case p_ of 
  1601 	     Res => 
  1602 	     if p = length ns (*last Res on this level: go a level up*)
  1603 	     then if g_ostate c = Complete then (P, Res)
  1604 		  else raise PTREE (ints2str' P^" not complete 1")
  1605 	     else (*go to the next Nd on this level, or down into the next Nd*)
  1606 		 if is_pblnd (nth (p+1) ns) then (P@[p+1], Pbl)
  1607 		 else 
  1608 		     if g_res' (nth p ns) = g_form' (nth (p+1) ns)
  1609 		     then if (null o children o (nth (p+1))) ns
  1610 			  then (*take the Res if Complete*) 
  1611 			      if g_ostate' (nth (p+1) ns) = Complete 
  1612 			      then (P@[p+1], Res)
  1613 			      else raise PTREE (ints2str' (P@[p+1])^
  1614 						" not complete 2")
  1615 			  else (P@[p+1,1], Frm)(*go down into the next PrfObj*)
  1616 		     else (P@[p+1], Frm)(*take Frm: exists if the Nd exists*)
  1617 	   | Frm => (*go down or to the Res of this Nd*)
  1618 	     if (null o children o (nth p)) ns
  1619 	     then if g_ostate' (nth p ns) = Complete then (P @ [p], Res)
  1620 		  else raise PTREE (ints2str' (P @ [p])^" not complete 3")
  1621 	     else (P @ [p, 1], Frm)
  1622 	   | _ => (*is Pbl or Met*)
  1623 	     if (null o children o (nth p)) ns
  1624 	     then raise PTREE "move_dn:solve subproblem not startd"
  1625 	     else (P @ [p, 1], 
  1626 		   if (is_pblnd o hd o children o (nth p)) ns
  1627 		   then Pbl else Frm);
  1628 
  1629 
  1630 (*.go one level down into ptree.*)
  1631 fun movelevel_dn [] (Nd (c, ns)) ([],p_) = (*root problem*)
  1632     if is_pblobj c 
  1633     then if null ns 
  1634 	 then raise PTREE "solve problem not started"
  1635 	 else ([1], if (is_pblnd o hd) ns then Pbl else Frm)
  1636     else raise PTREE "pos not existent 1"
  1637 
  1638   (*iterate towards end of pos*)
  1639   | movelevel_dn P (Nd (_, ns)) (p::(ps as (_::_)),p_) =
  1640     if p > length ns then raise PTREE "pos not existent 2"
  1641     else movelevel_dn (P@[p]) (nth p ns) (ps, p_)
  1642 
  1643   | movelevel_dn P (Nd (c, ns)) ([p], p_) = (*act on last element of pos*)
  1644     if p > length ns then raise PTREE "pos not existent 3" else
  1645     case p_ of Res => 
  1646 	       if p = length ns 
  1647 	       then raise PTREE "no children"
  1648 	       else 
  1649 		   if g_branch c = TransitiveB
  1650 		   then if (null o children o (nth (p+1))) ns
  1651 			then raise PTREE "no children"
  1652 			else (P @ [p+1, 1], 
  1653 			      if (is_pblnd o hd o children o (nth (p+1))) ns
  1654 			      then Pbl else Frm)
  1655 		   else if (null o children o (nth p)) ns
  1656 		   then raise PTREE "no children"
  1657 		   else (P @ [p, 1], if (is_pblnd o hd o children o (nth p)) ns
  1658 				     then Pbl else Frm)
  1659 	     | _ => if (null o children o (nth p)) ns 
  1660 		    then raise PTREE "no children"
  1661 		    else (P @ [p, 1], (*go down*)
  1662 			  if (is_pblnd o hd o children o (nth p)) ns
  1663 			  then Pbl else Frm);
  1664 
  1665 
  1666 
  1667 (*.go to the previous position in ptree; regard TransitiveB.*)
  1668 fun move_up _ (Nd (c, ns)) (([],p_):pos') = (*root problem*)
  1669     if is_pblobj c 
  1670     then case p_ of Res => if null ns then ([], Pbl) (*Res -> Pbl (not Met)!*)
  1671 			   else ([length ns], Res)
  1672 		  | _  => raise PTREE "begin of calculation"
  1673     else raise PTREE "pos not existent"
  1674 
  1675   | move_up P  (Nd (_, ns)) (p::(ps as (_::_)),p_) = (*iterate to end of pos*)
  1676     if p > length ns then raise PTREE "pos not existent"
  1677     else move_up (P@[p]) (nth p ns) (ps,p_)
  1678 
  1679   | move_up P (Nd (c, ns)) ([p], p_) = (*act on last element of pos*)
  1680     if p > length ns then raise PTREE "pos not existent"
  1681     else if is_pblnd (nth p ns)  then
  1682 	case p_ of Res => 
  1683 		   let val nc = (length o children o (nth p)) ns
  1684 		   in if nc = 0 then (P@[p], Pbl) (*Res -> Pbl (not Met)!*)
  1685 		      else (P @ [p, nc], Res) end (*go down*)
  1686 		 | _ => if p = 1 then (P, Pbl) else (P@[p-1], Res) 
  1687     else case p_ of Frm => if p <> 1 then (P, Frm) 
  1688 			  else if is_pblobj c then (P, Pbl) else (P, Frm)
  1689 		  | Res => 
  1690 		    let val nc = (length o children o (nth p)) ns
  1691 		    in if nc = 0 (*cannot go down*)
  1692 		       then if g_branch c = TransitiveB andalso p <> 1
  1693 			    then (P@[p-1], Res) else (P@[p], Frm)
  1694 		       else (P @ [p, nc], Res) end; (*go down*)
  1695 
  1696 
  1697 
  1698 (*.go one level up in ptree; sets the position on Frm.*)
  1699 fun movelevel_up _ (Nd (c, ns)) (([],p_):pos') = (*root problem*)
  1700     raise PTREE "pos not existent"
  1701 
  1702   (*iterate towards end of pos*)
  1703   | movelevel_up P  (Nd (_, ns)) (p::(ps as (_::_)),p_) = 
  1704     if p > length ns then raise PTREE "pos not existent"
  1705     else movelevel_up (P@[p]) (nth p ns) (ps,p_)
  1706 
  1707   | movelevel_up P (Nd (c, ns)) ([p], p_) = (*act on last element of pos*)
  1708     if p > length ns then raise PTREE "pos not existent"
  1709     else if is_pblobj c then (P, Pbl) else (P, Frm);
  1710 
  1711 
  1712 (*.go to the next calc-head up in the calc-tree.*)
  1713 fun movecalchd_up pt ((p, Res):pos') =
  1714     (par_pblobj pt p, Pbl):pos'
  1715   | movecalchd_up pt (p, _) =
  1716     if is_pblobj (get_obj I pt p) 
  1717     then (p, Pbl) else (par_pblobj pt p, Pbl);
  1718 
  1719 (*.determine the previous pos' on the same level.*)
  1720 (*WN0502 made for interSteps; _only_ works for branch TransitiveB*)
  1721 fun lev_pred' pt (pos:pos' as ([],Res)) = ([],Pbl):pos'
  1722   | lev_pred' pt (pos:pos' as (p, Res)) =
  1723     let val (p', last) = split_last p
  1724     in if last = 1 
  1725        then if (is_pblobj o (get_obj I pt)) p then (p,Pbl) else (p, Frm)
  1726        else if get_obj g_res pt (p' @ [last - 1]) = get_obj g_form pt p
  1727        then (p' @ [last - 1], Res) (*TransitiveB*)
  1728        else if (is_pblobj o (get_obj I pt)) p then (p,Pbl) else (p, Frm)
  1729     end;
  1730 
  1731 (*.determine the next pos' on the same level.*)
  1732 fun lev_on' pt (([],Pbl):pos') = ([],Res):pos'
  1733   | lev_on' pt (p, Res) =
  1734     if get_obj g_res pt p = get_obj g_form pt (lev_on p)(*TransitiveB*)
  1735     then if existpt' (lev_on p, Res) pt then (lev_on p, Res)
  1736 	 else raise error ("lev_on': (p, Res) -> (p, Res) not existent, \
  1737 		      \p = "^ints2str' (lev_on p))
  1738     else (lev_on p, Frm)
  1739   | lev_on' pt (p, _) =
  1740     if existpt' (p, Res) pt then (p, Res)
  1741     else raise error ("lev_on': (p, Frm) -> (p, Res) not existent, \
  1742 		      \p = "^ints2str' p);
  1743 
  1744 fun exist_lev_on' pt p = (lev_on' pt p; true) handle _ => false;
  1745 
  1746 (*.is the pos' at the last element of a calulation _AND_ can be continued.*)
  1747 (* val (pt, pos as (p,p_)) = (pt, ([1],Frm));
  1748    *)
  1749 fun is_curr_endof_calc pt (([],Res) : pos') = false
  1750   | is_curr_endof_calc pt (pos as (p,_)) =
  1751     not (exist_lev_on' pt pos) 
  1752     andalso get_obj g_ostate pt (lev_up p) = Incomplete;
  1753 
  1754 
  1755 (**.insert into ctree and cut branches accordingly.**)
  1756   
  1757 (*.get all positions of certain intervals on the ctree.*)
  1758 (*OLD VERSION without move_dn; kept for occasional redesign
  1759    get all pos's to be cut in a ptree
  1760    below a pos or from a ptree list after i-th element (NO level_up).*)
  1761 fun get_allpos' (_:pos, _:posel) EmptyPtree   = ([]:pos' list)
  1762   | get_allpos' (p, 1) (Nd (b, bs)) = (*p is pos of Nd*)
  1763     if g_ostate b = Incomplete 
  1764     then ((*writeln("get_allpos' (p, 1) Incomplete: p="^ints2str' p);*)
  1765 	  [(p,Frm)] @ (get_allpos's (p, 1) bs)
  1766 	  )
  1767     else ((*writeln("get_allpos' (p, 1) else: p="^ints2str' p);*)
  1768 	  [(p,Frm)] @ (get_allpos's (p, 1) bs) @ [(p,Res)]
  1769 	  )
  1770     (*WN041020 here we assume what is presented on the worksheet ?!*)
  1771   | get_allpos' (p, i) (Nd (b, bs)) = (*p is pos of Nd*)
  1772     if length bs > 0 orelse is_pblobj b
  1773     then if g_ostate b = Incomplete 
  1774 	 then [(p,Frm)] @ (get_allpos's (p, 1) bs)
  1775 	 else [(p,Frm)] @ (get_allpos's (p, 1) bs) @ [(p,Res)]
  1776     else 
  1777 	if g_ostate b = Incomplete 
  1778 	then []
  1779 	else [(p,Res)]
  1780 (*WN041020 here we assume what is presented on the worksheet ?!*)
  1781 and get_allpos's _ [] = []
  1782   | get_allpos's (p, i) (pt::pts) = (*p is pos of parent-Nd*)
  1783     (get_allpos' (p@[i], i) pt) @ (get_allpos's (p, i+1) pts);
  1784 
  1785 (*.get all positions of certain intervals on the ctree.*)
  1786 (*NEW version WN050225*)
  1787 
  1788 
  1789 (*.cut branches.*)
  1790 (*before WN041019......
  1791 val cut_branch = (test_trans, curry take):
  1792     (ppobj -> bool) * (int -> ptree list -> ptree list);
  1793 .. formlery used for ...
  1794 fun cut_tree''' _ [] = EmptyPtree
  1795   | cut_tree''' pt pos = 
  1796   let val (pt',cut) = appl_branch cut_branch pt pos
  1797   in if cut andalso length pos > 1 then cut_tree''' pt' (lev_up pos)
  1798      else pt' end;
  1799 *)
  1800 (*OLD version before WN050225*)
  1801 (*WN050106 like cut_level, but deletes exactly 1 node --- for tests ONLY*)
  1802 fun cut_level_'_ (_:pos' list) (_:pos) EmptyPtree (_:pos') =
  1803     raise PTREE "cut_level_'_ Empty _"
  1804   | cut_level_'_ _ _ (Nd ( _, _)) ([],_) = raise PTREE "cut_level_'_ _ []"
  1805   | cut_level_'_ cuts P (Nd (b, bs)) (p::[],p_) = 
  1806     if test_trans b 
  1807     then (Nd (b, drop_nth [] (p:posel, bs)),
  1808 	  (*     ~~~~~~~~~~~*)
  1809 	  cuts @ 
  1810 	  (if p_ = Frm then [(P@[p],Res)] else ([]:pos' list)) @
  1811 	  (*WN041020 here we assume what is presented on the worksheet ?!*)
  1812 	  (get_allpos's (P, p+1) (drop_nth [] (p, bs))))
  1813     (*                            ~~~~~~~~~~~*)
  1814     else (Nd (b, bs), cuts)
  1815   | cut_level_'_ cuts P (Nd (b, bs)) ((p::ps),p_) =
  1816     let val (bs',cuts') = cut_level_'_ cuts P (nth p bs) (ps, p_)
  1817     in (Nd (b, repl_app bs p bs'), cuts @ cuts') end;
  1818 
  1819 (*before WN050219*)
  1820 fun cut_level (_:pos' list) (_:pos) EmptyPtree (_:pos') =
  1821     raise PTREE "cut_level EmptyPtree _"
  1822   | cut_level _ _ (Nd ( _, _)) ([],_) = raise PTREE "cut_level _ []"
  1823 
  1824   | cut_level cuts P (Nd (b, bs)) (p::[],p_) = 
  1825     if test_trans b 
  1826     then (Nd (b, take (p:posel, bs)),
  1827 	  cuts @ 
  1828 	  (if p_ = Frm andalso (*#*) g_ostate b = Complete
  1829 	   then [(P@[p],Res)] else ([]:pos' list)) @
  1830 	  (*WN041020 here we assume what is presented on the worksheet ?!*)
  1831 	  (get_allpos's (P, p+1) (takerest (p, bs))))
  1832     else (Nd (b, bs), cuts)
  1833 
  1834   | cut_level cuts P (Nd (b, bs)) ((p::ps),p_) =
  1835     let val (bs',cuts') = cut_level cuts P (nth p bs) (ps, p_)
  1836     in (Nd (b, repl_app bs p bs'), cuts @ cuts') end;
  1837 
  1838 (*OLD version before WN050219, overwritten below*)
  1839 fun cut_tree _ (([],_):pos') = raise PTREE "cut_tree _ ([],_)"
  1840   | cut_tree pt (pos as ([p],_)) =
  1841     let	val (pt', cuts) = cut_level ([]:pos' list) [] pt pos
  1842     in (pt', cuts @ (if get_obj g_ostate pt [] = Incomplete 
  1843 		     then [] else [([],Res)])) end
  1844   | cut_tree pt (p,p_) =
  1845     let	
  1846 	fun cutfn pt cuts (p,p_) = 
  1847 	    let val (pt', cuts') = cut_level [] (lev_up p) pt (p,p_)
  1848 		val cuts'' = if get_obj g_ostate pt (lev_up p) = Incomplete 
  1849 			     then [] else [(lev_up p, Res)]
  1850 	    in if length cuts' > 0 andalso length p > 1
  1851 	       then cutfn pt' (cuts @ cuts') (lev_up p, Frm(*-->(p,Res)*))
  1852 	       else (pt',cuts @ cuts') end
  1853 	val (pt', cuts) = cutfn pt [] (p,p_)
  1854     in (pt', cuts @ (if get_obj g_ostate pt [] = Incomplete 
  1855 		     then [] else [([], Res)])) end;
  1856 
  1857 
  1858 (*########/ inserted from ctreeNEW.sml \#################################**)
  1859 
  1860 (*.get all positions in a ptree until ([],Res) or ostate=Incomplete
  1861 val get_allp = fn : 
  1862   pos' list -> : accumulated, start with []
  1863   pos ->       : the offset for subtrees wrt the root
  1864   ptree ->     : (sub)tree
  1865   pos'         : initialization (the last pos' before ...)
  1866   -> pos' list : of positions in this (sub) tree (relative to the root)
  1867 .*)
  1868 (* val (cuts, P, pt, pos) = ([], [3], get_nd pt [3], ([], Frm):pos');
  1869    val (cuts, P, pt, pos) = ([], [2], get_nd pt [2], ([], Frm):pos');
  1870    length (children pt);
  1871    *)
  1872 fun get_allp (cuts:pos' list) (P:pos, pos:pos') pt =
  1873     (let val nxt = move_dn [] pt pos (*exn if Incomplete reached*)
  1874      in if nxt <> ([],Res) 
  1875 	then get_allp (cuts @ [nxt]) (P, nxt) pt
  1876 	else (map (apfst (curry op@ P)) (cuts @ [nxt])): pos' list
  1877      end) handle PTREE _ => (map (apfst (curry op@ P)) cuts);
  1878 
  1879 
  1880 (*the pts are assumed to be on the same level*)
  1881 fun get_allps (cuts: pos' list) (P:pos) [] = cuts
  1882   | get_allps cuts P (pt::pts) =
  1883     let val below = get_allp [] (P, ([], Frm)) pt
  1884 	val levfrm = 
  1885 	    if is_pblnd pt 
  1886 	    then (P, Pbl)::below
  1887 	    else if last_elem P = 1 
  1888 	    then (P, Frm)::below
  1889 	    else (*Trans*) below
  1890 	val levres = levfrm @ (if null below then [(P, Res)] else [])
  1891     in get_allps (cuts @ levres) (lev_on P) pts end;
  1892 
  1893 
  1894 (**.these 2 funs decide on how far cut_tree goes.**)
  1895 (*.shall the nodes _after_ the pos to be inserted at be deleted?.*)
  1896 fun test_trans (PrfObj{branch = Transitive,...}) = true
  1897   | test_trans (PrfObj{branch = NoBranch,...}) = true
  1898   | test_trans (PblObj{branch = Transitive,...}) = true 
  1899   | test_trans (PblObj{branch = NoBranch,...}) = true 
  1900   | test_trans _ = false;
  1901 (*.shall cutting be continued on the higher level(s)?
  1902    the Nd regarded will NOT be changed.*)
  1903 fun cutlevup (PblObj _) = false (*for tests of LK0502*)
  1904   | cutlevup _ = true;
  1905     
  1906 (*cut_bottom new S(603)..(608)
  1907 cut the level at the bottom of the pos (used by cappend_...)
  1908 and handle the parent in order to avoid extra case for root
  1909 fn: ptree ->         : the _whole_ ptree for cut_levup
  1910     pos * posel ->   : the pos after split_last
  1911     ptree ->         : the parent of the Nd to be cut
  1912 return
  1913     (ptree *         : the updated ptree
  1914      pos' list) *    : the pos's cut
  1915      bool            : cutting shall be continued on the higher level(s)
  1916 *)
  1917 fun cut_bottom _ (pt' as Nd (b, [])) = ((pt', []), cutlevup b)
  1918   | cut_bottom (P:pos, p:posel) (Nd (b, bs)) =
  1919     let (*divide level into 3 parts...*)
  1920 	val keep = take (p - 1, bs)
  1921 	val pt' as Nd (_,bs') = nth p bs
  1922 	(*^^^^^_here_ will be 'insert'ed by 'append_..'*)
  1923 	val (tail, tp) = (takerest (p, bs), 
  1924 			  if null (takerest (p, bs)) then 0 else p + 1)
  1925 	val (children, cuts) = 
  1926 	    if test_trans b
  1927 	    then (keep,
  1928 		  (if is_pblnd pt' then [(P @ [p], Pbl)] else [])
  1929 		  @ (get_allp  [] (P @ [p], (P, Frm)) pt')
  1930 		  @ (get_allps [] (P @ [p+1]) tail))
  1931 	    else (keep @ [(*'insert'ed by 'append_..'*)] @ tail,
  1932 		  get_allp  [] (P @ [p], (P, Frm)) pt')
  1933 	val (pt'', cuts) = 
  1934 	    if cutlevup b
  1935 	    then (Nd (del_res b, children), 
  1936 		  cuts @ (if g_ostate b = Incomplete then [] else [(P,Res)]))
  1937 	    else (Nd (b, children), cuts)
  1938 	(*val _= writeln("####cut_bottom (P, p)="^pos2str (P @ [p])^
  1939 		       ", Nd=.............................................")
  1940 	val _= show_pt pt''
  1941 	val _= writeln("####cut_bottom form='"^
  1942 		       term2str (get_obj g_form pt'' []))
  1943 	val _= writeln("####cut_bottom cuts#="^string_of_int (length cuts)^
  1944 		       ", cuts="^pos's2str cuts)*)
  1945     in ((pt'', cuts:pos' list), cutlevup b) end;
  1946 print_depth 3;
  1947 
  1948 
  1949 (*.go all levels from the bottom of 'pos' up to the root, 
  1950  on each level compose the children of a node and accumulate the cut Nds
  1951 args
  1952    pos' list ->      : for accumulation
  1953    bool -> 	     : cutting shall be continued on the higher level(s)
  1954    ptree -> 	     : the whole ptree for 'get_nd pt P' on each level
  1955    ptree -> 	     : the Nd from the lower level for insertion at path
  1956    pos * posel ->    : pos=path split for convenience
  1957    ptree -> 	     : Nd the children of are under consideration on this call 
  1958 returns		     :
  1959    ptree * pos' list : the updated parent-Nd and the pos's of the Nds cut
  1960 .*)
  1961 print_depth 99;
  1962 fun cut_levup (cuts:pos' list) clevup pt pt' (P:pos, p:posel) (Nd (b, bs)) =
  1963     let (*divide level into 3 parts...*)
  1964 	val keep = take (p - 1, bs)
  1965 	(*val pt' comes as argument from below*)
  1966 	val (tail, tp) = (takerest (p, bs), 
  1967 			  if null (takerest (p, bs)) then 0 else p + 1)
  1968 	val (children, cuts') = 
  1969 	    if clevup
  1970 	    then (keep @ [pt'], get_allps [] (P @ [p+1]) tail)
  1971 	    else (keep @ [pt'] @ tail, [])
  1972 	val clevup' = if clevup then cutlevup b else false 
  1973 	(*the first Nd with false stops cutting on all levels above*)
  1974 	val (pt'', cuts') = 
  1975 	    if clevup'
  1976 	    then (Nd (del_res b, children), 
  1977 		  cuts' @ (if g_ostate b = Incomplete then [] else [(P,Res)]))
  1978 	    else (Nd (b, children), cuts')
  1979 	(*val _= writeln("#####cut_levup clevup= "^bool2str clevup)
  1980 	val _= writeln("#####cut_levup cutlevup b= "^bool2str (cutlevup b))
  1981 	val _= writeln("#####cut_levup (P, p)="^pos2str (P @ [p])^
  1982 		       ", Nd=.............................................")
  1983 	val _= show_pt pt''
  1984 	val _= writeln("#####cut_levup form='"^
  1985 		       term2str (get_obj g_form pt'' []))
  1986 	val _= writeln("#####cut_levup cuts#="^string_of_int (length cuts)^
  1987 		       ", cuts="^pos's2str cuts)*)
  1988     in if null P then (pt'', (cuts @ cuts'):pos' list)
  1989        else let val (P, p) = split_last P
  1990 	    in cut_levup (cuts @ cuts') clevup' pt pt'' (P, p) (get_nd pt P)
  1991 	    end
  1992     end;
  1993  
  1994 
  1995 fun cut_tree pt (pos,_) =
  1996     if not (existpt pos pt) 
  1997     then (pt,[]) (*appending a formula never cuts anything*)
  1998     else let val (P, p) = split_last pos
  1999 	     val ((pt', cuts), clevup) = cut_bottom (P, p) (get_nd pt P)
  2000 	 (*        pt' is the updated parent of the Nd to cappend_..*)
  2001 	 in if null P then (pt', cuts)
  2002 	    else let val (P, p) = split_last P
  2003 		 in cut_levup cuts clevup pt pt' (P, p) (get_nd pt P)
  2004 		 end
  2005 	 end;
  2006 print_depth 3;
  2007 (*########\ inserted from ctreeNEW.sml /#################################**)
  2008 
  2009 fun append_atomic p l f r f' s pt = 
  2010   let (**val _= writeln("#@append_atomic: pos ="^pos2str p)**)
  2011 	val (iss, f) = if existpt p pt andalso get_obj g_tac pt p=Empty_Tac
  2012 		     then (*after Take*)
  2013 			 ((fst (get_obj g_loc pt p), Some l), 
  2014 			  get_obj g_form pt p) 
  2015 (*040223	     else ((Some l, None), f)*)
  2016 		     else ((None, Some l), f)
  2017   in insert (PrfObj {cell = None,
  2018 		     form  = f,
  2019 		     tac  = r,
  2020 		     loc   = iss,
  2021 		     branch= NoBranch,
  2022 		     result= f',
  2023 		     ostate= s}) pt p end;
  2024 
  2025 (*20.8.02: cappend_* FIXXXXME cut branches below cannot be decided here:
  2026   detail - generate - cappend: inserted, not appended !!!
  2027 
  2028   cut decided in applicable_in !?!
  2029 *)
  2030 fun cappend_atomic pt p loc f r f' s = 
  2031 (* val (pt, p, loc, f, r, f', s) = 
  2032        (pt,p,l,f,Rewrite_Set_Inst (subst2subs subs',id_rls rls'),
  2033 	(f',asm),Complete);
  2034    *)
  2035 ((*writeln("##@cappend_atomic: pos ="^pos2str p);*)
  2036   apfst (append_atomic p loc f r f' s) (cut_tree pt (p,Frm))
  2037 );
  2038 (*TODO.WN050305 redesign the handling of istates*)
  2039 fun cappend_atomic pt p ist_res f r f' s = 
  2040     if existpt p pt andalso get_obj g_tac pt p=Empty_Tac
  2041     then (*after Take: transfer Frm and respective istate*)
  2042 	let val (ist_form, f) = (get_loc pt (p,Frm), 
  2043 				 get_obj g_form pt p)
  2044 	    val (pt, cs) = cut_tree pt (p,Frm)
  2045 	    val pt = append_atomic p e_istate f r f' s pt
  2046 	    val pt = update_loc' pt p (Some ist_form, Some ist_res)
  2047 	in (pt, cs) end
  2048     else apfst (append_atomic p ist_res f r f' s) (cut_tree pt (p,Frm));
  2049 
  2050 
  2051 (* called by Take *)
  2052 fun append_form p l f pt = 
  2053 ((*writeln("##@append_form: pos ="^pos2str p);*)
  2054   insert (PrfObj {cell = None,
  2055 		  form  = (*if existpt p pt 
  2056 		  andalso get_obj g_tac pt p = Empty_Tac 
  2057 			    (*distinction from 'old' (+complete!) pobjs*)
  2058 			    then get_obj g_form pt p else*) f,
  2059 		  tac  = Empty_Tac,
  2060 		  loc   = (Some l, None),
  2061 		  branch= NoBranch,
  2062 		  result= (e_term,[]),
  2063 		  ostate= Incomplete}) pt p
  2064 );
  2065 (* val (p,loc,f) = ([1], e_istate, str2term "x + 1 = 2");
  2066    val (p,loc,f) = (fst p, e_istate, str2term "-1 + x = 0");
  2067    *)
  2068 fun cappend_form pt p loc f =
  2069 ((*writeln("##@cappend_form: pos ="^pos2str p);*)
  2070   apfst (append_form p loc f) (cut_tree pt (p,Frm))
  2071 );
  2072 fun cappend_form pt p loc f =
  2073 let (*val _= writeln("##@cappend_form: pos ="^pos2str p)
  2074     val _= writeln("##@cappend_form before cut_tree: loc ="^istate2str loc)*)
  2075     val (pt', cs) = cut_tree pt (p,Frm)
  2076     val pt'' = append_form p loc f pt'
  2077     (*val _= writeln("##@cappend_form after append: loc ="^
  2078 		   istates2str (get_obj g_loc pt'' p))*)
  2079 in (pt'', cs) end;
  2080 
  2081 
  2082     
  2083 fun append_result pt p l f s =
  2084 ((*writeln("##@append_result: pos ="^pos2str p);*)
  2085     (appl_obj (repl_result (fst (get_obj g_loc pt p),
  2086 			    Some l) f s) pt p, [])
  2087 );
  2088 
  2089 
  2090 (*WN041022 deprecated, still for kbtest/diffapp.sml, /systest/root-equ.sml*)
  2091 fun append_parent p l f r b pt = 
  2092   let (*val _= writeln("###append_parent: pos ="^pos2str p);*)
  2093     val (ll,f) = if existpt p pt andalso get_obj g_tac pt p=Empty_Tac
  2094 		  then ((fst (get_obj g_loc pt p), Some l), 
  2095 			get_obj g_form pt p) 
  2096 		 else ((Some l, None), f)
  2097   in insert (PrfObj 
  2098 	  {cell = None,
  2099 	   form  = f,
  2100 	   tac  = r,
  2101 	   loc   = ll,
  2102 	   branch= b,
  2103 	   result= (e_term,[]),
  2104 	   ostate= Incomplete}) pt p end;
  2105 fun cappend_parent pt p loc f r b =
  2106 ((*writeln("###cappend_parent: pos ="^pos2str p);*)
  2107   apfst (append_parent p loc f r b) (cut_tree pt (p,Und))
  2108 );
  2109 
  2110 
  2111 fun append_problem [] l fmz (strs,spec,hdf) _ =
  2112 ((*writeln("###append_problem: pos = []");*)
  2113   (Nd (PblObj 
  2114 	       {cell  = None,
  2115 		origin= (strs,spec,hdf),
  2116 		fmz   = fmz,
  2117 		spec  = empty_spec,
  2118 		probl = []:itm list,
  2119 		meth  = []:itm list,
  2120 		env   = None,
  2121 		loc   = (Some l, None),
  2122 		branch= TransitiveB,(*FIXXXXXME.27.8.03: for equations only*)
  2123 		result= (e_term,[]),
  2124 		ostate= Incomplete},[]))
  2125 )
  2126   | append_problem p l fmz (strs,spec,hdf) pt =
  2127 ((*writeln("###append_problem: pos ="^pos2str p);*)
  2128   insert (PblObj 
  2129 	  {cell  = None,
  2130 	   origin= (strs,spec,hdf),
  2131 	   fmz   = fmz,
  2132 	   spec  = empty_spec,
  2133 	   probl = []:itm list,
  2134 	   meth  = []:itm list,
  2135 	   env   = None,
  2136 	   loc   = (Some l, None),
  2137 	   branch= TransitiveB,
  2138 	   result= (e_term,[]),
  2139 	   ostate= Incomplete}) pt p
  2140 );
  2141 fun cappend_problem _ [] loc fmz ori =
  2142 ((*writeln("###cappend_problem: pos = []");*)
  2143   (append_problem [] loc fmz ori EmptyPtree,[])
  2144 )
  2145   | cappend_problem pt p loc fmz ori = 
  2146 ((*writeln("###cappend_problem: pos ="^pos2str p);*)
  2147   apfst (append_problem p (loc:istate) fmz ori) (cut_tree pt (p,Frm))
  2148 );
  2149 
  2150 (*.get the theory explicitly specified for the rootpbl;
  2151    thus use this function _after_ finishing specification.*)
  2152 fun rootthy (Nd (PblObj {spec=(thyID, _, _),...}, _)) = assoc_thy thyID
  2153   | rootthy _ = raise error "rootthy";
  2154