src/Tools/isac/Interpret/calchead.sml
author Walther Neuper <neuper@ist.tugraz.at>
Thu, 23 Sep 2010 08:43:36 +0200
branchisac-update-Isa09-2
changeset 38011 3147f2c1525c
parent 38010 a37a3ab989f4
child 38012 f57ddfd09474
permissions -rw-r--r--
repaired is_copy_named, cpy_nam and improved tests & comments
     1 (* Specify-phase: specifying and modeling a problem or a subproblem. The
     2    most important types are declared in mstools.sml.
     3    author: Walther Neuper
     4    991122
     5    (c) due to copyright terms
     6 
     7 use"ME/calchead.sml";
     8 use"calchead.sml";
     9 12345678901234567890123456789012345678901234567890123456789012345678901234567890
    10         10        20        30        40        50        60        70        80
    11 *)
    12 
    13 (* TODO interne Funktionen aus sig entfernen *)
    14 signature CALC_HEAD =
    15   sig
    16     datatype additm = Add of SpecifyTools.itm | Err of string
    17     val all_dsc_in : SpecifyTools.itm_ list -> Term.term list
    18     val all_modspec : ptree * pos' -> ptree * pos'
    19     datatype appl = Appl of tac_ | Notappl of string
    20     val appl_add :
    21        theory ->
    22        string ->
    23        SpecifyTools.ori list ->
    24        SpecifyTools.itm list ->
    25        (string * (Term.term * Term.term)) list -> cterm' -> additm
    26     type calcstate
    27     type calcstate'
    28     val chk_vars : term ppc -> string * Term.term list
    29     val chktyp :
    30        theory -> int * term list * term list -> term
    31     val chktyps :
    32        theory -> term list * term list -> term list
    33     val complete_metitms :
    34    SpecifyTools.ori list ->
    35    SpecifyTools.itm list ->
    36    SpecifyTools.itm list -> pat list -> SpecifyTools.itm list
    37     val complete_mod_ : ori list * pat list * pat list * itm list ->
    38 			itm list * itm list
    39     val complete_mod : ptree * pos' -> ptree * (pos * pos_)
    40     val complete_spec : ptree * pos' -> ptree * pos'
    41     val cpy_nam :
    42        pat list -> preori list -> pat -> preori
    43     val e_calcstate : calcstate
    44     val e_calcstate' : calcstate'
    45     val eq1 : ''a -> 'b * (''a * 'c) -> bool
    46     val eq3 :
    47        ''a -> Term.term -> 'b * 'c * 'd * ''a * SpecifyTools.itm_ -> bool
    48     val eq4 : ''a -> 'b * ''a list * 'c * 'd * 'e -> bool
    49     val eq5 :
    50        'a * 'b * 'c * 'd * SpecifyTools.itm_ ->
    51        'e * 'f * 'g * Term.term * 'h -> bool
    52     val eq_dsc : SpecifyTools.itm * SpecifyTools.itm -> bool
    53     val eq_pos' : ''a * pos_ -> ''a * pos_ -> bool
    54     val f_mout : theory -> mout -> Term.term
    55     val filter_outs :
    56        SpecifyTools.ori list ->
    57        SpecifyTools.itm list -> SpecifyTools.ori list
    58     val filter_pbt :
    59        SpecifyTools.ori list ->
    60        ('a * (Term.term * 'b)) list -> SpecifyTools.ori list
    61     val foldl1 : ('a * 'a -> 'a) -> 'a list -> 'a
    62     val foldr1 : ('a * 'a -> 'a) -> 'a list -> 'a
    63     val form : 'a -> ptree -> (string * ('a * pos_) * Term.term) list
    64     val formres : 'a -> ptree -> (string * ('a * pos_) * Term.term) list
    65     val gen_ins' : ('a * 'a -> bool) -> 'a * 'a list -> 'a list
    66     val get_formress :
    67        (string * (pos * pos_) * Term.term) list list ->
    68        pos -> ptree list -> (string * (pos * pos_) * Term.term) list
    69     val get_forms :
    70        (string * (pos * pos_) * Term.term) list list ->
    71        posel list -> ptree list -> (string * (pos * pos_) * Term.term) list
    72     val get_interval : pos' -> pos' -> int -> ptree -> (pos' * term) list
    73     val get_ocalhd : ptree * pos' -> ocalhd
    74     val get_spec_form : tac_ -> pos' -> ptree -> mout
    75     val geti_ct :
    76        theory ->
    77        SpecifyTools.ori -> SpecifyTools.itm -> string * cterm'
    78     val getr_ct : theory -> SpecifyTools.ori -> string * cterm'
    79     val has_list_type : Term.term -> bool
    80     val header : pos_ -> pblID -> metID -> pblmet
    81     val insert_ppc :
    82        theory ->
    83        int * SpecifyTools.vats * bool * string * SpecifyTools.itm_ ->
    84        SpecifyTools.itm list -> SpecifyTools.itm list
    85     val insert_ppc' :
    86        SpecifyTools.itm -> SpecifyTools.itm list -> SpecifyTools.itm list
    87     val is_complete_mod : ptree * pos' -> bool
    88     val is_complete_mod_ : SpecifyTools.itm list -> bool
    89     val is_complete_modspec : ptree * pos' -> bool
    90     val is_complete_spec : ptree * pos' -> bool
    91     val is_copy_named : 'a * ('b * Term.term) -> bool
    92     val is_copy_named_idstr : string -> bool
    93     val is_error : SpecifyTools.itm_ -> bool
    94     val is_field_correct : ''a -> ''b -> (''a * ''b list) list -> bool
    95     val is_known :
    96        theory ->
    97        string ->
    98        SpecifyTools.ori list ->
    99        Term.term -> string * SpecifyTools.ori * Term.term list
   100     val is_list_type : Term.typ -> bool
   101     val is_notyet_input :
   102        theory ->
   103        SpecifyTools.itm list ->
   104        Term.term list ->
   105        SpecifyTools.ori ->
   106        ('a * (Term.term * Term.term)) list -> string * SpecifyTools.itm
   107     val is_parsed : SpecifyTools.itm_ -> bool
   108     val is_untouched : SpecifyTools.itm -> bool
   109     val matc :
   110        theory ->
   111        pat list ->
   112        Term.term list ->
   113        (int list * string * Term.term * Term.term list) list ->
   114        (int list * string * Term.term * Term.term list) list
   115     val match_ags :
   116        theory -> pat list -> Term.term list -> SpecifyTools.ori list
   117     val maxl : int list -> int
   118     val match_ags_msg : string list -> Term.term -> Term.term list -> unit
   119     val memI : ''a list -> ''a -> bool
   120     val mk_additem : string -> cterm' -> tac
   121     val mk_delete : theory -> string -> SpecifyTools.itm_ -> tac
   122     val mtc :
   123        theory -> pat -> Term.term -> SpecifyTools.preori option
   124     val nxt_add :
   125        theory ->
   126        SpecifyTools.ori list ->
   127        (string * (Term.term * 'a)) list ->
   128        SpecifyTools.itm list -> (string * cterm') option
   129     val nxt_model_pbl : tac_ -> ptree * (int list * pos_) -> tac_
   130     val nxt_spec :
   131        pos_ ->
   132        bool ->
   133        SpecifyTools.ori list ->
   134        spec ->
   135        SpecifyTools.itm list * SpecifyTools.itm list ->
   136        (string * (Term.term * 'a)) list * (string * (Term.term * 'b)) list ->
   137        spec -> pos_ * tac
   138     val nxt_specif : tac -> ptree * (int list * pos_) -> calcstate'
   139     val nxt_specif_additem :
   140        string -> cterm' -> ptree * (int list * pos_) -> calcstate'
   141     val nxt_specify_init_calc : fmz -> calcstate
   142     val ocalhd_complete :
   143        SpecifyTools.itm list ->
   144        (bool * Term.term) list -> domID * pblID * metID -> bool
   145     val ori2Coritm :
   146 	pat list -> ori -> itm
   147     val ori_2itm :
   148        'a ->
   149        SpecifyTools.itm_ ->
   150        Term.term -> Term.term list -> SpecifyTools.ori -> SpecifyTools.itm
   151     val overwrite_ppc :
   152        theory ->
   153        int * SpecifyTools.vats * bool * string * SpecifyTools.itm_ ->
   154        SpecifyTools.itm list ->
   155        (int * SpecifyTools.vats * bool * string * SpecifyTools.itm_) list
   156     val parse_ok : SpecifyTools.itm_ list -> bool
   157     val posform2str : pos' * ptform -> string
   158     val posforms2str : (pos' * ptform) list -> string
   159     val posterms2str : (pos' * term) list -> string (*tests only*)
   160     val ppc135list : 'a SpecifyTools.ppc -> 'a list
   161     val ppc2list : 'a SpecifyTools.ppc -> 'a list
   162     val pt_extract :
   163        ptree * (int list * pos_) ->
   164        ptform * tac option * Term.term list
   165     val pt_form : ppobj -> ptform
   166     val pt_model : ppobj -> pos_ -> ptform
   167     val reset_calchead : ptree * pos' -> ptree * pos'
   168     val seek_oridts :
   169        theory ->
   170        string ->
   171        Term.term * Term.term list ->
   172        (int * SpecifyTools.vats * string * Term.term * Term.term list) list
   173        -> string * SpecifyTools.ori * Term.term list
   174     val seek_orits :
   175        theory ->
   176        string ->
   177        Term.term list ->
   178        (int * SpecifyTools.vats * string * Term.term * Term.term list) list
   179        -> string * SpecifyTools.ori * Term.term list
   180     val seek_ppc :
   181        int -> SpecifyTools.itm list -> SpecifyTools.itm option
   182     val show_pt : ptree -> unit
   183     val some_spec : spec -> spec -> spec
   184     val specify :
   185        tac_ ->
   186        pos' ->
   187        cid ->
   188        ptree ->
   189        (posel list * pos_) * ((posel list * pos_) * istate) * mout * tac *
   190        safe * ptree
   191     val specify_additem :
   192        string ->
   193        cterm' * 'a ->
   194        int list * pos_ ->
   195        'b ->
   196        ptree ->
   197        (pos * pos_) * ((pos * pos_) * istate) * mout * tac * safe * ptree
   198     val tag_form : theory -> term * term -> term
   199     val test_types : theory -> Term.term * Term.term list -> string
   200     val typeless : Term.term -> Term.term
   201     val unbound_ppc : term SpecifyTools.ppc -> Term.term list
   202     val vals_of_oris : SpecifyTools.ori list -> Term.term list
   203     val variants_in : Term.term list -> int
   204     val vars_of_pbl_ : ('a * ('b * Term.term)) list -> Term.term list
   205     val vars_of_pbl_' : ('a * ('b * Term.term)) list -> Term.term list
   206   end
   207  
   208 
   209 
   210 
   211 
   212 (*---------------------------------------------------------------------*)
   213 structure CalcHead (**): CALC_HEAD(**) =
   214 
   215 struct
   216 (*---------------------------------------------------------------------*)
   217 
   218 (* datatypes *)
   219 
   220 (*.the state wich is stored after each step of calculation; it contains
   221    the calc-state and a list of [tac,istate](="tacis") to be applied.
   222    the last_elem tacis is the first to apply to the calc-state and
   223    the (only) one shown to the front-end as the 'proposed tac'.
   224    the calc-state resulting from the application of tacis is not stored,
   225    because the tacis hold enought information for efficiently rebuilding
   226    this state just by "fun generate ".*)
   227 type calcstate = 
   228      (ptree * pos') *    (*the calc-state to which the tacis could be applied*)
   229      (taci list);        (*ev. several (hidden) steps; 
   230                            in REVERSE order: first tac_ to apply is last_elem*)
   231 val e_calcstate = ((EmptyPtree, e_pos'), [e_taci]):calcstate;
   232 
   233 (*the state used during one calculation within the mathengine; it contains
   234   a list of [tac,istate](="tacis") which generated the the calc-state;
   235   while this state's tacis are extended by each (internal) step,
   236   the calc-state is used for creating new nodes in the calc-tree
   237   (eg. applicable_in requires several particular nodes of the calc-tree)
   238   and then replaced by the the newly created;
   239   on leave of the mathengine the resuing calc-state is dropped anyway,
   240   because the tacis hold enought information for efficiently rebuilding
   241   this state just by "fun generate ".*)
   242 type calcstate' = 
   243      taci list *        (*cas. several (hidden) steps; 
   244                           in REVERSE order: first tac_ to apply is last_elem*)
   245      pos' list *        (*a "continuous" sequence of pos',
   246 			 deleted by application of taci list*)     
   247      (ptree * pos');    (*the calc-state resulting from the application of tacis*)
   248 val e_calcstate' = ([e_taci], [e_pos'], (EmptyPtree, e_pos')):calcstate';
   249 
   250 (*FIXXXME.WN020430 intermediate hack for fun ass_up*)
   251 fun f_mout thy (Form' (FormKF (_,_,_,_,f))) = (term_of o the o (parse thy)) f
   252   | f_mout thy _ = raise error "f_mout: not called with formula";
   253 
   254 
   255 (*.is the calchead complete ?.*)
   256 fun ocalhd_complete (its: itm list) (pre: (bool * term) list) (dI,pI,mI) = 
   257     foldl and_ (true, map #3 its) andalso 
   258     foldl and_ (true, map #1 pre) andalso 
   259     dI<>e_domID andalso pI<>e_pblID andalso mI<>e_metID;
   260 
   261 
   262 (* make a term 'typeless' for comparing with another 'typeless' term;
   263    'type-less' usually is illtyped                                  *)
   264 fun typeless (Const(s,_)) = (Const(s,e_type)) 
   265   | typeless (Free(s,_)) = (Free(s,e_type))
   266   | typeless (Var(n,_)) = (Var(n,e_type))
   267   | typeless (Bound i) = (Bound i)
   268   | typeless (Abs(s,_,t)) = Abs(s,e_type, typeless t)
   269   | typeless (t1 $ t2) = (typeless t1) $ (typeless t2);
   270 (*
   271 > val (SOME ct) = parse thy "max_relation (A=#2*a*b - a^^^#2)";
   272 > val (_,t1) = split_dsc_t hs (term_of ct);
   273 > val (SOME ct) = parse thy "A=#2*a*b - a^^^#2";
   274 > val (_,t2) = split_dsc_t hs (term_of ct);
   275 > typeless t1 = typeless t2;
   276 val it = true : bool
   277 *)
   278 
   279 
   280 
   281 (*.to an input (d,ts) find the according ori and insert the ts.*)
   282 (*WN.11.03: + dont take first inter<>[]*)
   283 fun seek_oridts thy sel (d,ts) [] = 
   284   ("'"^(Syntax.string_of_term (thy2ctxt thy) (comp_dts thy (d,ts)))^
   285    "' not found (typed)", (0,[],sel,d,ts):ori, [])
   286   (* val (id,vat,sel',d',ts')::oris = ori;
   287      val (id,vat,sel',d',ts') = ori;
   288      *)
   289   | seek_oridts thy sel (d,ts) ((id,vat,sel',d',ts')::(oris:ori list)) =
   290     if sel = sel' andalso d=d' andalso (inter op = ts ts') <> [] 
   291     then if sel = sel' 
   292 	 then ("", 
   293                (id,vat,sel,d, inter op = ts ts'):ori, 
   294                ts')
   295 	 else ((Syntax.string_of_term (thy2ctxt thy) (comp_dts thy (d,ts))) 
   296                ^ " not for " ^ sel, 
   297                e_ori_, 
   298                [])
   299     else seek_oridts thy sel (d,ts) oris;
   300 
   301 (*.to an input (_,ts) find the according ori and insert the ts.*)
   302 fun seek_orits thy sel ts [] = 
   303   ("'"^
   304    (strs2str (map (Syntax.string_of_term (thy2ctxt thy)) ts))^
   305    "' not found (typed)", e_ori_, [])
   306   | seek_orits thy sel ts ((id,vat,sel',d,ts')::(oris:ori list)) =
   307     if sel = sel' andalso (inter op = ts ts') <> [] 
   308       then if sel = sel' 
   309 	   then ("",
   310                  (id,vat,sel,d, inter op = ts ts'):ori, 
   311                  ts')
   312 	   else (((strs2str' o map (Syntax.string_of_term (thy2ctxt thy))) ts)
   313                  ^ " not for "^sel, 
   314                  e_ori_, 
   315                  [])
   316     else seek_orits thy sel ts oris;
   317 (* false
   318 > val ((id,vat,sel',d,ts')::(ori':ori)) = ori;
   319 > seek_orits thy sel ts [(id,vat,sel',d,ts')];
   320 uncaught exception TYPE
   321 > seek_orits thy sel ts [];
   322 uncaught exception TYPE
   323 *)
   324 
   325 (*find_first item with #1 equal to id*)
   326 fun seek_ppc id [] = NONE
   327   | seek_ppc id (p::(ppc:itm list)) =
   328     if id = #1 p then SOME p else seek_ppc id ppc;
   329 
   330 
   331 
   332 (*---------------------------------------------(3) nach ptyps.sml 23.3.02*)
   333 
   334 
   335 datatype appl = Appl of tac_ | Notappl of string;
   336 
   337 fun ppc2list ({Given=gis,Where=whs,Find=fis,
   338 	       With=wis,Relate=res}: 'a ppc) =
   339   gis @ whs @ fis @ wis @ res;
   340 fun ppc135list ({Given=gis,Find=fis,Relate=res,...}: 'a ppc) =
   341   gis @ fis @ res;
   342 
   343 
   344 
   345 
   346 (* get the number of variants in a problem in 'original',
   347    assumes equal descriptions in immediate sequence    *)
   348 fun variants_in ts =
   349   let fun eq(x,y) = head_of x = head_of y;
   350     fun cnt eq [] y n = ([n],[])
   351       | cnt eq (x::xs) y n = if eq(x,y) then cnt eq xs y (n+1)
   352 			     else ([n], x::xs);
   353     fun coll eq  xs [] = xs
   354       | coll eq  xs (y::ys) = 
   355       let val (n,ys') = cnt eq (y::ys) y 0;
   356       in if ys' = [] then xs @ n else coll eq  (xs @ n) ys' end;
   357     val vts = subtract op = [1] (distinct (coll eq [] ts));
   358   in case vts of [] => 1 | [n] => n
   359       | _ => error "different variants in formalization" end;
   360 (*
   361 > cnt (op=) [2,2,2,4,5,5,5,5,5] 2 0;
   362 val it = ([3],[4,5,5,5,5,5]) : int list * int list
   363 > coll (op=) [] [1,2,2,2,4,5,5,5,5,5];
   364 val it = [1,3,1,5] : int list
   365 *)
   366 
   367 fun is_list_type (Type("List.list",_)) = true
   368   | is_list_type _ = false;
   369 (* fun destr (Type(str,sort)) = (str,sort);
   370 > val (SOME ct) = parse thy "lll::real list";
   371 > val ty = (#T o rep_cterm) ct;
   372 > is_list_type ty;
   373 val it = true : bool 
   374 > destr ty;
   375 val it = ("List.list",["RealDef.real"]) : string * typ list
   376 > atomty ((#t o rep_cterm) ct);
   377 *** -------------
   378 *** Free ( lll, real list)
   379 val it = () : unit
   380  
   381 > val (SOME ct) = parse thy "[lll::real]";
   382 > val ty = (#T o rep_cterm) ct;
   383 > is_list_type ty;
   384 val it = true : bool 
   385 > destr ty;
   386 val it = ("List.list",["'a"]) : string * typ list
   387 > atomty ((#t o rep_cterm) ct);
   388 *** -------------
   389 *** Const ( List.list.Cons, [real, real list] => real list)
   390 ***   Free ( lll, real)
   391 ***   Const ( List.list.Nil, real list) 
   392 
   393 > val (SOME ct) = parse thy "lll";
   394 > val ty = (#T o rep_cterm) ct;
   395 > is_list_type ty;
   396 val it = false : bool  *)
   397 
   398 
   399 fun has_list_type (Free(_,T)) = is_list_type T
   400   | has_list_type _ = false;
   401 (*
   402 > val (SOME ct) = parse thy "lll::real list";
   403 > has_list_type (term_of ct);
   404 val it = true : bool
   405 > val (SOME ct) = parse thy "[lll::real]";
   406 > has_list_type (term_of ct);
   407 val it = false : bool *)
   408 
   409 fun is_parsed (Syn _) = false
   410   | is_parsed _ = true;
   411 fun parse_ok its = foldl and_ (true, map is_parsed its);
   412 
   413 fun all_dsc_in itm_s =
   414   let    
   415     fun d_in (Cor ((d,_),_)) = [d]
   416       | d_in (Syn c) = []
   417       | d_in (Typ c) = []
   418       | d_in (Inc ((d,_),_)) = [d]
   419       | d_in (Sup (d,_)) = [d]
   420       | d_in (Mis (d,_)) = [d];
   421   in (flat o (map d_in)) itm_s end;  
   422 
   423 (* 30.1.00 ---
   424 fun is_Syn (Syn _) = true
   425   | is_Syn (Typ _) = true
   426   | is_Syn _ = false;
   427  --- *)
   428 fun is_error (Cor (_,ts)) = false
   429   | is_error (Sup (_,ts)) = false
   430   | is_error (Inc (_,ts)) = false
   431   | is_error (Mis (_,ts)) = false
   432   | is_error _ = true;
   433 
   434 (* 30.1.00 ---
   435 fun ct_in (Syn (c)) = c
   436   | ct_in (Typ (c)) = c
   437   | ct_in _ = raise error "ct_in called for Cor .. Sup";
   438  --- *)
   439 
   440 (*#############################################################*)
   441 (*#############################################################*)
   442 (* vvv--- aus nnewcode.sml am 30.1.00 ---vvv *)
   443 
   444 
   445 (* testdaten besorgen:
   446    use"test-coil-kernel.sml";
   447    val (PblObj{origin=(oris,_,_),meth={ppc=itms,...},...}) = 
   448         get_obj I pt p;
   449   *)
   450 
   451 (* given oris, ppc, 
   452    variant V: oris union ppc => int, id ID: oris union ppc => int
   453 
   454    ppc is_complete == 
   455      EX vt:V. ALL r:oris --> EX i:ppc. ID r = ID i  &  complete i
   456 
   457    and
   458      @vt = max sum(i : ppc) V i
   459 *)
   460 
   461 
   462 
   463 (*
   464 > ((vts_cnt (vts_in itms))) itms;
   465 
   466 
   467 
   468 ---^^--test 10.3.
   469 > val vts = vts_in itms;
   470 val vts = [1,2,3] : int list
   471 > val nvts = vts_cnt vts itms;
   472 val nvts = [(1,6),(2,5),(3,7)] : (int * int) list
   473 > val mx = max2 nvts;
   474 val mx = (3,7) : int * int
   475 > val v = max_vt itms;
   476 val v = 3 : int
   477 --------------------------
   478 > 
   479 *)
   480 
   481 (*.get the first term in ts from ori.*)
   482 (* val (_,_,fd,d,ts) = hd miss;
   483    *)
   484 fun getr_ct thy ((_,_,fd,d,ts):ori) =
   485   (fd, ((Syntax.string_of_term (thy2ctxt thy)) o 
   486         (comp_dts thy)) (d,[hd ts]):cterm');
   487 (* val t = comp_dts thy (d,[hd ts]);
   488    *)
   489 
   490 (* get a term from ori, notyet input in itm *)
   491 fun geti_ct thy ((_,_,_,d,ts):ori) ((_,_,_,fd,itm_):itm) =  
   492   (fd, ((Syntax.string_of_term (thy2ctxt thy)) o (comp_dts thy)) 
   493            (d, subtract op = (ts_in itm_) ts):cterm');
   494 (* test-maximum.sml fmy <> [], Init_Proof ...
   495    val (_,_,_,d,ts) = ori; val (_,_,_,fd,itm_) = hd icl;
   496    val d' $ ts' = (term_of o the o (parse thy)) "fixedValues [r=Arbfix]";
   497    atomty d;
   498    atomty d';
   499    atomty (hd ts);
   500    atomty ts';
   501    cterm_of thy (d $ (hd ts));
   502    cterm_of thy (d' $ ts');
   503 
   504    comp_dts thy (d,ts);
   505    *)
   506 
   507 
   508 (* in FE dsc, not dat: this is in itms ...*)
   509 fun is_untouched ((_,_,false,_,Inc((_,[]),_)):itm) = true
   510   | is_untouched _ = false;
   511 
   512 
   513 (* select an item in oris, notyet input in itms 
   514    (precondition: in itms are only Cor, Sup, Inc) *)
   515 local infix mem;
   516 fun x mem [] = false
   517   | x mem (y :: ys) = x = y orelse x mem ys;
   518 in 
   519 fun nxt_add thy ([]:ori list) pbt itms = (*root (only) ori...fmz=[]*)
   520   let
   521     fun test_d d ((i,_,_,_,itm_):itm) = (d = (d_in itm_)) andalso i<>0; 
   522     fun is_elem itms (f,(d,t)) = 
   523       case find_first (test_d d) itms of 
   524 	SOME _ => true | NONE => false;
   525   in case filter_out (is_elem itms) pbt of
   526 (* val ((f,(d,_))::itms) = filter_out (is_elem itms) pbt;
   527    *)
   528     (f,(d,_))::itms => 
   529       SOME (f:string, ((Syntax.string_of_term (thy2ctxt thy)) o comp_dts thy) (d,[]):cterm')
   530   | _ => NONE end
   531 
   532 (* val (thy,itms) = (assoc_thy (if dI=e_domID then dI' else dI),pbl);
   533    *)
   534   | nxt_add thy oris pbt itms =
   535   let
   536     fun testr_vt v ori = (curry (op mem) v) (#2 (ori:ori))
   537       andalso (#3 ori) <>"#undef";
   538     fun testi_vt v itm = (curry (op mem) v) (#2 (itm:itm));
   539     fun test_id ids r = curry (op mem) (#1 (r:ori)) ids;
   540 (* val itm = hd icl; val (_,_,_,d,ts) = v6;
   541    *)
   542     fun test_subset (itm:itm) ((_,_,_,d,ts):ori) = 
   543 	(d_in (#5 itm)) = d andalso subset op = (ts_in (#5 itm), ts);
   544     fun false_and_not_Sup((i,v,false,f,Sup _):itm) = false
   545       | false_and_not_Sup (i,v,false,f, _) = true
   546       | false_and_not_Sup  _ = false;
   547 
   548     val v = if itms = [] then 1 else max_vt itms;
   549     val vors = if v = 0 then oris else filter (testr_vt v) oris;(*oris..vat*)
   550     val vits = if v = 0 then itms (*because of dsc without dat*)
   551 	       else filter (testi_vt v) itms;                   (*itms..vat*)
   552     val icl = filter false_and_not_Sup vits; (* incomplete *)
   553   in if icl = [] 
   554      then case filter_out (test_id (map #1 vits)) vors of
   555 	      [] => NONE
   556 	    (* val miss = filter_out (test_id (map #1 vits)) vors;
   557 	       *)
   558 	    | miss => SOME (getr_ct thy (hd miss))
   559      else
   560 	 case find_first (test_subset (hd icl)) vors of
   561 	     (* val SOME ori = find_first (test_subset (hd icl)) vors;
   562 	      *)
   563 	     NONE => raise error "nxt_add: EX itm. not(dat(itm)<=dat(ori))"
   564 	   | SOME ori => SOME (geti_ct thy ori (hd icl))
   565   end
   566 end;
   567 
   568 
   569 
   570 fun mk_delete thy "#Given"  itm_ = Del_Given   (itm_out thy itm_)
   571   | mk_delete thy "#Find"   itm_ = Del_Find    (itm_out thy itm_)
   572   | mk_delete thy "#Relate" itm_ = Del_Relation(itm_out thy itm_)
   573   | mk_delete thy str _ = 
   574   raise error ("mk_delete: called with field '"^str^"'");
   575 fun mk_additem "#Given" ct = Add_Given ct
   576   | mk_additem "#Find"  ct = Add_Find ct    
   577   | mk_additem "#Relate"ct = Add_Relation ct
   578   | mk_additem str _ = 
   579   raise error ("mk_additem: called with field '"^str^"'");
   580 
   581 
   582 
   583 
   584 
   585 (* find the next tac in specify (except nxt_model_pbl)
   586    4.00.: TODO: do not return a pos !!!
   587           (sind from DG comes the _OLD_ writepos)*)
   588 (* 
   589 > val (pbl,pbt,mpc) =(pbl',get_pbt cpI,(#ppc o get_met) cmI);
   590 > val (dI,pI,mI) = empty_spec;
   591 > nxt_spec Pbl (oris:ori list) ((dI',pI',mI'):spec(*original*))
   592   ((pbl:itm list), (met:itm list)) (pbt,mpc) ((dI,pI,mI):spec);
   593 
   594 at Init_Proof:
   595 > val met = [];val (pbt,mpc) = (get_pbt pI',(#ppc o get_met) mI');
   596 > val (dI,pI,mI) = empty_spec;
   597 > nxt_spec Pbl (oris:ori list) ((dI',pI',mI'):spec(*original*))
   598   ((pbl:itm list), (met:itm list)) (pbt,mpc) ((dI,pI,mI):spec);
   599   *)
   600 
   601 (*. determine the next step of specification;
   602     not done here: Refine_Tacitly (otherwise *** unknown method: (..., no_met))
   603 eg. in rootpbl 'no_met': 
   604 args:
   605   preok          predicates are _all_ ok, or problem matches completely
   606   oris           immediately from formalization 
   607   (dI',pI',mI')  specification coming from author/parent-problem
   608   (pbl,          item lists specified by user
   609    met)          -"-, tacitly completed by copy_probl
   610   (dI,pI,mI)     specification explicitly done by the user
   611   (pbt, mpc)     problem type, guard of method
   612 .*)
   613 (* val (preok,pbl,pbt,mpc)=(pb,pbl',(#ppc o get_pbt) cpI,(#ppc o get_met) cmI);
   614    val (preok,pbl,pbt,mpc)=(pb,pbl',ppc,(#ppc o get_met) cmI);
   615    val (Pbl, preok, oris, (dI',pI',mI'), (pbl,met), (pbt,mpc), (dI,pI,mI)) =
   616        (p_, pb, oris, (dI',pI',mI'), (probl,meth), 
   617 	(ppc, (#ppc o get_met) cmI), (dI,pI,mI));
   618    *)
   619 fun nxt_spec Pbl preok (oris:ori list) ((dI',pI',mI'):spec)
   620   ((pbl:itm list), (met:itm list)) (pbt,mpc) ((dI,pI,mI):spec) = 
   621   ((*writeln"### nxt_spec Pbl";*)
   622    if dI'=e_domID andalso dI=e_domID then (Pbl, Specify_Theory dI')
   623    else if pI'=e_pblID andalso pI=e_pblID then (Pbl, Specify_Problem pI')
   624 	else case find_first (is_error o #5) (pbl:itm list) of
   625 	  SOME (_,_,_,fd,itm_) => 
   626 	      (Pbl, mk_delete 
   627 	       (assoc_thy (if dI=e_domID then dI' else dI)) fd itm_)
   628 	| NONE => 
   629 	    ((*writeln"### nxt_spec is_error NONE";*)
   630 	     case nxt_add (assoc_thy (if dI=e_domID then dI' else dI)) 
   631 		 oris pbt pbl of
   632 (* val SOME (fd,ct') = nxt_add (assoc_thy (if dI=e_domID then dI' else dI)) 
   633                        oris pbt pbl;
   634   *)
   635 	       SOME (fd,ct') => ((*writeln"### nxt_spec nxt_add SOME";*)
   636 				 (Pbl, mk_additem fd ct'))
   637 	     | NONE => (*pbl-items complete*)
   638 	       if not preok then (Pbl, Refine_Problem pI')
   639 	       else
   640 		 if dI = e_domID then (Pbl, Specify_Theory dI')
   641 		 else if pI = e_pblID then (Pbl, Specify_Problem pI')
   642 		      else if mI = e_metID then (Pbl, Specify_Method mI')
   643 			   else
   644 			     case find_first (is_error o #5) met of
   645 			       SOME (_,_,_,fd,itm_) => 
   646 				   (Met, mk_delete (assoc_thy dI) fd itm_)
   647 			     | NONE => 
   648 				 (case nxt_add (assoc_thy dI) oris mpc met of
   649 				      SOME (fd,ct') => (*30.8.01: pre?!?*)
   650 				      (Met, mk_additem fd ct')
   651 				    | NONE => 
   652 				      ((*Solv 3.4.00*)Met, Apply_Method mI))))
   653 (* val preok=pb; val (pbl, met) = (pbl,met');
   654    val (pbt,mpc)=((#ppc o get_pbt) cpI,(#ppc o get_met) cmI);
   655    val (Met, preok, oris, (dI',pI',mI'), (pbl,met), (pbt,mpc), (dI,pI,mI)) =
   656        (p_, pb, oris, (dI',pI',mI'), (probl,meth), 
   657 	(ppc, (#ppc o get_met) cmI), (dI,pI,mI));
   658    *)
   659   | nxt_spec Met preok oris (dI',pI',mI') (pbl, met) (pbt,mpc) (dI,pI,mI) = 
   660   ((*writeln"### nxt_spec Met"; *)
   661    case find_first (is_error o #5) met of
   662      SOME (_,_,_,fd,itm_) => 
   663 	 (Met, mk_delete (assoc_thy (if dI=e_domID then dI' else dI)) fd itm_)
   664    | NONE => 
   665        case nxt_add (assoc_thy (if dI=e_domID then dI' else dI))oris mpc met of
   666 	 SOME (fd,ct') => (Met, mk_additem fd ct')
   667        | NONE => 
   668 	   ((*writeln"### nxt_spec Met: nxt_add NONE";*)
   669 	    if dI = e_domID then (Met, Specify_Theory dI')
   670 	    else if pI = e_pblID then (Met, Specify_Problem pI')
   671 		 else if not preok then (Met, Specify_Method mI)
   672 		      else (Met, Apply_Method mI)));
   673 	  
   674 (* di_ pI_ mI_ pos_
   675 val itms = [(1,[1],true,"#Find",Cor(e_term,[e_term])):itm,
   676 	    (2,[2],true,"#Find",Syn("empty"))];
   677 *)
   678 
   679 
   680 (* ^^^--- aus nnewcode.sml am 30.1.00 ---^^^ *)
   681 (*#############################################################*)
   682 (*#############################################################*)
   683 (* vvv--- aus nnewcode.sml vor 29.1.00 ---vvv *)
   684 
   685 (*3.3.--
   686 fun update_itm (cl,d,ts) ((id,vt,_,sl,Cor (_,_)):itm) = 
   687   (id,vt,cl,sl,Cor (d,ts)):itm
   688   | update_itm (cl,d,ts) (id,vt,_,sl,Syn (_)) =   
   689   raise error ("update_itm "^((Syntax.string_of_term (thy2ctxt thy)) (comp_dts thy (d,ts)))^
   690 	       " not not for Syn (s:cterm')")
   691   | update_itm (cl,d,ts) (id,vt,_,sl,Typ (_)) = 
   692   raise error ("update_itm "^((Syntax.string_of_term (thy2ctxt thy)) (comp_dts thy (d,ts)))^
   693 	       " not not for Typ (s:cterm')")
   694   | update_itm (cl,d,ts) (id,vt,_,sl,Fal (_,_)) =
   695   (id,vt,cl,sl,Fal (d,ts))
   696   | update_itm (cl,d,ts) (id,vt,_,sl,Inc (_,_)) =
   697   (id,vt,cl,sl,Inc (d,ts))
   698   | update_itm (cl,d,ts) (id,vt,_,sl,Sup (_,_)) =
   699   (id,vt,cl,sl,Sup (d,ts));
   700 *)
   701 
   702 
   703 
   704 
   705 fun is_field_correct sel d dscpbt =
   706   case assoc (dscpbt, sel) of
   707     NONE => false
   708   | SOME ds => member op = ds d;
   709 
   710 (*. update the itm_ already input, all..from ori .*)
   711 (* val (id,vt,fd,d,ts) = (i,v,f,d,ts\\ts');
   712    *)
   713 fun ori_2itm thy itm_ pid all ((id,vt,fd,d,ts):ori) = 
   714   let 
   715     val ts' = union op = (ts_in itm_) ts;
   716     val pval = pbl_ids' thy d ts'
   717 	(*WN.9.5.03: FIXXXME [#0, epsilon]
   718 	  here would upd_penv be called for [#0, epsilon] etc. *)
   719     val complete = if eq_set op = (ts', all) then true else false;
   720   in case itm_ of
   721     (Cor _) => 
   722 	(if fd = "#undef" then (id,vt,complete,fd,Sup(d,ts')) 
   723 	 else (id,vt,complete,fd,Cor((d,ts'),(pid, pval)))):itm
   724   | (Syn c)     => raise error ("ori_2itm wants to overwrite "^c)
   725   | (Typ c)     => raise error ("ori_2itm wants to overwrite "^c)
   726   | (Inc _) => if complete
   727 	       then (id,vt,true ,fd, Cor ((d,ts'),(pid, pval)))
   728 	       else (id,vt,false,fd, Inc ((d,ts'),(pid, pval)))
   729   | (Sup ((*_,_*)d,ts')) => (*4.9.01 lost env*)
   730 	 (*if fd = "#undef" then*) (id,vt,complete,fd,Sup(d,ts'))
   731 	 (*else (id,vt,complete,fd,Cor((d,ts'),e))*)
   732 (* 28.1.00: not completely clear ---^^^ etc.*)
   733 (* 4.9.01: Mis just copied---vvv *)
   734   | (Mis _) => if complete
   735 		     then (id,vt,true ,fd, Cor ((d,ts'),(pid, pval)))
   736 		     else (id,vt,false,fd, Inc ((d,ts'),(pid, pval)))
   737   end;
   738 
   739 
   740 fun eq1 d (_,(d',_)) = (d = d');
   741 fun eq3 f d (_,_,_,f',itm_) = f = f' andalso d = (d_in itm_); 
   742 
   743 
   744 (* 'all' ts from ori; ts is the input; (ori carries rest of info)
   745    9.01: this + ori_2itm is _VERY UNCLEAR_ ? overhead ?
   746    pval: value for problem-environment _NOT_ checked for 'inter' --
   747    -- FIXXME.WN.11.03 the generation of penv has to go to insert_ppc
   748   (as it has been done for input_icalhd+insert_ppc' in 11.03)*)
   749 (*. is_input ori itms <=> 
   750     EX itm. (1) ori(field,dsc) = itm(field,dsc) & (2..4)
   751             (2) ori(ts) subset itm(ts)        --- Err "already input"       
   752 	    (3) ori(ts) inter itm(ts) = empty --- new: ori(ts)
   753 	    (4) -"- <> empty                  --- new: ori(ts) \\ inter .*)
   754 (* val(itms,(i,v,f,d,ts)) = (ppc,ori');
   755    *)
   756 fun is_notyet_input thy (itms:itm list) all ((i,v,f,d,ts):ori) pbt =
   757   case find_first (eq1 d) pbt of
   758       SOME (_,(_,pid)) =>(* val SOME (_,(_,pid)) = find_first (eq1 d) pbt;
   759                             val SOME (_,_,_,_,itm_)=find_first (eq3 f d) itms;
   760 			   *)
   761       (case find_first (eq3 f d) itms of
   762 	   SOME (_,_,_,_,itm_) =>
   763 	   let 
   764 	       val ts' = inter op = (ts_in itm_) ts;
   765 	   in if subset op = (ts, ts') 
   766 	      then (((strs2str' o 
   767 		      map (Syntax.string_of_term (thy2ctxt thy))) ts')^
   768 		    " already input", e_itm)                            (*2*)
   769 	      else ("", 
   770                     ori_2itm thy itm_ pid all (i,v,f,d,
   771                                                subtract op = ts' ts))   (*3,4*)
   772 	   end
   773 	 | NONE => ("", ori_2itm thy (Inc ((e_term,[]),(pid,[]))) 
   774 				 pid all (i,v,f,d,ts))                  (*1*)
   775 	)
   776     | NONE => ("", ori_2itm thy (Sup (d,ts)) 
   777 			      e_term all (i,v,f,d,ts));
   778 
   779 fun test_types thy (d,ts) =
   780   let 
   781     val s = !show_types; val _ = show_types:= true;
   782     val opt = (try (comp_dts thy)) (d,ts);
   783     val msg = case opt of 
   784       SOME _ => "" 
   785     | NONE => ((Syntax.string_of_term (thy2ctxt thy) d)^" "^
   786 	     ((strs2str' o map (Syntax.string_of_term (thy2ctxt thy))) ts)
   787 	     ^ " is illtyped");
   788     val _ = show_types:= s
   789   in msg end;
   790 
   791 
   792 
   793 fun maxl [] = raise error "maxl of []"
   794   | maxl (y::ys) =
   795   let fun mx x [] = x
   796 	| mx x (y::ys) = if x < (y:int) then mx y ys else mx x ys
   797   in mx y ys end;
   798 
   799 
   800 (*. is the input term t known in oris ? 
   801     give feedback on all(?) strange input;
   802     return _all_ terms already input to this item (e.g. valuesFor a,b) .*)
   803 (*WN.11.03: from lists*)
   804 fun is_known thy sel ori t =
   805 (* val (ori,t)=(oris,term_of ct);
   806    *)
   807   let
   808     val ots = (distinct o flat o (map #5)) (ori:ori list);
   809     val oids = ((map (fst o dest_Free)) o distinct o 
   810 		flat o (map vars)) ots;
   811     val (d,ts(*,pval*)) = split_dts thy t;
   812     val ids = map (fst o dest_Free) 
   813       ((distinct o (flat o (map vars))) ts);
   814   in if (subtract op = oids ids) <> []
   815      then (("identifiers "^(strs2str' (subtract op = oids ids))^
   816 	    " not in example"), e_ori_, [])
   817      else 
   818 	 if d = e_term 
   819 	 then 
   820 	     if not (subset op = (map typeless ts, map typeless ots))
   821 	     then (("terms '"^
   822 		    ((strs2str' o (map (Syntax.string_of_term 
   823 					    (thy2ctxt thy)))) ts)^
   824 		    "' not in example (typeless)"), e_ori_, [])
   825 	     else (case seek_orits thy sel ts ori of
   826 		       ("", ori_ as (_,_,_,d,ts), all) =>
   827 		       (case test_types thy (d,ts) of
   828 			    "" => ("", ori_, all)
   829 			  | msg => (msg, e_ori_, []))
   830 		     | (msg,_,_) => (msg, e_ori_, []))
   831 	 else 
   832 	     if member op = (map #4 ori) d
   833 	     then seek_oridts thy sel (d,ts) ori
   834 	     else ((Syntax.string_of_term (thy2ctxt thy) d)^
   835 		   (*" not in example", e_ori_, []) ///11.11.03*)
   836 		   " not in example", (0,[],sel,d,ts), [])
   837   end;
   838 
   839 
   840 (*. for return-value of appl_add .*)
   841 datatype additm =
   842 	 Add of itm
   843        | Err of string;    (*error-message*)
   844 
   845 
   846 (*. add an item; check wrt. oris and pbt .*)
   847 
   848 (* in contrary to oris<>[] below, this part handles user-input
   849    extremely acceptive, i.e. accept input instead error-msg *)
   850 fun appl_add thy sel ([]:ori list) ppc pbt ct' =
   851 (* val (ppc,pbt,ct',env) = (pbl, (#ppc o get_pbt) cpI, ct, []:envv);
   852    !!!! 28.8.01: env tested _minimally_ !!!
   853    *)
   854   let 
   855     val i = 1 + (if ppc=[] then 0 else maxl (map #1 ppc));
   856   in case parse thy ct' of (*should be done in applicable_in 4.00.FIXME*)
   857     NONE => Add (i,[],false,sel,Syn ct')
   858 (* val (SOME ct) = parse thy ct';
   859    *)
   860   | SOME ct =>
   861       let
   862 	val (d,ts(*,pval*)) = split_dts thy (term_of ct);
   863       in if d = e_term 
   864 	 then Add (i,[],false,sel,Mis (dsc_unknown,hd ts(*24.3.02*)))
   865       
   866 	 else  
   867 	   (case find_first (eq1 d) pbt of
   868 	     NONE => Add (i,[],true,sel,Sup ((d,ts)))
   869 	   | SOME (f,(_,id)) =>
   870 (* val SOME (f,(_,id)) = find_first (eq1 d) pbt;
   871    *)
   872 	       let
   873 		 fun eq2 d ((i,_,_,_,itm_):itm) = 
   874 		     (d = (d_in itm_)) andalso i<>0;
   875 	       in case find_first (eq2 d) ppc of 
   876 		 NONE => Add (i,[],true,f, Cor ((d,ts), (id, (*pval*)
   877 							 pbl_ids' thy d ts)))
   878 	       | SOME (i',_,_,_,itm_) => 
   879 (* val SOME (i',_,_,_,itm_) = find_first (eq2 d) ppc;
   880    val NONE = find_first (eq2 d) ppc;
   881    *)
   882 		   if is_list_dsc d
   883 		   then let val ts = union op = ts (ts_in itm_) 
   884 			in Add (if ts_in itm_ = [] then i else i',
   885 				 [],true,f,Cor ((d, ts), (id, (*pval*)
   886 							  pbl_ids' thy d ts)))
   887 			end
   888 		   else Add (i',[],true,f,Cor ((d,ts),(id, (*pval*)
   889 						       pbl_ids' thy d ts)))
   890 	       end
   891 	   )
   892       end
   893   end
   894 (*. add ct to ppc .*)
   895 (*FIXXME: accept items as Sup, Syn here, too (like appl_add..oris=[] above)*)
   896 (* val (ppc,pbt) = (pbl, ppc);
   897    val (ppc,pbt) = (met, (#ppc o get_met) cmI);
   898 
   899    val (ppc,pbt) = (pbl, (#ppc o get_pbt) cpI);
   900    *)
   901   | appl_add thy sel oris ppc pbt(*only for upd_envv*) ct = 
   902   let
   903     val ctopt = parse thy ct;
   904   in case ctopt of
   905     NONE => Err ("syntax error in "^ct)
   906   | SOME ct =>(* val SOME ct = ctopt;
   907 		 val (msg,ori',all) = is_known thy sel oris (term_of ct);
   908 		 val (msg,itm) = is_notyet_input thy ppc all ori' pbt;
   909 		*) 
   910     (case is_known thy sel oris (term_of ct) of
   911 	 ("",ori'(*ts='ct'*), all) => 
   912 	 (case is_notyet_input thy ppc all ori' pbt of
   913 	      ("",itm)  => Add itm
   914 	    | (msg,_) => Err msg)
   915        | (msg,_,_) => Err msg)
   916   end;
   917 (* 
   918 > val (msg,itm) = is_notyet_input thy ppc all ori';
   919 val itm = (12,[3],false,"#Relate",Cor (Const #,[#,#])) : itm
   920 > val itm_ = #5 itm;
   921 > val ts = ts_in itm_;
   922 > map (atomty) ts; 
   923 *)
   924 
   925 (** make oris from args of the stac SubProblem and from pbt **)
   926 
   927 (*.can this formal argument (of a model-pattern) be omitted in the arg-list
   928    of a SubProblem ? see ME/ptyps.sml 'type met '.*)
   929 fun is_copy_named_idstr str =
   930     case (rev o explode) str of
   931       (*"_":: _ ::"_"::_ => true*)
   932 	"'":: _ ::"'"::_ => (tracing ((strs2str o (rev o explode)) 
   933                                   "is_copy_named_idstr: " ^ str ^ " T"); true)
   934       | _ => (tracing ((strs2str o (rev o explode)) 
   935                                   "is_copy_named_idstr: " ^ str ^ " F"); false);
   936 fun is_copy_named (_, (_, t)) = (is_copy_named_idstr o free2str) t;
   937 
   938 (*.should this formal argument (of a model-pattern) create a new identifier?.*)
   939 fun is_copy_named_generating_idstr str =
   940     if is_copy_named_idstr str
   941     then case (rev o explode) str of
   942       (*"_"::"_"::"_"::_ => false*)
   943 	"'"::"'"::"'"::_ => false
   944       | _ => true
   945     else false;
   946 fun is_copy_named_generating (_, (_, t)) = 
   947     (is_copy_named_generating_idstr o free2str) t;
   948 
   949 (*.split type-wrapper from scr-arg and build part of an ori;
   950    an type-error is reported immediately, raises an exn, 
   951    subsequent handling of exn provides 2nd part of error message.*)
   952 fun mtc thy ((str, (dsc, _)):pat) (ty $ var) =
   953     (* val (thy, (str, (dsc, _)), (ty $ var)) =
   954 	   (thy,  p,               a);
   955        *)
   956     (cterm_of thy (dsc $ var);(*type check*)
   957      SOME ((([1], str, dsc, (*[var]*)
   958 	    split_dts' (dsc, var))): preori)(*:ori without leading #*))
   959     handle e as TYPE _ => 
   960 	   (writeln (dashs 70 ^ "\n"
   961 	^"*** ERROR while creating the items for the model of the ->problem\n"
   962 	^"*** from the ->stac with ->typeconstructor in arglist:\n"
   963 	^"*** item (->description ->value): "^term2str dsc^" "^term2str var^"\n"
   964 	^"*** description: "^(term_detail2str dsc)
   965 	^"*** value: "^(term_detail2str var)
   966 	^"*** typeconstructor in script: "^(term_detail2str ty)
   967 	^"*** checked by theory: "^(theory2str thy)^"\n"
   968 	^"*** " ^ dots 66);
   969 	    OldGoals.print_exn e; (*raises exn again*)
   970 	(*raise ERROR "actual args do not match formal args";FIXXXME.WN100916*)
   971 	NONE);
   972 
   973 (*.match each pat of the model-pattern with an actual argument;
   974    precondition: copy-named vars are filtered out.*)
   975 fun matc thy ([]:pat list)  _  (oris:preori list) = oris
   976   | matc thy pbt [] _ =
   977     (writeln (dashs 70);
   978      raise error ("actual arg(s) missing for '"^pats2str pbt
   979 		 ^"' i.e. should be 'copy-named' by '*_._'"))
   980   | matc thy ((p as (s,(d,t)))::pbt) (a::ags) oris =
   981     (* val (thy, ((p as (s,(d,t)))::pbt), (a::ags), oris) =
   982 	   (thy,  pbt',                    ags,     []);
   983        (*recursion..*)
   984        val (thy, ((p as (s,(d,t)))::pbt), (a::ags), oris) =
   985 	   (thy,  pbt,                     ags,    (oris @ [ori]));
   986        *)
   987     (*del?..*)if (is_copy_named_idstr o free2str) t then oris
   988     else(*..del?*) let val opt = mtc thy p a;  
   989 	 in case opt of
   990 		(* val SOME ori = mtc thy p a;
   991 		   *)
   992 		SOME ori => matc thy pbt ags (oris @ [ori])
   993 	      | NONE => [](*WN050903 skipped by exn handled in match_ags*)
   994 	 end; 
   995 (* run subp-rooteq.sml until Init_Proof before ...
   996 > val Nd (PblObj {origin=(oris,_,_),...},_) = pt;(*from test/subp-rooteq.sml*)
   997 > fun xxxfortest (_,a,b,c,d) = (a,b,c,d);val oris = map xxxfortest oris;
   998 
   999  other vars as in mtc ..
  1000 > matc thy (drop_last pbt) ags [];
  1001 val it = ([[1],"#Given",Const #,[#]),(0,[#],"#Given",Const #,[#])],2)*)
  1002 
  1003 
  1004 (* generate a new variable "x_i" name from a related given one "x"
  1005    by use of oris relating "v_i_" (is_copy_named!) to "v_"
  1006    e.g. (v_, x) & (v_i_, ?) --> (v_i_, x_i) *)
  1007 
  1008 (* generate a new variable "x_i" name from a related given one "x"
  1009    by use of oris relating "v_v'i'" (is_copy_named!) to "v_v"
  1010    e.g. (v_v, x) & (v_v'i', ?) --> (v_v'i', x_i) *)
  1011 fun cpy_nam (pbt:pat list) (oris:preori list) (p as (field,(dsc,t)):pat) =
  1012   (if is_copy_named_generating p
  1013    then (*WN051014 kept strange old code ...*)
  1014        let fun sel (_,_,d,ts) = comp_ts (d, ts) 
  1015 	   val cy' = (implode o (drop_last_n 3) o explode o free2str) t
  1016 	   val ext = (last_elem o drop_last o explode o free2str) t
  1017 	   val vars' = map (free2str o snd o snd) pbt (*cpy-nam filtered_out*)
  1018 	   val vals = map sel oris
  1019 	   val cy_ext = (free2str o the) (assoc (vars'~~vals, cy'))^"_"^ext
  1020        in ([1], field, dsc, [mk_free (type_of t) cy_ext]):preori end
  1021    else ([1], field, dsc, [t])
  1022 	)
  1023   handle _ => raise error ("cpy_nam: for "^(term2str t));
  1024 
  1025 (*.match the actual arguments of a SubProblem with a model-pattern
  1026    and create an ori list (in root-pbl created from formalization).
  1027    expects ags:pats = 1:1, while copy-named are filtered out of pats;
  1028    if no 1:1 the exn raised by matc/mtc and handled at call.
  1029    copy-named pats are appended in order to get them into the model-items.*)
  1030 fun match_ags thy (pbt:pat list) ags =
  1031     let fun flattup (i,(var,bool,str,itm_)) = (i,var,bool,str,itm_);
  1032 	val pbt' = filter_out is_copy_named pbt;
  1033 	val cy = filter is_copy_named pbt;
  1034 	val oris' = matc thy pbt' ags [];
  1035 	val cy' = map (cpy_nam pbt' oris') cy;
  1036 	val ors = add_id (oris' @ cy'); 
  1037     (*appended in order to get ^^^^^ into the model-items*)
  1038     in (map flattup ors):ori list end;
  1039 
  1040 (*.report part of the error-msg which is not available in match_args.*)
  1041 fun match_ags_msg pI stac ags =
  1042     let val s = !show_types
  1043 	val _ = show_types:= true
  1044 	val pats = (#ppc o get_pbt) pI
  1045 	val msg = (dots 70^"\n"
  1046 		 ^"*** problem "^strs2str pI^" has the ...\n"
  1047 		 ^"*** model-pattern "^pats2str pats^"\n"
  1048 		 ^"*** stac   '"^term2str stac^"' has the ...\n"
  1049 		 ^"*** arg-list "^terms2str ags^"\n"
  1050 		 ^dashs 70)
  1051 	(*WN100921 ^^^^ expect TYPE errormsg below; lost with Isa09*)
  1052 	val _ = show_types:= s
  1053     in writeln msg end;
  1054 
  1055 
  1056 (*get the variables out of a pbl_; FIXME.WN.0311: is_copy_named ...obscure!!!*)
  1057 fun vars_of_pbl_ pbl_ = 
  1058     let fun var_of_pbl_ (gfr,(dsc,t)) = t
  1059     in ((map var_of_pbl_) o (filter_out is_copy_named)) pbl_ end;
  1060 fun vars_of_pbl_' pbl_ = 
  1061     let fun var_of_pbl_ (gfr,(dsc,t)) = t:term
  1062     in ((map var_of_pbl_)(* o (filter_out is_copy_named)*)) pbl_ end;
  1063 
  1064 fun overwrite_ppc thy itm ppc =
  1065   let 
  1066     fun repl ppc' (_,_,_,_,itm_) [] =
  1067       raise error ("overwrite_ppc: " ^ (itm_2str_ (thy2ctxt thy) itm_) ^ 
  1068                    " not found")
  1069       | repl ppc' itm (p::ppc) =
  1070 	if (#1 itm) = (#1 (p:itm)) then ppc' @ [itm] @ ppc
  1071 	else repl (ppc' @ [p]) itm ppc
  1072   in repl [] itm ppc end;
  1073 
  1074 (*10.3.00: insert the already compiled itm into model;
  1075    ev. filter_out  untouched (in FE: (0,...)) item related to insert-item *)
  1076 (* val ppc=pbl;
  1077    *)
  1078 fun insert_ppc thy itm ppc =
  1079     let 
  1080 	fun eq_untouched d ((0,_,_,_,itm_):itm) = (d = d_in itm_)
  1081 	  | eq_untouched _ _ = false;
  1082 	    val ppc' = 
  1083 		(
  1084 		 (*writeln("### insert_ppc: itm= "^(itm2str_ itm));*)       
  1085 		 case seek_ppc (#1 itm) ppc of
  1086 		     (* val SOME xxx = seek_ppc (#1 itm) ppc;
  1087 		        *)
  1088 		     SOME _ => (*itm updated in is_notyet_input WN.11.03*)
  1089 		     overwrite_ppc thy itm ppc
  1090 		   | NONE => (ppc @ [itm]));
  1091     in filter_out (eq_untouched ((d_in o #5) itm)) ppc' end;
  1092 
  1093 (*from Isabelle/src/Pure/library.ML, _appends_ a new element*)
  1094 fun gen_ins' eq (x, xs) = if gen_mem eq (x, xs) then xs else xs @ [x];
  1095 
  1096 fun eq_dsc ((_,_,_,_,itm_):itm, (_,_,_,_,iitm_):itm) = 
  1097     (d_in itm_) = (d_in iitm_);
  1098 (*insert_ppc = insert_ppc' for appl_add', input_icalhd 11.03,
  1099     handles superfluous items carelessly*)
  1100 fun insert_ppc' itm itms = gen_ins' eq_dsc (itm, itms);
  1101 (* val eee = op=;
  1102  > gen_ins' eee (4,[1,3,5,7]);
  1103 val it = [1, 3, 5, 7, 4] : int list*)
  1104 
  1105 
  1106 (*. output the headline to a ppc .*)
  1107 fun header p_ pI mI =
  1108     case p_ of Pbl => Problem (if pI = e_pblID then [] else pI) 
  1109 	     | Met => Method mI
  1110 	     | pos => raise error ("header called with "^ pos_2str pos);
  1111 
  1112 
  1113 
  1114 (* test-printouts ---
  1115 val _=writeln("### insert_ppc: (d,ts)="^((Syntax.string_of_term (thy2ctxt thy))(comp_dts thy(d,ts))));
  1116  val _=writeln("### insert_ppc: pts= "^
  1117 (strs2str' o map (Syntax.string_of_term (thy2ctxt thy))) pts);
  1118 
  1119 
  1120  val sel = "#Given"; val Add_Given' ct = m;
  1121 
  1122  val sel = "#Find"; val Add_Find' (ct,_) = m; 
  1123  val (p,_) = p;
  1124  val (_,_,f,nxt',_,pt')= specify_additem sel (ct,[]) (p,Pbl(*!!!!!!!*)) c pt;
  1125 --------------
  1126  val sel = "#Given"; val Add_Given' (ct,_) = nxt; val (p,_) = p;
  1127   *)
  1128 fun specify_additem sel (ct,_) (p,Met) c pt = 
  1129     let
  1130       val (PblObj{meth=met,origin=(oris,(dI',pI',mI'),_),
  1131 		  probl=pbl,spec=(dI,pI,mI),...}) = get_obj I pt p;
  1132       val thy = if dI = e_domID then assoc_thy dI' else assoc_thy dI;
  1133     (*val ppt = if pI = e_pblID then get_pbt pI' else get_pbt pI;*)
  1134       val cpI = if pI = e_pblID then pI' else pI;
  1135       val cmI = if mI = e_metID then mI' else mI;
  1136       val {ppc,pre,prls,...} = get_met cmI
  1137     in case appl_add thy sel oris met ppc ct of
  1138       Add itm (*..union old input *) =>
  1139 	let (* val Add itm = appl_add thy sel oris met (#ppc (get_met cmI)) ct;
  1140                *)
  1141 	  val met' = insert_ppc thy itm met;
  1142 	  (*val pt' = update_met pt p met';*)
  1143 	  val ((p,Met),_,_,pt') = 
  1144 	      generate1 thy (case sel of
  1145 				 "#Given" => Add_Given' (ct, met')
  1146 			       | "#Find"  => Add_Find'  (ct, met')
  1147 			       | "#Relate"=> Add_Relation'(ct, met')) 
  1148 			Uistate (p,Met) pt
  1149 	  val pre' = check_preconds thy prls pre met'
  1150 	  val pb = foldl and_ (true, map fst pre')
  1151 	  (*val _=writeln("@@@ specify_additem: Met Add before nxt_spec")*)
  1152 	  val (p_,nxt) =
  1153 	    nxt_spec Met pb oris (dI',pI',mI') (pbl,met') 
  1154 	    ((#ppc o get_pbt) cpI,ppc) (dI,pI,mI);
  1155 	in ((p,p_), ((p,p_),Uistate),
  1156 	    Form' (PpcKF (0,EdUndef,(length p),Nundef,
  1157 			  (Method cmI, itms2itemppc thy met' pre'))),
  1158 	    nxt,Safe,pt') end
  1159     | Err msg =>
  1160 	  let val pre' = check_preconds thy prls pre met
  1161 	      val pb = foldl and_ (true, map fst pre')
  1162 	    (*val _=writeln("@@@ specify_additem: Met Err before nxt_spec")*)
  1163 	      val (p_,nxt) =
  1164 	    nxt_spec Met pb oris (dI',pI',mI') (pbl,met) 
  1165 	    ((#ppc o get_pbt) cpI,(#ppc o get_met) cmI) (dI,pI,mI);
  1166 	  in ((p,p_), ((p,p_),Uistate), Error' (Error_ msg), nxt, Safe,pt) end
  1167     end
  1168 (* val (p,_) = p;
  1169    *)
  1170 | specify_additem sel (ct,_) (p,_(*Frm, Pbl*)) c pt = 
  1171     let
  1172       val (PblObj{meth=met,origin=(oris,(dI',pI',mI'),_),
  1173 		  probl=pbl,spec=(dI,pI,mI),...}) = get_obj I pt p;
  1174       val thy = if dI = e_domID then assoc_thy dI' else assoc_thy dI;
  1175       val cpI = if pI = e_pblID then pI' else pI;
  1176       val cmI = if mI = e_metID then mI' else mI;
  1177       val {ppc,where_,prls,...} = get_pbt cpI;
  1178     in case appl_add thy sel oris pbl ppc ct of
  1179       Add itm (*..union old input *) =>
  1180       (* val Add itm = appl_add thy sel oris pbl ppc ct;
  1181          *)
  1182 	let
  1183 	    (*val _= writeln("###specify_additem: itm= "^(itm2str_ itm));*)
  1184 	  val pbl' = insert_ppc thy itm pbl
  1185 	  val ((p,Pbl),_,_,pt') = 
  1186 	      generate1 thy (case sel of
  1187 				 "#Given" => Add_Given' (ct, pbl')
  1188 			       | "#Find"  => Add_Find'  (ct, pbl')
  1189 			       | "#Relate"=> Add_Relation'(ct, pbl')) 
  1190 			Uistate (p,Pbl) pt
  1191 	  val pre = check_preconds thy prls where_ pbl'
  1192 	  val pb = foldl and_ (true, map fst pre)
  1193 	(*val _=writeln("@@@ specify_additem: Pbl Add before nxt_spec")*)
  1194 	  val (p_,nxt) =
  1195 	    nxt_spec Pbl pb oris (dI',pI',mI') (pbl',met) 
  1196 		     (ppc,(#ppc o get_met) cmI) (dI,pI,mI);
  1197 	  val ppc = if p_= Pbl then pbl' else met;
  1198 	in ((p,p_), ((p,p_),Uistate),
  1199 	    Form' (PpcKF (0,EdUndef,(length p),Nundef,
  1200 			  (header p_ pI cmI,
  1201 			   itms2itemppc thy ppc pre))), nxt,Safe,pt') end
  1202 
  1203     | Err msg =>
  1204 	  let val pre = check_preconds thy prls where_ pbl
  1205 	      val pb = foldl and_ (true, map fst pre)
  1206 	    (*val _=writeln("@@@ specify_additem: Pbl Err before nxt_spec")*)
  1207 	      val (p_,nxt) =
  1208 	    nxt_spec Pbl pb oris (dI',pI',mI') (pbl,met) 
  1209 	    (ppc,(#ppc o get_met) cmI) (dI,pI,mI);
  1210 	  in ((p,p_), ((p,p_),Uistate), Error' (Error_ msg), nxt, Safe,pt) end
  1211     end;
  1212 (* val sel = "#Find"; val (p,_) = p; val Add_Find' ct = nxt;
  1213    val (_,_,f,nxt',_,pt')= specify_additem sel ct (p,Met) c pt;
  1214   *)
  1215 
  1216 (* ori
  1217 val (msg,itm) = appl_add thy sel oris ppc ct;
  1218 val (Cor(d,ts)) = #5 itm;
  1219 map (atomty) ts;
  1220 
  1221 pre
  1222 *)
  1223 
  1224 
  1225 (* val Init_Proof' (fmz,(dI',pI',mI')) = m;
  1226    specify (Init_Proof' (fmz,(dI',pI',mI'))) e_pos' [] EmptyPtree;
  1227    *)
  1228 fun specify (Init_Proof' (fmz,(dI',pI',mI'))) (_:pos') (_:cid) (_:ptree)= 
  1229   let          (* either """"""""""""""" all empty or complete *)
  1230     val thy = assoc_thy dI';
  1231     val oris = if dI' = e_domID orelse pI' = e_pblID then ([]:ori list)
  1232 	       else prep_ori fmz thy ((#ppc o get_pbt) pI');
  1233     val (pt,c) = cappend_problem e_ptree [] e_istate (fmz,(dI',pI',mI'))
  1234 				 (oris,(dI',pI',mI'),e_term);
  1235     val {ppc,prls,where_,...} = get_pbt pI'
  1236     (*val pbl = init_pbl ppc;  WN.9.03: done in Model/Refine_Problem
  1237     val pt = update_pbl pt [] pbl;
  1238     val pre = check_preconds thy prls where_ pbl
  1239     val pb = foldl and_ (true, map fst pre)*)
  1240     val (pbl, pre, pb) = ([], [], false)
  1241   in case mI' of
  1242 	 ["no_met"] => 
  1243 	 (([],Pbl), (([],Pbl),Uistate),
  1244 	  Form' (PpcKF (0,EdUndef,(length []),Nundef,
  1245 			(Problem [], itms2itemppc (assoc_thy dI') pbl pre))),
  1246 	  Refine_Tacitly pI', Safe,pt)
  1247        | _ => 
  1248 	 (([],Pbl), (([],Pbl),Uistate),
  1249 	  Form' (PpcKF (0,EdUndef,(length []),Nundef,
  1250 			(Problem [], itms2itemppc (assoc_thy dI') pbl pre))),
  1251 	  Model_Problem,
  1252 	  Safe,pt)
  1253   end
  1254   (*ONLY for STARTING modeling phase*)
  1255   | specify (Model_Problem' (_,pbl,met)) (pos as (p,p_)) c pt =
  1256   let (* val (Model_Problem' (_,pbl), pos as (p,p_)) = (m, (p,p_));
  1257          *)
  1258     val (PblObj{origin=(oris,(dI',pI',mI'),_), spec=(dI,_,_),...}) = 
  1259 	get_obj I pt p
  1260     val thy' = if dI = e_domID then dI' else dI
  1261     val thy = assoc_thy thy'
  1262     val {ppc,prls,where_,...} = get_pbt pI'
  1263     val pre = check_preconds thy prls where_ pbl
  1264     val pb = foldl and_ (true, map fst pre)
  1265     val ((p,_),_,_,pt) = 
  1266 	generate1 thy (Model_Problem'([],pbl,met)) Uistate pos pt
  1267     val (_,nxt) = nxt_spec Pbl pb oris (dI',pI',mI') (pbl,met) 
  1268 		(ppc,(#ppc o get_met) mI') (dI',pI',mI');
  1269   in ((p,Pbl), ((p,p_),Uistate),
  1270       Form' (PpcKF (0,EdUndef,(length p),Nundef,
  1271 		    (Problem pI', itms2itemppc (assoc_thy dI') pbl pre))),
  1272       nxt, Safe, pt) end
  1273 
  1274 (*. called only if no_met is specified .*)     
  1275   | specify (Refine_Tacitly' (pI,pIre,_,_,_)) (pos as (p,_)) c pt =
  1276   let (* val Refine_Tacitly' (pI,pIre,_,_,_) = m;
  1277          *)
  1278     val (PblObj{origin=(oris,(dI',pI',mI'),_), meth=met, ...}) = 
  1279 	get_obj I pt p;
  1280     val {prls,met,ppc,thy,where_,...} = get_pbt pIre
  1281     (*val pbl = init_pbl ppc --- Model_Problem recognizes probl=[]*)
  1282     (*val pt = update_pbl pt p pbl;
  1283     val pt = update_orispec pt p 
  1284 		(string_of_thy thy, pIre, 
  1285 		 if length met = 0 then e_metID else hd met);*)
  1286     val (domID, metID) = (string_of_thy thy, 
  1287 		      if length met = 0 then e_metID else hd met)
  1288     val ((p,_),_,_,pt) = 
  1289 	generate1 thy (Refine_Tacitly'(pI,pIre,domID,metID,(*pbl*)[])) 
  1290 		  Uistate pos pt
  1291     (*val pre = check_preconds thy prls where_ pbl
  1292     val pb = foldl and_ (true, map fst pre)*)
  1293     val (pbl, pre, pb) = ([], [], false)
  1294   in ((p,Pbl), (pos,Uistate),
  1295       Form' (PpcKF (0,EdUndef,(length p),Nundef,
  1296 		    (Problem pIre, itms2itemppc (assoc_thy dI') pbl pre))),
  1297       Model_Problem, Safe, pt) end
  1298 
  1299   | specify (Refine_Problem' (rfd as (pI,_))) pos c pt =
  1300     let val (pos,_,_,pt) = generate1 (assoc_thy "Isac.thy") 
  1301 				     (Refine_Problem' rfd) Uistate pos pt
  1302     in (pos(*p,Pbl*), (pos(*p,Pbl*),Uistate), Problems (RefinedKF rfd), 
  1303 	Model_Problem, Safe, pt) end
  1304 
  1305 (* val (Specify_Problem' (pI, (ok, (itms, pre)))) = nxt; val (p,_) = p;
  1306    val (Specify_Problem' (pI, (ok, (itms, pre)))) = m; val (p,_) = p;
  1307    *)
  1308   | specify (Specify_Problem' (pI, (ok, (itms, pre)))) (pos as (p,_)) c pt =
  1309   let val (PblObj {origin=(oris,(dI',pI',mI'),_), spec=(dI,_,mI), 
  1310 		   meth=met, ...}) = get_obj I pt p;
  1311     (*val pt = update_pbl pt p itms;
  1312     val pt = update_pblID pt p pI;*)
  1313     val thy = assoc_thy dI
  1314     val ((p,Pbl),_,_,pt)= 
  1315 	generate1 thy (Specify_Problem' (pI, (ok, (itms, pre)))) Uistate pos pt
  1316     val dI'' = assoc_thy (if dI=e_domID then dI' else dI);
  1317     val mI'' = if mI=e_metID then mI' else mI;
  1318   (*val _=writeln("@@@ specify (Specify_Problem) before nxt_spec")*)
  1319     val (_,nxt) = nxt_spec Pbl ok oris (dI',pI',mI') (itms, met) 
  1320 		((#ppc o get_pbt) pI,(#ppc o get_met) mI'') (dI,pI,mI);
  1321   in ((p,Pbl), (pos,Uistate),
  1322       Form' (PpcKF (0,EdUndef,(length p),Nundef,
  1323 		    (Problem pI, itms2itemppc dI'' itms pre))),
  1324       nxt, Safe, pt) end    
  1325 (* val Specify_Method' mID = nxt; val (p,_) = p;
  1326    val Specify_Method' mID = m;
  1327    specify (Specify_Method' mID) (p,p_) c pt;
  1328    *)
  1329   | specify (Specify_Method' (mID,_,_)) (pos as (p,_)) c pt =
  1330   let val (PblObj {origin=(oris,(dI',pI',mI'),_), probl=pbl, spec=(dI,pI,mI), 
  1331 		   meth=met, ...}) = get_obj I pt p;
  1332     val {ppc,pre,prls,...} = get_met mID
  1333     val thy = assoc_thy dI
  1334     val oris = add_field' thy ppc oris;
  1335     (*val pt = update_oris pt p oris; 20.3.02: repl. "#undef"*)
  1336     val dI'' = if dI=e_domID then dI' else dI;
  1337     val pI'' = if pI = e_pblID then pI' else pI;
  1338     val met = if met=[] then pbl else met;
  1339     val (ok, (itms, pre')) = match_itms_oris thy met (ppc,pre,prls ) oris;
  1340     (*val pt = update_met pt p itms;
  1341     val pt = update_metID pt p mID*)
  1342     val (pos,_,_,pt)= 
  1343 	generate1 thy (Specify_Method' (mID, oris, itms)) Uistate pos pt
  1344     (*val _=writeln("@@@ specify (Specify_Method) before nxt_spec")*)
  1345     val (_,nxt) = nxt_spec Met (*ok*)true oris (dI',pI',mI') (pbl, itms) 
  1346 		((#ppc o get_pbt) pI'',ppc) (dI'',pI'',mID);
  1347   in (pos, (pos,Uistate),
  1348       Form' (PpcKF (0,EdUndef,(length p),Nundef,
  1349 		    (Method mID, itms2itemppc (assoc_thy dI'') itms pre'))),
  1350       nxt, Safe, pt) end    
  1351 (* val Add_Find' ct = nxt; val sel = "#Find"; 
  1352    *)
  1353   | specify (Add_Given' ct) p c pt = specify_additem "#Given" ct p c pt
  1354   | specify (Add_Find'  ct) p c pt = specify_additem "#Find"  ct p c pt
  1355   | specify (Add_Relation' ct) p c pt=specify_additem"#Relate"ct p c pt
  1356 (* val Specify_Theory' domID = m;
  1357    val (Specify_Theory' domID, (p,p_)) = (m, pos);
  1358    *)
  1359   | specify (Specify_Theory' domID) (pos as (p,p_)) c pt =
  1360     let val p_ = case p_ of Met => Met | _ => Pbl
  1361       val thy = assoc_thy domID;
  1362       val (PblObj{origin=(oris,(dI',pI',mI'),_), meth=met,
  1363 		  probl=pbl, spec=(dI,pI,mI),...}) = get_obj I pt p;
  1364       val mppc = case p_ of Met => met | _ => pbl;
  1365       val cpI = if pI = e_pblID then pI' else pI;
  1366       val {prls=per,ppc,where_=pwh,...} = get_pbt cpI
  1367       val cmI = if mI = e_metID then mI' else mI;
  1368       val {prls=mer,ppc=mpc,pre=mwh,...} = get_met cmI
  1369       val pre = 
  1370 	  case p_ of
  1371 	      Met => (check_preconds thy mer mwh met)
  1372 	    | _ => (check_preconds thy per pwh pbl)
  1373       val pb = foldl and_ (true, map fst pre)
  1374     in if domID = dI
  1375        then let 
  1376 	 (*val _=writeln("@@@ specify (Specify_Theory) THEN before nxt_spec")*)
  1377            val (p_,nxt) = nxt_spec p_ pb oris (dI',pI',mI') 
  1378 				   (pbl,met) (ppc,mpc) (dI,pI,mI);
  1379 	      in ((p,p_), (pos,Uistate), 
  1380 		  Form'(PpcKF (0,EdUndef,(length p), Nundef,
  1381 			       (header p_ pI cmI, itms2itemppc thy mppc pre))),
  1382 		  nxt,Safe,pt) end
  1383        else (*FIXME: check ppc wrt. (new!) domID ..? still parsable?*)
  1384 	 let 
  1385 	   (*val pt = update_domID pt p domID;11.8.03*)
  1386 	   val ((p,p_),_,_,pt) = generate1 thy (Specify_Theory' domID) 
  1387 					   Uistate (p,p_) pt
  1388 	 (*val _=writeln("@@@ specify (Specify_Theory) ELSE before nxt_spec")*)
  1389 	   val (p_,nxt) = nxt_spec p_ pb oris (dI',pI',mI') (pbl,met) 
  1390 				   (ppc,mpc) (domID,pI,mI);
  1391 	 in ((p,p_), (pos,Uistate), 
  1392 	     Form' (PpcKF (0, EdUndef, (length p),Nundef,
  1393 			   (header p_ pI cmI, itms2itemppc thy mppc pre))),
  1394 	     nxt, Safe,pt) end
  1395     end
  1396 (* itms2itemppc thy [](*mpc*) pre
  1397    *)
  1398   | specify m' _ _ _ = 
  1399     raise error ("specify: not impl. for "^tac_2str m');
  1400 
  1401 (* val (sel, Add_Given ct, ptp as (pt,(p,Pbl))) = ("#Given", tac, ptp);
  1402    val (sel, Add_Find  ct, ptp as (pt,(p,Pbl))) = ("#Find", tac, ptp);
  1403    *)
  1404 fun nxt_specif_additem sel ct (ptp as (pt,(p,Pbl))) = 
  1405     let
  1406       val (PblObj{meth=met,origin=(oris,(dI',pI',_),_),
  1407 		  probl=pbl,spec=(dI,pI,_),...}) = get_obj I pt p;
  1408       val thy = if dI = e_domID then assoc_thy dI' else assoc_thy dI;
  1409       val cpI = if pI = e_pblID then pI' else pI;
  1410     in case appl_add thy sel oris pbl ((#ppc o get_pbt) cpI) ct of
  1411 	   Add itm (*..union old input *) =>
  1412 (* val Add itm = appl_add thy sel oris pbl ppc ct;
  1413    *)
  1414 	   let
  1415 	       (*val _=writeln("###nxt_specif_additem: itm= "^(itm2str_ itm));*)
  1416 	       val pbl' = insert_ppc thy itm pbl
  1417 	       val (tac,tac_) = 
  1418 		   case sel of
  1419 		       "#Given" => (Add_Given    ct, Add_Given'   (ct, pbl'))
  1420 		     | "#Find"  => (Add_Find     ct, Add_Find'    (ct, pbl'))
  1421 		     | "#Relate"=> (Add_Relation ct, Add_Relation'(ct, pbl'))
  1422 	       val ((p,Pbl),c,_,pt') = 
  1423 		   generate1 thy tac_ Uistate (p,Pbl) pt
  1424 	   in ([(tac,tac_,((p,Pbl),Uistate))], c, (pt',(p,Pbl))):calcstate' end
  1425 	       
  1426 	 | Err msg => 
  1427 	   (*TODO.WN03 pass error-msgs to the frontend..
  1428              FIXME ..and dont abuse a tactic for that purpose*)
  1429 	   ([(Tac msg,
  1430 	      Tac_ (theory "Pure", msg,msg,msg),
  1431 	      (e_pos', e_istate))], [], ptp) 
  1432     end
  1433 
  1434 (* val sel = "#Find"; val (p,_) = p; val Add_Find' ct = nxt;
  1435    val (_,_,f,nxt',_,pt')= nxt_specif_additem sel ct (p,Met) c pt;
  1436   *)
  1437   | nxt_specif_additem sel ct (ptp as (pt,(p,Met))) = 
  1438     let
  1439       val (PblObj{meth=met,origin=(oris,(dI',pI',mI'),_),
  1440 		  probl=pbl,spec=(dI,pI,mI),...}) = get_obj I pt p;
  1441       val thy = if dI = e_domID then assoc_thy dI' else assoc_thy dI;
  1442       val cmI = if mI = e_metID then mI' else mI;
  1443     in case appl_add thy sel oris met ((#ppc o get_met) cmI) ct of
  1444       Add itm (*..union old input *) =>
  1445 	let (* val Add itm = appl_add thy sel oris met (#ppc (get_met cmI)) ct;
  1446                *)
  1447 	  val met' = insert_ppc thy itm met;
  1448 	  val (tac,tac_) = 
  1449 	      case sel of
  1450 		  "#Given" => (Add_Given    ct, Add_Given'   (ct, met'))
  1451 		| "#Find"  => (Add_Find     ct, Add_Find'    (ct, met'))
  1452 		| "#Relate"=> (Add_Relation ct, Add_Relation'(ct, met'))
  1453 	  val ((p,Met),c,_,pt') = 
  1454 	      generate1 thy tac_ Uistate (p,Met) pt
  1455 	in ([(tac,tac_,((p,Met), Uistate))], c, (pt',(p,Met))) end
  1456 
  1457     | Err msg => ([(*tacis*)], [], ptp) 
  1458     (*nxt_me collects tacis until not hide; here just no progress*)
  1459     end;
  1460 
  1461 (* ori
  1462 val (msg,itm) = appl_add thy sel oris ppc ct;
  1463 val (Cor(d,ts)) = #5 itm;
  1464 map (atomty) ts;
  1465 
  1466 pre
  1467 *)
  1468 fun ori2Coritm pbt ((i,v,f,d,ts):ori) =
  1469     (i,v,true,f, Cor ((d,ts),(((snd o snd o the o (find_first (eq1 d))) pbt) 
  1470 			      handle _ => raise error ("ori2Coritm: dsc "^
  1471 						term2str d^
  1472 						"in ori, but not in pbt")
  1473 			      ,ts))):itm;
  1474 fun ori2Coritm (pbt:pat list) ((i,v,f,d,ts):ori) =
  1475     ((i,v,true,f, Cor ((d,ts),((snd o snd o the o 
  1476 			       (find_first (eq1 d))) pbt,ts))):itm)
  1477     handle _ => (*dsc in oris, but not in pbl pat list: keep this dsc*)
  1478     ((i,v,true,f, Cor ((d,ts),(d,ts))):itm);
  1479 
  1480 
  1481 (*filter out oris which have same description in itms*)
  1482 fun filter_outs oris [] = oris
  1483   | filter_outs oris (i::itms) = 
  1484     let val ors = filter_out ((curry op= ((d_in o #5) (i:itm))) o 
  1485 			      (#4:ori -> term)) oris;
  1486     in filter_outs ors itms end;
  1487 
  1488 fun memI a b = member op = a b;
  1489 (*filter oris which are in pbt, too*)
  1490 fun filter_pbt oris pbt =
  1491     let val dscs = map (fst o snd) pbt
  1492     in filter ((memI dscs) o (#4: ori -> term)) oris end;
  1493 
  1494 (*.combine itms from pbl + met and complete them wrt. pbt.*)
  1495 (*FIXXXME.WN031205 complete_metitms doesnt handle incorrect itms !*)
  1496 local infix mem;
  1497 fun x mem [] = false
  1498   | x mem (y :: ys) = x = y orelse x mem ys;
  1499 in 
  1500 fun complete_metitms (oris:ori list) (pits:itm list) (mits:itm list) met = 
  1501 (* val met = (#ppc o get_met) ["DiffApp","max_by_calculus"];
  1502    *)
  1503     let val vat = max_vt pits;
  1504         val itms = pits @ 
  1505 		   (filter ((curry (op mem) vat) o (#2:itm -> int list)) mits);
  1506 	val ors = filter ((curry (op mem) vat) o (#2:ori -> int list)) oris;
  1507         val os = filter_outs ors itms;
  1508     (*WN.12.03?: does _NOT_ add itms from met ?!*)
  1509     in itms @ (map (ori2Coritm met) os) end
  1510 end;
  1511 
  1512 
  1513 
  1514 (*.complete model and guard of a calc-head .*)
  1515 local infix mem;
  1516 fun x mem [] = false
  1517   | x mem (y :: ys) = x = y orelse x mem ys;
  1518 in 
  1519 fun complete_mod_ (oris, mpc, ppc, probl) =
  1520     let	val pits = filter_out ((curry op= false) o (#3: itm -> bool)) probl
  1521 	val vat = if probl = [] then 1 else max_vt probl
  1522 	val pors = filter ((curry (op mem) vat) o (#2:ori -> int list)) oris
  1523 	val pors = filter_outs pors pits (*which are in pbl already*)
  1524         val pors = (filter_pbt pors ppc) (*which are in pbt, too*)
  1525 
  1526 	val pits = pits @ (map (ori2Coritm ppc) pors)
  1527 	val mits = complete_metitms oris pits [] mpc
  1528     in (pits, mits) end
  1529 end;
  1530 
  1531 fun some_spec ((odI, opI, omI):spec) ((dI, pI, mI):spec) =
  1532     (if dI = e_domID then odI else dI,
  1533      if pI = e_pblID then opI else pI,
  1534      if mI = e_metID then omI else mI):spec;
  1535 
  1536 
  1537 (*.find a next applicable tac (for calcstate) and update ptree
  1538  (for ev. finding several more tacs due to hide).*)
  1539 (*FIXXXME: unify ... fun nxt_specif = nxt_spec + applicable_in + specify !!*)
  1540 (*WN.24.10.03        ~~~~~~~~~~~~~~   -> tac     -> tac_      -> -"- as arg*)
  1541 (*WN.24.10.03        fun nxt_solv   = ...................................??*)
  1542 fun nxt_specif (tac as Model_Problem) (pt, pos as (p,p_)) =
  1543   let
  1544     val (PblObj{origin=(oris,ospec,_),probl,spec,...}) = get_obj I pt p
  1545     val (dI,pI,mI) = some_spec ospec spec
  1546     val thy = assoc_thy dI
  1547     val mpc = (#ppc o get_met) mI (*just for reuse complete_mod_*)
  1548     val {cas,ppc,...} = get_pbt pI
  1549     val pbl = init_pbl ppc (*fill in descriptions*)
  1550     (*--------------if you think, this should be done by the Dialog 
  1551      in the java front-end, search there for WN060225-modelProblem----*)
  1552     val (pbl,met) = case cas of NONE => (pbl,[])
  1553 			    | _ => complete_mod_ (oris, mpc, ppc, probl)
  1554     (*----------------------------------------------------------------*)
  1555     val tac_ = Model_Problem' (pI, pbl, met)
  1556     val (pos,c,_,pt) = generate1 thy tac_ Uistate pos pt
  1557   in ([(tac,tac_, (pos, Uistate))], c, (pt,pos)):calcstate' end
  1558 
  1559 (* val Add_Find ct = tac;
  1560    *)
  1561   | nxt_specif (Add_Given ct) ptp = nxt_specif_additem "#Given" ct ptp
  1562   | nxt_specif (Add_Find  ct) ptp = nxt_specif_additem "#Find"  ct ptp
  1563   | nxt_specif (Add_Relation ct) ptp = nxt_specif_additem"#Relate" ct ptp
  1564 
  1565 (*. called only if no_met is specified .*)     
  1566   | nxt_specif (Refine_Tacitly pI) (ptp as (pt, pos as (p,_))) =
  1567     let val (PblObj {origin = (oris, (dI,_,_),_), ...}) = get_obj I pt p
  1568 	val opt = refine_ori oris pI
  1569     in case opt of
  1570 	   SOME pI' => 
  1571 	   let val {met,ppc,...} = get_pbt pI'
  1572 	       val pbl = init_pbl ppc
  1573 	       (*val pt = update_pbl pt p pbl ..done by Model_Problem*)
  1574 	       val mI = if length met = 0 then e_metID else hd met
  1575                val thy = assoc_thy dI
  1576 	       val (pos,c,_,pt) = 
  1577 		   generate1 thy (Refine_Tacitly' (pI,pI',dI,mI,(*pbl*)[])) 
  1578 			     Uistate pos pt
  1579 	   in ([(Refine_Tacitly pI, Refine_Tacitly' (pI,pI',dI,mI,(*pbl*)[]),
  1580 		 (pos, Uistate))], c, (pt,pos)) end
  1581 	 | NONE => ([], [], ptp)
  1582     end
  1583 
  1584   | nxt_specif (Refine_Problem pI) (ptp as (pt, pos as (p,_))) =
  1585     let val (PblObj {origin=(_,(dI,_,_),_),spec=(dI',_,_),
  1586 		     probl, ...}) = get_obj I pt p
  1587 	val thy = if dI' = e_domID then dI else dI'
  1588     in case refine_pbl (assoc_thy thy) pI probl of
  1589 	   NONE => ([], [], ptp)
  1590 	 | SOME (rfd as (pI',_)) => 
  1591 	   let val (pos,c,_,pt) = 
  1592 		   generate1 (assoc_thy thy) 
  1593 			     (Refine_Problem' rfd) Uistate pos pt
  1594 	    in ([(Refine_Problem pI, Refine_Problem' rfd,
  1595 			    (pos, Uistate))], c, (pt,pos)) end
  1596     end
  1597 
  1598   | nxt_specif (Specify_Problem pI) (pt, pos as (p,_)) =
  1599     let val (PblObj {origin=(oris,(dI,_,_),_),spec=(dI',pI',_),
  1600 		     probl, ...}) = get_obj I pt p;
  1601 	val thy = assoc_thy (if dI' = e_domID then dI else dI');
  1602         val {ppc,where_,prls,...} = get_pbt pI
  1603 	val pbl as (_,(itms,_)) = 
  1604 	    if pI'=e_pblID andalso pI=e_pblID
  1605 	    then (false, (init_pbl ppc, []))
  1606 	    else match_itms_oris thy probl (ppc,where_,prls) oris(*FIXXXXXME?*)
  1607 	(*FIXXXME~~~~~~~~~~~~~~~: take pbl and compare with new pI WN.8.03*)
  1608 	val ((p,Pbl),c,_,pt)= 
  1609 	    generate1 thy (Specify_Problem' (pI, pbl)) Uistate pos pt
  1610     in ([(Specify_Problem pI, Specify_Problem' (pI, pbl),
  1611 		    (pos,Uistate))], c, (pt,pos)) end
  1612 
  1613   (*transfers oris (not required in pbl) to met-model for script-env
  1614     FIXME.WN.8.03: application of several mIDs to SAME model?*)
  1615   | nxt_specif (Specify_Method mID) (ptp as (pt, pos as (p,_))) = 
  1616   let val (PblObj {origin=(oris,(dI',pI',mI'),_), probl=pbl, spec=(dI,pI,mI), 
  1617 		   meth=met, ...}) = get_obj I pt p;
  1618     val {ppc,pre,prls,...} = get_met mID
  1619     val thy = assoc_thy dI
  1620     val oris = add_field' thy ppc oris;
  1621     val dI'' = if dI=e_domID then dI' else dI;
  1622     val pI'' = if pI = e_pblID then pI' else pI;
  1623     val met = if met=[] then pbl else met;(*WN0602 what if more itms in met?*)
  1624     val (ok, (itms, pre')) = match_itms_oris thy met (ppc,pre,prls ) oris;
  1625     val (pos,c,_,pt)= 
  1626 	generate1 thy (Specify_Method' (mID, oris, itms)) Uistate pos pt
  1627   in ([(Specify_Method mID, Specify_Method' (mID, oris, itms),
  1628 		  (pos,Uistate))], c, (pt,pos)) end    
  1629 
  1630   | nxt_specif (Specify_Theory dI) (pt, pos as (p,Pbl)) =
  1631     let val (dI',_,_) = get_obj g_spec pt p
  1632 	val (pos,c,_,pt) = 
  1633 	    generate1 (assoc_thy "Isac.thy") (Specify_Theory' dI) 
  1634 		      Uistate pos pt
  1635     in  (*FIXXXME: check if pbl can still be parsed*)
  1636 	([(Specify_Theory dI, Specify_Theory' dI, (pos,Uistate))], c,
  1637 	 (pt, pos)) end
  1638 
  1639   | nxt_specif (Specify_Theory dI) (pt, pos as (p,Met)) =
  1640     let val (dI',_,_) = get_obj g_spec pt p
  1641 	val (pos,c,_,pt) = 
  1642 	    generate1 (assoc_thy "Isac.thy") (Specify_Theory' dI) 
  1643 		      Uistate pos pt
  1644     in  (*FIXXXME: check if met can still be parsed*)
  1645 	([(Specify_Theory dI, Specify_Theory' dI, (pos,Uistate))], c,
  1646 	 (pt, pos)) end
  1647 
  1648   | nxt_specif m' _ = 
  1649     raise error ("nxt_specif: not impl. for "^tac2str m');
  1650 
  1651 (*.get the values from oris; handle the term list w.r.t. penv.*)
  1652 
  1653 local infix mem;
  1654 fun x mem [] = false
  1655   | x mem (y :: ys) = x = y orelse x mem ys;
  1656 in 
  1657 fun vals_of_oris oris =
  1658     ((map (mkval' o (#5:ori -> term list))) o 
  1659      (filter ((curry (op mem) 1) o (#2:ori -> int list)))) oris
  1660 end;
  1661 
  1662 
  1663 
  1664 (*.create a calc-tree with oris via an cas.refined pbl.*)
  1665 fun nxt_specify_init_calc (([],(dI,pI,mI)): fmz) =
  1666 (* val ([],(dI,pI,mI)) = (fmz, sp);
  1667    *)
  1668     if pI <> [] then (*comes from pbl-browser*)
  1669 	let val {cas,met,ppc,thy,...} = get_pbt pI
  1670 	    val dI = if dI = "" then theory2theory' thy else dI
  1671 	    val thy = assoc_thy dI
  1672 	    val mI = if mI = [] then hd met else mI
  1673 	    val hdl = case cas of NONE => pblterm dI pI | SOME t => t
  1674 	    val (pt,_) = cappend_problem e_ptree [] e_istate ([], (dI,pI,mI))
  1675 					 ([], (dI,pI,mI), hdl)
  1676 	    val pt = update_spec pt [] (dI,pI,mI)
  1677 	    val pits = init_pbl' ppc
  1678 	    val pt = update_pbl pt [] pits
  1679 	in ((pt,([],Pbl)), []): calcstate end
  1680     else if mI <> [] then (*comes from met-browser*)
  1681 	let val {ppc,...} = get_met mI
  1682 	    val dI = if dI = "" then "Isac.thy" else dI
  1683 	    val thy = assoc_thy dI
  1684 	    val (pt,_) = cappend_problem e_ptree [] e_istate ([], (dI,pI,mI))
  1685 					 ([], (dI,pI,mI), e_term(*FIXME met*))
  1686 	    val pt = update_spec pt [] (dI,pI,mI)
  1687 	    val mits = init_pbl' ppc
  1688 	    val pt = update_met pt [] mits
  1689 	in ((pt,([],Met)), []) end
  1690     else (*completely new example*)
  1691 	let val (pt,_) = cappend_problem e_ptree [] e_istate ([], e_spec)
  1692 					 ([], e_spec, e_term)
  1693 	in ((pt,([],Pbl)), []) end
  1694 (* val (fmz, (dI,pI,mI)) = (fmz, sp);
  1695    *)
  1696   | nxt_specify_init_calc (fmz:fmz_,(dI,pI,mI):spec) = 
  1697     let            (* either """"""""""""""" all empty or complete *)
  1698 	val thy = assoc_thy dI
  1699 	val (pI, pors, mI) = 
  1700 	    if mI = ["no_met"] 
  1701 	    then let val pors = prep_ori fmz thy ((#ppc o get_pbt) pI)
  1702 		     val pI' = refine_ori' pors pI;
  1703 		 in (pI', pors (*refinement over models with diff.prec only*), 
  1704 		     (hd o #met o get_pbt) pI') end
  1705 	    else (pI, prep_ori fmz thy ((#ppc o get_pbt) pI), mI)
  1706 	val {cas,ppc,thy=thy',...} = get_pbt pI (*take dI from _refined_ pbl*)
  1707 	val dI = theory2theory' (maxthy thy thy');
  1708 	val hdl = case cas of
  1709 		      NONE => pblterm dI pI
  1710 		    | SOME t => subst_atomic ((vars_of_pbl_' ppc) 
  1711 						  ~~~ vals_of_oris pors) t
  1712     val (pt,_) = cappend_problem e_ptree [] e_istate (fmz,(dI,pI,mI))
  1713 				 (pors,(dI,pI,mI),hdl)
  1714     (*val pbl = init_pbl ppc  WN.9.03: done by Model/Refine_Problem
  1715     val pt = update_pbl pt [] pbl*)
  1716   in ((pt,([],Pbl)), fst3 (nxt_specif Model_Problem (pt, ([],Pbl))))
  1717   end;
  1718 
  1719 
  1720 
  1721 (*18.12.99*)
  1722 fun get_spec_form (m:tac_) ((p,p_):pos') (pt:ptree) = 
  1723 (*  case appl_spec p pt m of           /// 19.1.00
  1724     Notappl e => Error' (Error_ e)
  1725   | Appl => 
  1726 *)    let val (_,_,f,_,_,_) = specify m (p,p_) [] pt
  1727       in f end;
  1728 
  1729 
  1730 (*fun tag_form thy (formal, given) = cterm_of thy
  1731 	      (((head_of o term_of) given) $ (term_of formal)); WN100819*)
  1732 fun tag_form thy (formal, given) =
  1733     (let val gf = (head_of given) $ formal;
  1734          val _ = cterm_of thy gf
  1735      in gf end)
  1736     handle _ => raise error ("calchead.tag_form: " ^ 
  1737                              Syntax.string_of_term (thy2ctxt thy) given ^
  1738                              " .. " ^
  1739                              Syntax.string_of_term (thy2ctxt thy) formal ^
  1740                          " ..types do not match");
  1741 (* val formal = (the o (parse thy)) "[R::real]";
  1742 > val given = (the o (parse thy)) "fixed_values (cs::real list)";
  1743 > tag_form thy (formal, given);
  1744 val it = "fixed_values [R]" : cterm
  1745 *)
  1746 fun chktyp thy (n, fs, gs) = 
  1747   ((writeln o (Syntax.string_of_term (thy2ctxt thy)) o (nth n)) fs;
  1748    (writeln o (Syntax.string_of_term (thy2ctxt thy)) o (nth n)) gs;
  1749    tag_form thy (nth n fs, nth n gs));
  1750 
  1751 fun chktyps thy (fs, gs) = map (tag_form thy) (fs ~~ gs);
  1752 
  1753 (* #####################################################
  1754    find the failing item:
  1755 > val n = 2;
  1756 > val tag__form = chktyp (n,formals,givens);
  1757 > (type_of o term_of o (nth n)) formals; 
  1758 > (type_of o term_of o (nth n)) givens;
  1759 > atomty ((term_of o (nth n)) formals);
  1760 > atomty ((term_of o (nth n)) givens);
  1761 > atomty (term_of tag__form);
  1762 > use_thy"isa-98-1-HOL-plus/knowl-base/DiffAppl";
  1763  ##################################################### *)
  1764 
  1765 (* #####################################################
  1766    testdata setup
  1767 val origin = ["sqrt(9+4*x)=sqrt x + sqrt(5+x)","x::rat","(+0)"];
  1768 val formals = map (the o (parse thy)) origin;
  1769 
  1770 val given  = ["equation (lhs=rhs)",
  1771 	     "bound_variable bdv",   (* TODO type *) 
  1772 	     "error_bound apx"];
  1773 val where_ = ["e is_root_equation_in bdv",
  1774 	      "bdv is_var",
  1775 	      "apx is_const_expr"];
  1776 val find   = ["L::rat set"];
  1777 val with_  = ["L = {bdv. || ((%x. lhs) bdv) - ((%x. rhs) bdv) || < apx}"];
  1778 val chkpbl = map (the o (parse thy)) (given @ where_ @ find @ with_);
  1779 val givens = map (the o (parse thy)) given;
  1780 
  1781 val tag__forms = chktyps (formals, givens);
  1782 map ((atomty) o term_of) tag__forms;
  1783  ##################################################### *)
  1784 
  1785 
  1786 (* check pbltypes, announces one failure a time *)
  1787 (*fun chk_vars ctppc = 
  1788   let val {Given=gi,Where=wh,Find=fi,With=wi,Relate=re} = 
  1789     appc flat (mappc (vars o term_of) ctppc)
  1790   in if (wh\\gi) <> [] then ("wh\\gi",wh\\gi)
  1791      else if (re\\(gi union fi)) <> [] 
  1792 	    then ("re\\(gi union fi)",re\\(gi union fi))
  1793 	  else ("ok",[]) end;*)
  1794 fun chk_vars ctppc = 
  1795   let val {Given=gi,Where=wh,Find=fi,With=wi,Relate=re} = 
  1796           appc flat (mappc vars ctppc)
  1797       val chked = subtract op = gi wh
  1798   in if chked <> [] then ("wh\\gi", chked)
  1799      else let val chked = subtract op = (union op = gi fi) re
  1800           in if chked  <> []
  1801 	     then ("re\\(gi union fi)", chked)
  1802 	     else ("ok", []) 
  1803           end
  1804   end;
  1805 
  1806 (* check a new pbltype: variables (Free) unbound by given, find*) 
  1807 fun unbound_ppc ctppc =
  1808   let val {Given=gi,Find=fi,Relate=re,...} = 
  1809     appc flat (mappc vars ctppc)
  1810   in distinct (*re\\(gi union fi)*) 
  1811               (subtract op = (union op = gi fi) re) end;
  1812 (*
  1813 > val org = {Given=["[R=(R::real)]"],Where=[],
  1814 	   Find=["[A::real]"],With=[],
  1815 	   Relate=["[A=#2*a*b - a^^^#2, (a//#2)^^^#2 + (b//#2)^^^#2 = R^^^#2]"]
  1816 	   }:string ppc;
  1817 > val ctppc = mappc (the o (parse thy)) org;
  1818 > unbound_ppc ctppc;
  1819 val it = [("a","RealDef.real"),("b","RealDef.real")] : (string * typ) list
  1820 *)
  1821 
  1822 
  1823 (* f, a binary operator, is nested rightassociative *)
  1824 fun foldr1 f xs =
  1825   let
  1826     fun fld f (x::[]) = x
  1827       | fld f (x::x'::[]) = f (x',x)
  1828       | fld f (x::x'::xs) = f (fld f (x'::xs),x);
  1829   in ((fld f) o rev) xs end;
  1830 (*
  1831 > val (SOME ct) = parse thy "[a=b,c=d,e=f]";
  1832 > val ces = map (cterm_of thy) (isalist2list (term_of ct));
  1833 > val conj = foldr1 HOLogic.mk_conj (isalist2list (term_of ct));
  1834 > cterm_of thy conj;
  1835 val it = "(a = b & c = d) & e = f" : cterm
  1836 *)
  1837 
  1838 (* f, a binary operator, is nested leftassociative *)
  1839 fun foldl1 f (x::[]) = x
  1840   | foldl1 f (x::x'::[]) = f (x,x')
  1841   | foldl1 f (x::x'::xs) = f (x,foldl1 f (x'::xs));
  1842 (*
  1843 > val (SOME ct) = parse thy "[a=b,c=d,e=f,g=h]";
  1844 > val ces = map (cterm_of thy) (isalist2list (term_of ct));
  1845 > val conj = foldl1 HOLogic.mk_conj (isalist2list (term_of ct));
  1846 > cterm_of thy conj;
  1847 val it = "a = b & c = d & e = f & g = h" : cterm
  1848 *)
  1849 
  1850 
  1851 (* called only once, if a Subproblem has been located in the script*)
  1852 fun nxt_model_pbl (Subproblem'((_,pblID,metID),_,_,_,_)) ptp =
  1853 (* val (Subproblem'((_,pblID,metID),_,_,_,_),ptp) = (m', (pt,(p,p_)));
  1854    *)
  1855     (case metID of
  1856 	 ["no_met"] => 
  1857 	 (snd3 o hd o fst3) (nxt_specif (Refine_Tacitly pblID) ptp)
  1858        | _ => (snd3 o hd o fst3) (nxt_specif Model_Problem ptp))
  1859   (*all stored in tac_ itms     ^^^^^^^^^^*)
  1860   | nxt_model_pbl tac_ _ = 
  1861     raise error ("nxt_model_pbl: called by tac= "^tac_2str tac_);
  1862 (* run subp_rooteq.sml ''
  1863    until nxt=("Subproblem",Subproblem ("SqRoot.thy",["univariate","equation"]))
  1864 > val (_, (Subproblem'((_,pblID,metID),_,_,_,_),_,_,_,_,_)) =
  1865       (last_elem o drop_last) ets'';
  1866 > val mst = (last_elem o drop_last) ets'';
  1867 > nxt_model_pbl mst;
  1868 val it = Refine_Tacitly ["univariate","equation"] : tac
  1869 *)
  1870 
  1871 (*fun eq1 d (_,(d',_)) = (d = d'); ---modspec.sml*)
  1872 fun eq4 v (_,vts,_,_,_) = member op = vts v;
  1873 fun eq5 (_,_,_,_,itm_) (_,_,_,d,_) = d_in itm_ = d;
  1874 
  1875  
  1876 
  1877 (*
  1878   writeln (oris2str pors);
  1879 
  1880   writeln (itms2str_ thy pits);
  1881   writeln (itms2str_ thy mits);
  1882    *)
  1883 
  1884 
  1885 (*.complete _NON_empty calc-head for autocalc (sub-)pbl from oris
  1886   + met from fmz; assumes pos on PblObj, meth = [].*)
  1887 fun complete_mod (pt, pos as (p, p_):pos') =
  1888 (* val (pt, (p, _)) = (pt, p);
  1889    val (pt, (p, _)) = (pt, pos);
  1890    *)
  1891     let val _= if p_ <> Pbl 
  1892 	       then writeln("###complete_mod: only impl.for Pbl, called with "^
  1893 			    pos'2str pos) else ()
  1894 	val (PblObj{origin=(oris, ospec, hdl), probl, spec,...}) =
  1895 	    get_obj I pt p
  1896 	val (dI,pI,mI) = some_spec ospec spec
  1897 	val mpc = (#ppc o get_met) mI
  1898 	val ppc = (#ppc o get_pbt) pI
  1899 	val (pits, mits) = complete_mod_ (oris, mpc, ppc, probl)
  1900         val pt = update_pblppc pt p pits
  1901 	val pt = update_metppc pt p mits
  1902     in (pt, (p,Met):pos') end
  1903 ;
  1904 (*| complete_mod (pt, pos as (p, Met):pos') =
  1905     raise error ("###complete_mod: only impl.for Pbl, called with "^
  1906 		 pos'2str pos);*)
  1907 
  1908 (*.complete _EMPTY_ calc-head for autocalc (sub-)pbl from oris(+met from fmz);
  1909    oris and spec (incl. pbl-refinement) given from init_calc or SubProblem .*)
  1910 fun all_modspec (pt, (p,_):pos') =
  1911 (* val (pt, (p,_)) = ptp;
  1912    *)
  1913     let val (PblObj{fmz=(fmz_,_), origin=(pors, spec as (dI,pI,mI), hdl),
  1914 		    ...}) = get_obj I pt p;
  1915 	val thy = assoc_thy dI;
  1916 	val {ppc,...} = get_met mI;
  1917 	val mors = prep_ori fmz_ thy ppc;
  1918         val pt = update_pblppc pt p (map (ori2Coritm ppc) pors);
  1919 	val pt = update_metppc pt p (map (ori2Coritm ppc) mors);
  1920 	val pt = update_spec pt p (dI,pI,mI);
  1921     in (pt, (p,Met): pos') end;
  1922 
  1923 (*WN.12.03: use in nxt_spec, too ? what about variants ???*)
  1924 fun is_complete_mod_ ([]: itm list) = false
  1925   | is_complete_mod_ itms = 
  1926     foldl and_ (true, (map #3 itms));
  1927 fun is_complete_mod (pt, pos as (p, Pbl): pos') =
  1928     if (is_pblobj o (get_obj I pt)) p 
  1929     then (is_complete_mod_ o (get_obj g_pbl pt)) p
  1930     else raise error ("is_complete_mod: called by PrfObj at "^pos'2str pos)
  1931   | is_complete_mod (pt, pos as (p, Met)) = 
  1932     if (is_pblobj o (get_obj I pt)) p 
  1933     then (is_complete_mod_ o (get_obj g_met pt)) p
  1934     else raise error ("is_complete_mod: called by PrfObj at "^pos'2str pos)
  1935   | is_complete_mod (_, pos) =
  1936     raise error ("is_complete_mod called by "^pos'2str pos^
  1937 		 " (should be Pbl or Met)");
  1938 
  1939 (*.have (thy, pbl, met) _all_ been specified explicitly ?.*)
  1940 fun is_complete_spec (pt, pos as (p,_): pos') = 
  1941     if (not o is_pblobj o (get_obj I pt)) p 
  1942     then raise error ("is_complete_spec: called by PrfObj at "^pos'2str pos)
  1943     else let val (dI,pI,mI) = get_obj g_spec pt p
  1944 	 in dI<>e_domID andalso pI<>e_pblID andalso mI<>e_metID end;
  1945 (*.complete empty items in specification from origin (pbl, met ev.refined);
  1946   assumes 'is_complete_mod'.*)
  1947 fun complete_spec (pt, pos as (p,_): pos') = 
  1948     let val PblObj {origin = (_,ospec,_), spec,...} = get_obj I pt p
  1949 	val pt = update_spec pt p (some_spec ospec spec)
  1950     in (pt, pos) end;
  1951 
  1952 fun is_complete_modspec ptp = 
  1953     is_complete_mod ptp andalso is_complete_spec ptp;
  1954 
  1955 
  1956 
  1957 
  1958 fun pt_model (PblObj {meth,spec,origin=(_,spec',hdl),...}) Met =
  1959 (* val ((PblObj {meth,spec,origin=(_,spec',hdl),...}), Met) = (ppobj, p_);
  1960    *)
  1961     let val (_,_,metID) = get_somespec' spec spec'
  1962 	val pre = 
  1963 	    if metID = e_metID then []
  1964 	    else let val {prls,pre=where_,...} = get_met metID
  1965 		     val pre = check_preconds' prls where_ meth 0
  1966 		 in pre end
  1967 	val allcorrect = is_complete_mod_ meth
  1968 			 andalso foldl and_ (true, (map #1 pre))
  1969     in ModSpec (allcorrect, Met, hdl, meth, pre, spec) end
  1970   | pt_model (PblObj {probl,spec,origin=(_,spec',hdl),...}) _(*Frm,Pbl*) =
  1971 (* val ((PblObj {probl,spec,origin=(_,spec',hdl),...}),_) = (ppobj, p_);
  1972    *)
  1973     let val (_,pI,_) = get_somespec' spec spec'
  1974 	val pre =
  1975 	    if pI = e_pblID then []
  1976 	    else let val {prls,where_,cas,...} = get_pbt pI
  1977 		     val pre = check_preconds' prls where_ probl 0
  1978 		 in pre end
  1979 	val allcorrect = is_complete_mod_ probl
  1980 			 andalso foldl and_ (true, (map #1 pre))
  1981     in ModSpec (allcorrect, Pbl, hdl, probl, pre, spec) end;
  1982 
  1983 
  1984 fun pt_form (PrfObj {form,...}) = Form form
  1985   | pt_form (PblObj {probl,spec,origin=(_,spec',_),...}) =
  1986     let val (dI, pI, _) = get_somespec' spec spec'
  1987 	val {cas,...} = get_pbt pI
  1988     in case cas of
  1989 	   NONE => Form (pblterm dI pI)
  1990 	 | SOME t => Form (subst_atomic (mk_env probl) t)
  1991     end;
  1992 (*vvv takes the tac _generating_ the formula=result, asm ok....
  1993 fun pt_result (PrfObj {result=(t,asm), tac,...}) = 
  1994     (Form t, 
  1995      if null asm then NONE else SOME asm, 
  1996      SOME tac)
  1997   | pt_result (PblObj {result=(t,asm), origin = (_,ospec,_), spec,...}) =
  1998     let val (_,_,metID) = some_spec ospec spec
  1999     in (Form t, 
  2000 	if null asm then NONE else SOME asm, 
  2001 	if metID = e_metID then NONE else SOME (Apply_Method metID)) end;
  2002 -------------------------------------------------------------------------*)
  2003 
  2004 
  2005 (*.pt_extract returns
  2006       # the formula at pos
  2007       # the tactic applied to this formula
  2008       # the list of assumptions generated at this formula
  2009 	(by application of another tac to the preceding formula !)
  2010    pos is assumed to come from the frontend, ie. generated by moveDown.*)
  2011 (*cannot be in ctree.sml, because ModSpec has to be calculated*)
  2012 fun pt_extract (pt,([],Res)) =
  2013 (* val (pt,([],Res)) = ptp;
  2014    *)
  2015     let val (f, asm) = get_obj g_result pt []
  2016     in (Form f, NONE, asm) end
  2017 (* val p = [3,2];
  2018    *)
  2019   | pt_extract (pt,(p,Res)) =
  2020 (* val (pt,(p,Res)) = ptp;
  2021    *)
  2022     let val (f, asm) = get_obj g_result pt p
  2023 	val tac = if last_onlev pt p
  2024 		  then if is_pblobj' pt (lev_up p)
  2025 		       then let val (PblObj{spec=(_,pI,_),...}) = 
  2026 				    get_obj I pt (lev_up p)
  2027 			    in if pI = e_pblID then NONE 
  2028 			       else SOME (Check_Postcond pI) end
  2029 		       else SOME End_Trans (*WN0502 TODO for other branches*)
  2030 		  else let val p' = lev_on p
  2031 		       in if is_pblobj' pt p'
  2032 			  then let val (PblObj{origin = (_,(dI,pI,_),_),...}) =
  2033 				       get_obj I pt p'
  2034 			       in SOME (Subproblem (dI, pI)) end
  2035 			  else if f = get_obj g_form pt p'
  2036 			  then SOME (get_obj g_tac pt p')
  2037 			  (*because this Frm          ~~~is not on worksheet*)
  2038 			  else SOME (Take (term2str (get_obj g_form pt p')))
  2039 		       end
  2040     in (Form f, tac, asm) end
  2041 	
  2042   | pt_extract (pt, pos as (p,p_(*Frm,Pbl*))) =
  2043 (* val (pt, pos as (p,p_(*Frm,Pbl*))) = ptp;
  2044    val (pt, pos as (p,p_(*Frm,Pbl*))) = (pt, p);
  2045    *)
  2046     let val ppobj = get_obj I pt p
  2047 	val f = if is_pblobj ppobj then pt_model ppobj p_
  2048 		else get_obj pt_form pt p
  2049 	val tac = g_tac ppobj
  2050     in (f, SOME tac, []) end;
  2051 
  2052 
  2053 (**. get the formula from a ctree-node:
  2054  take form+res from PblObj and 1.PrfObj and (PrfObj after PblObj)
  2055  take res from all other PrfObj's .**)
  2056 (*designed for interSteps, outcommented 04 in favour of calcChangedEvent*)
  2057 fun formres p (Nd (PblObj {origin = (_,_, h), result = (r, _),...}, _)) =
  2058     [("headline", (p, Frm), h), 
  2059      ("stepform", (p, Res), r)]
  2060   | formres p (Nd (PrfObj {form, result = (r, _),...}, _)) = 
  2061     [("stepform", (p, Frm), form), 
  2062      ("stepform", (p, Res), r)];
  2063 
  2064 fun form p (Nd (PrfObj {result = (r, _),...}, _)) = 
  2065     [("stepform", (p, Res), r)]
  2066 
  2067 (*assumes to take whole level, in particular hd -- for use in interSteps*)
  2068 fun get_formress fs p [] = flat fs
  2069   | get_formress fs p (nd::nds) =
  2070     (* start with   'form+res'       and continue with trying 'res' only*)
  2071     get_forms (fs @ [formres p nd]) (lev_on p) nds
  2072 and get_forms fs p [] = flat fs
  2073   | get_forms fs p (nd::nds) =
  2074     if is_pblnd nd
  2075     (* start again with      'form+res' ///ugly repeat with Check_elementwise
  2076     then get_formress (fs @ [formres p nd]) (lev_on p) nds                   *)
  2077     then get_forms    (fs @ [formres p nd]) (lev_on p) nds
  2078     (* continue with trying 'res' only*)
  2079     else get_forms    (fs @ [form    p nd]) (lev_on p) nds;
  2080 
  2081 (**.get an 'interval' 'from' 'to' of formulae from a ptree.**)
  2082 (*WN050219 made robust against _'to' below or after Complete nodes
  2083 	   by handling exn caused by move_dn*)
  2084 (*WN0401 this functionality belongs to ctree.sml, 
  2085 but fetching a calc_head requires calculations defined in modspec.sml
  2086 transfer to ME/me.sml !!!
  2087 WN051224 ^^^ doesnt hold any longer, since only the headline of a calc_head
  2088 is returned !!!!!!!!!!!!!
  2089 *)
  2090 fun eq_pos' (p1,Frm) (p2,Frm) = p1 = p2
  2091   | eq_pos' (p1,Res) (p2,Res) = p1 = p2
  2092   | eq_pos' (p1,Pbl) (p2,p2_) = p1 = p2 andalso (case p2_ of
  2093 						     Pbl => true
  2094 						   | Met => true
  2095 						   | _ => false)
  2096   | eq_pos' (p1,Met) (p2,p2_) = p1 = p2 andalso (case p2_ of
  2097 						     Pbl => true
  2098 						   | Met => true
  2099 						   | _ => false)
  2100   | eq_pos' _ _ = false;
  2101 
  2102 (*.get an 'interval' from the ctree; 'interval' is w.r.t. the 
  2103    total ordering Position#compareTo(Position p) in the java-code
  2104 val get_interval = fn
  2105     : pos' ->     : from is "move_up 1st-element" to return
  2106       pos' -> 	  : to the last element to be returned; from < to
  2107       int -> 	  : level: 0 gets the flattest sub-tree possible
  2108 			   >999 gets the deepest sub-tree possible
  2109       ptree -> 	  : 
  2110       (pos' * 	  : of the formula
  2111        Term.term) : the formula
  2112 	  list
  2113 .*)
  2114 fun get_interval from to level pt =
  2115 (* val (from,level) = (f,lev);
  2116    val (from, to, level) = (([3, 2, 1], Res), ([],Res), 9999);
  2117    *)
  2118     let fun get_inter c (from:pos') (to:pos') lev pt =
  2119 (* val (c, from, to, lev) = ([], from, to, level);
  2120    ------for recursion.......
  2121    val (c, from:pos', to:pos') = (c @ [(from, f)], move_dn [] pt from, to);
  2122    *)
  2123 	    if eq_pos' from to orelse from = ([],Res)
  2124 	    (*orelse ... avoids Exception- PTREE "end of calculation" raised,
  2125 	     if 'to' has values NOT generated by move_dn, see systest/me.sml
  2126              TODO.WN0501: introduce an order on pos' and check "from > to"..
  2127              ...there is an order in Java! 
  2128              WN051224 the hack got worse with returning term instead ptform*)
  2129 	    then let val (f,_,_) = pt_extract (pt, from)
  2130 		 in case f of
  2131 			ModSpec (_,_,headline,_,_,_) => c @ [(from, headline)] 
  2132 		      | Form t => c @ [(from, t)]
  2133 		 end
  2134 	    else 
  2135 		if lev < lev_of from
  2136 		then (get_inter c (move_dn [] pt from) to lev pt)
  2137 		     handle (PTREE _(*from move_dn too far*)) => c
  2138 		else let val (f,_,_) = pt_extract (pt, from)
  2139 			 val term = case f of
  2140 					ModSpec (_,_,headline,_,_,_)=> headline
  2141 				      | Form t => t
  2142 		     in (get_inter (c @ [(from, term)]) 
  2143 				   (move_dn [] pt from) to lev pt)
  2144 			handle (PTREE _(*from move_dn too far*)) 
  2145 			       => c @ [(from, term)] end
  2146     in get_inter [] from to level pt end;
  2147 
  2148 (*for tests*)
  2149 fun posform2str (pos:pos', form) =
  2150     "("^ pos'2str pos ^", "^
  2151     (case form of 
  2152 	 Form f => term2str f
  2153        | ModSpec c => term2str (#3 c(*the headline*)))
  2154     ^")";
  2155 fun posforms2str pfs = (strs2str' o (map (curry op ^ "\n")) o 
  2156 			(map posform2str)) pfs;
  2157 fun posterm2str (pos:pos', t) =
  2158     "("^ pos'2str pos ^", "^term2str t^")";
  2159 fun posterms2str pfs = (strs2str' o (map (curry op ^ "\n")) o 
  2160 			(map posterm2str)) pfs;
  2161 
  2162 
  2163 (*WN050225 omits the last step, if pt is incomplete*)
  2164 fun show_pt pt = 
  2165     writeln (posterms2str (get_interval ([],Frm) ([],Res) 99999 pt));
  2166 
  2167 (*.get a calchead from a PblObj-node in the ctree; 
  2168    preconditions must be calculated.*)
  2169 fun get_ocalhd (pt, pos' as (p,Pbl):pos') = 
  2170     let val PblObj {origin = (oris, ospec, hdf'), spec, probl,...} = 
  2171 	    get_obj I pt p
  2172 	val {prls,where_,...} = get_pbt (#2 (some_spec ospec spec))
  2173 	val pre = check_preconds (assoc_thy"Isac.thy") prls where_ probl
  2174     in (ocalhd_complete probl pre spec, Pbl, hdf', probl, pre, spec):ocalhd end
  2175 | get_ocalhd (pt, pos' as (p,Met):pos') = 
  2176     let val PblObj {fmz = fmz as (fmz_,_), origin = (oris, ospec, hdf'), 
  2177 		    spec, meth,...} = 
  2178 	    get_obj I pt p
  2179 	val {prls,pre,...} = get_met (#3 (some_spec ospec spec))
  2180 	val pre = check_preconds (assoc_thy"Isac.thy") prls pre meth
  2181     in (ocalhd_complete meth pre spec, Met, hdf', meth, pre, spec):ocalhd end;
  2182 
  2183 (*.at the activeFormula set the Model, the Guard and the Specification 
  2184    to empty and return a CalcHead;
  2185    the 'origin' remains (for reconstructing all that).*)
  2186 fun reset_calchead (pt, pos' as (p,_):pos') = 
  2187     let val PblObj {origin = (_, _, hdf'),...} = get_obj I pt p
  2188 	val pt = update_pbl pt p []
  2189 	val pt = update_met pt p []
  2190 	val pt = update_spec pt p e_spec
  2191     in (pt, (p,Pbl):pos') end;
  2192 
  2193 (*---------------------------------------------------------------------*)
  2194 end
  2195 
  2196 open CalcHead;
  2197 (*---------------------------------------------------------------------*)
  2198