src/Tools/isac/Specify/i-model.sml
author wneuper <Walther.Neuper@jku.at>
Thu, 30 Nov 2023 08:11:50 +0100
changeset 60769 0df0759fed26
parent 60767 466f0a5bfb73
child 60770 365758b39d90
permissions -rw-r--r--
some renamings
     1 (* Title:  Specify/i-model.sml
     2    Author: Walther Neuper 110226
     3    (c) due to copyright terms
     4 
     5 \<open>I_Model\<close> serves students' interactive modelling and gives feedback in the specify-phase.
     6 *)
     7 
     8 signature INTERACTION_MODEL =
     9 sig
    10 
    11   type T
    12   type T_TEST
    13   val OLD_to_TEST: T -> T_TEST
    14   val TEST_to_OLD: T_TEST -> T
    15   val empty: T
    16   val empty_TEST: T_TEST
    17 
    18   type single
    19   type single_TEST
    20   val empty_single: single
    21   val empty_single_TEST: single_TEST
    22   val is_empty_single_TEST: single_TEST -> bool
    23 
    24   type variant
    25   type variants
    26   type m_field
    27   type descriptor
    28   type values
    29 
    30   datatype feedback = datatype Model_Def.i_model_feedback
    31   datatype feedback_TEST = datatype Model_Def.i_model_feedback_TEST
    32   val feedback_empty_TEST: Model_Def.i_model_feedback_TEST
    33 
    34   type env
    35   type message
    36 
    37   val single_to_string: Proof.context -> single -> string
    38   val single_to_string_TEST: Proof.context -> single_TEST -> string
    39   val single_to_string_TEST': single_TEST -> string
    40   val to_string: Proof.context -> T -> string
    41   val to_string_TEST: Proof.context -> T_TEST -> string
    42 
    43   val feedback_OLD_to_TEST: feedback -> feedback_TEST
    44 
    45   datatype add_single = Add of single | Err of string
    46   val init: Model_Pattern.T -> T
    47   val init_TEST: Proof.context -> O_Model.T -> Model_Pattern.T -> T_TEST
    48   val check_single: Proof.context -> m_field -> O_Model.T -> T -> Model_Pattern.T ->
    49     TermC.as_string -> add_single
    50   val add_single: theory -> single -> T -> T
    51 
    52   val make_tactic: m_field -> TermC.as_string * T -> Tactic.T
    53 (*--*)
    54   val descriptor: feedback -> descriptor
    55 (*--*)
    56   val descriptor_TEST: feedback_TEST -> descriptor
    57   val values: feedback -> values option
    58   val o_model_values: feedback -> values
    59   val values_TEST': feedback_TEST -> values
    60   val descr_pairs_to_string: Proof.context -> (Model_Pattern.single * single_TEST) list -> string
    61   val variables: Model_Pattern.T -> Model_Def.i_model_TEST -> term list
    62   val is_notyet_input : Proof.context -> T -> O_Model.values -> O_Model.single -> Model_Pattern.T
    63     -> message * single
    64   val get_field_term: theory -> O_Model.single -> single -> m_field * TermC.as_string
    65 
    66   val fill_from_o: O_Model.T -> single_TEST -> single_TEST option
    67 
    68   val add_other: variant -> T_TEST -> single_TEST -> single_TEST
    69   val fill_method: O_Model.T -> T_TEST * T_TEST-> Model_Pattern.T -> T_TEST
    70   val s_make_complete: Proof.context ->  O_Model.T -> T_TEST * T_TEST -> Problem.id * MethodC.id ->
    71     T_TEST * T_TEST
    72   val s_are_complete: Proof.context -> O_Model.T -> T_TEST * T_TEST -> Problem.id * MethodC.id -> bool
    73 
    74   val is_error: feedback -> bool
    75   val to_p_model: theory -> feedback -> string
    76 
    77 (*/----- from isac_test for Minisubpbl*)
    78   val msg: variants -> feedback_TEST -> string
    79   val transfer_terms: O_Model.single -> single_TEST
    80 
    81   val eq1: ''a -> 'b * (''a * 'c) -> bool
    82   val feedback_to_string: Proof.context -> feedback -> string
    83   val feedback_TEST_to_string: Proof.context -> feedback_TEST -> string
    84   val descr_vals_to_string: Proof.context -> descriptor * values -> string
    85   val feedb_args_to_string: Proof.context -> feedback_TEST -> string
    86 
    87   val ori_2itm: feedback -> descriptor -> Model_Def.values -> O_Model.single -> single
    88   val seek_ppc: int -> T -> single option
    89   val overwrite_ppc: theory -> single -> T -> T
    90 (*\----- from isac_test for Minisubpbl*)
    91 
    92 \<^isac_test>\<open>
    93   (**)
    94 
    95 \<close>
    96 
    97 end
    98 
    99 (**)
   100 structure I_Model(**) : INTERACTION_MODEL(**) =
   101 struct
   102 (**)
   103 
   104 (** data types **)
   105 
   106 type variant =  Model_Def.variant;
   107 type variants =  Model_Def.variants;
   108 type m_field = Model_Def.m_field;
   109 type descriptor = Model_Def.descriptor;
   110 type values = Model_Def.values
   111 
   112 type T = Model_Def.i_model_single list;
   113 (* for developing input from PIDE, we use T_TEST with these ideas:
   114   (1) the new structure is as close to old T, because we want to preserve the old tests
   115   (2) after development (with *_TEST) of essential parts of the Specification's semantics,
   116       we adapt the old tests to the new T_TEST
   117   (3) together with adaption of the tests we remove the *_TEST
   118 *)
   119 type T_TEST = Model_Def.i_model_single_TEST list;
   120 datatype feedback = datatype Model_Def.i_model_feedback;
   121 datatype feedback_TEST = datatype Model_Def.i_model_feedback_TEST;
   122 val feedback_empty_TEST = Model_Def.feedback_empty_TEST
   123 type single = Model_Def.i_model_single;
   124 type single_TEST = Model_Def.i_model_single_TEST;
   125 val empty_single = Model_Def.i_model_empty;
   126 val empty_single_TEST = Model_Def.i_model_empty_TEST;
   127 fun is_empty_single_TEST (0, [], false, "i_model_empty", _) = true
   128   | is_empty_single_TEST _ = false
   129 
   130 val empty = []: T;
   131 val empty_TEST = []: T_TEST;
   132 
   133 type env = Env.T
   134 
   135 
   136 fun feedback_OLD_to_TEST (Cor ((d, ts), _)) = (Model_Def.Cor_TEST (d, ts))
   137   | feedback_OLD_to_TEST (Syn c) = (Model_Def.Syn_TEST c)
   138   | feedback_OLD_to_TEST (Typ c) = (Model_Def.Syn_TEST c)
   139   | feedback_OLD_to_TEST (Inc ((d, ts), _)) = (Model_Def.Inc_TEST (d, ts))
   140   | feedback_OLD_to_TEST (Sup (d, ts)) = (Model_Def.Sup_TEST (d, ts))
   141   | feedback_OLD_to_TEST (Mis (d, pid)) = Model_Def.Syn_TEST ((UnparseC.term (ContextC.for_ERROR ()) d) ^ " " ^
   142       (UnparseC.term (ContextC.for_ERROR ()) pid))
   143   | feedback_OLD_to_TEST (Par s) = (Model_Def.Syn_TEST s)
   144 fun OLD_to_TEST i_old =
   145   map (fn (a, b, c, d, e) => (a, b, c, d, (feedback_OLD_to_TEST e, Position.none))) i_old
   146 
   147 fun feedback_TEST_to_OLD (Model_Def.Cor_TEST (d, ts)) = (Cor ((d, ts), (TermC.empty, [])))
   148   | feedback_TEST_to_OLD (Model_Def.Syn_TEST c) = (Syn c)
   149   | feedback_TEST_to_OLD (Model_Def.Inc_TEST (d, ts)) = (Inc ((d, ts), (TermC.empty, [])))
   150   | feedback_TEST_to_OLD (Model_Def.Sup_TEST (d, ts)) = (Sup (d, ts))
   151 fun TEST_to_OLD i_model = 
   152   map (fn (a, b, c, d, (e, _)) => (a, b, c, d, feedback_TEST_to_OLD e)) i_model
   153 
   154 type message = string;
   155 
   156 fun feedback_to_string ctxt (Cor ((d, ts), _)) = 
   157     "Cor " ^ UnparseC.term  ctxt (Input_Descript.join (d, ts)) ^ " , pen2str"
   158   | feedback_to_string _ (Syn c) = "Syn " ^ c
   159   | feedback_to_string _ (Typ c) = "Typ " ^ c
   160   | feedback_to_string ctxt (Inc ((d, ts), _)) = 
   161     "Inc " ^ UnparseC.term  ctxt (Input_Descript.join (d, ts)) ^ " , pen2str"
   162   | feedback_to_string ctxt (Sup (d, ts)) = 
   163     "Sup " ^ UnparseC.term  ctxt (Input_Descript.join (d, ts))
   164   | feedback_to_string ctxt (Mis (d, pid)) = 
   165     "Mis " ^ UnparseC.term  ctxt d ^ " " ^ UnparseC.term ctxt pid
   166   | feedback_to_string _ (Par s) = "Trm "^s;
   167 
   168 fun feedback_TEST_to_string ctxt (Cor_TEST (d, ts)) = 
   169     "Cor_TEST " ^ UnparseC.term ctxt (Input_Descript.join (d, ts)) ^ " , pen2str"
   170   | feedback_TEST_to_string _ (Syn_TEST c) =
   171     "Syn_TEST " ^ c
   172   | feedback_TEST_to_string ctxt (Inc_TEST (d, [])) = 
   173     "Inc_TEST " ^ UnparseC.term ctxt (Input_Descript.join (d, [])) ^ " " ^ 
   174       Model_Pattern.empty_for d
   175   | feedback_TEST_to_string ctxt (Inc_TEST (d, ts)) =
   176     "Inc_TEST " ^ UnparseC.term ctxt (Input_Descript.join (d, ts)) ^ " , pen2str"
   177   | feedback_TEST_to_string ctxt (Sup_TEST (d, ts)) = 
   178     "Sup_TEST " ^ UnparseC.term ctxt (Input_Descript.join (d, ts))
   179 
   180 fun descr_vals_to_string ctxt (descr, values) =
   181   UnparseC.term ctxt (descr $ Model_Def.values_to_present values)
   182 
   183 (*prepare for presentation to user; thus Syn_TEST does NOT raise an exn*)
   184 fun feedb_args_to_string ctxt (Cor_TEST (descr, values)) =
   185     UnparseC.term ctxt (descr $ Model_Def.values_to_present values)
   186   | feedb_args_to_string _ (Syn_TEST str) = str
   187   | feedb_args_to_string ctxt (Inc_TEST (descr, [])) =
   188     UnparseC.term ctxt descr ^ Model_Pattern.empty_for descr
   189   | feedb_args_to_string ctxt (Inc_TEST (descr, values)) =
   190     UnparseC.term ctxt (descr $ Model_Def.values_to_present values)
   191   | feedb_args_to_string ctxt (Sup_TEST (descr, values)) =
   192     UnparseC.term ctxt (descr $ Model_Def.values_to_present values)
   193 
   194 fun single_to_string ctxt (i, is, b, s, itm_) = 
   195   "(" ^ string_of_int i ^ " ," ^ ints2str' is ^ " ," ^ bool2str b ^ " ," ^
   196   s ^ " ," ^ feedback_to_string ctxt itm_ ^ ")";
   197 fun single_to_string_TEST ctxt (i, is, b, s, (itm_, _(*Position.T*))) = 
   198   "(" ^ string_of_int i ^ ", " ^ ints2str' is ^ ", " ^ bool2str b ^ " ," ^
   199   s ^ ", (" ^ feedback_TEST_to_string ctxt itm_ ^ ", Position.T))";
   200 fun single_to_string_TEST' (i, is, b, s, (itm_, _(*Position.T*))) = 
   201   "(" ^ string_of_int i ^ ", " ^ ints2str' is ^ ", " ^ bool2str b ^ " ," ^
   202   s ^ ", (" ^ feedback_TEST_to_string (ContextC.for_ERROR ()) itm_ ^ ", Position.T))";
   203 
   204 fun to_string ctxt itms = strs2str' (map (linefeed o (single_to_string ctxt)) itms);
   205 fun to_string_TEST ctxt itms = strs2str' (map (linefeed o (single_to_string_TEST ctxt)) itms);
   206 
   207 
   208 (** make a Tactic.T **)
   209 
   210 fun make_tactic m_field (term_as_string, i_model) =
   211   case m_field of
   212     "#Given" => Tactic.Add_Given' (term_as_string, i_model)
   213   | "#Find" => Tactic.Add_Find' (term_as_string, i_model)
   214   | "#Relate" => Tactic.Add_Relation'(term_as_string, i_model)
   215   | str => raise ERROR ("specify_additem Frm, Pbl: uncovered case with " ^ str);
   216 
   217 
   218 (** initialise a model **)
   219 
   220 fun init pbt = 
   221   let
   222     fun pbt2itm (f, (d, _)) = (0, [], false, f, Inc ((d, []), (TermC.empty, [])))
   223   in map pbt2itm pbt end
   224 
   225 (*
   226   Design decision:
   227 * Now the Model in Specification is intialised such that the placement of items can be
   228   maximally stable during interactive input to the Specification.
   229 * Template.show provides the initial output to the user and thus determines what will be parsed
   230   by Outer_Syntax later during interaction.
   231 * The relation between O_Model.T and I_Model.T becomes much simpler.
   232 *)
   233 (**)
   234 fun pat_to_item ctxt o_model (_, (descriptor, _)) =
   235   case find_first (fn (_, _, _, desc, _) => desc = descriptor) o_model of
   236     NONE => raise ERROR ("I_Model.pat_to_item NONE for " ^ UnparseC.term ctxt descriptor)
   237   | SOME (_, variants, m_field, descr, _) => (variants, false, m_field,
   238     (Inc_TEST (descr, []), Position.none))
   239 fun init_TEST ctxt o_model model_patt =
   240   let
   241     val pre_items = map (pat_to_item ctxt o_model) model_patt
   242   in
   243     O_Model.add_enumerate pre_items |> map (fn (a, (b, c, d, e)) => (a, b, c, d, e))
   244   end
   245 
   246 
   247 val unique = Syntax.read_term\<^context> "UnIqE_tErM";
   248 (*/-wait for intro-fn into M_Match-\*)
   249 fun descriptor (Cor ((d ,_), _)) = d
   250   | descriptor (Syn _) = ((*tracing ("*** descriptor: Syn ("^c^")");*) unique)
   251   | descriptor (Typ _) = ((*tracing ("*** descriptor: Typ ("^c^")");*) unique)
   252   | descriptor (Inc ((d, _), _)) = d
   253   | descriptor (Sup (d, _)) = d
   254   | descriptor (Mis (d, _)) = d
   255   | descriptor _ = raise ERROR "descriptor: uncovered case in fun.def.";
   256 (*\-wait for intro-fn into M_Match-/*)
   257 fun descriptor_TEST (Cor_TEST (d ,_)) = d
   258   | descriptor_TEST (Syn_TEST _) = ((*tracing ("*** descriptor: Syn ("^c^")");*) unique)
   259   | descriptor_TEST (Inc_TEST (d, _)) = d
   260   | descriptor_TEST (Sup_TEST (d, _)) = d
   261 
   262 fun values (Cor ((_ , ts), _)) = SOME ts
   263   | values (Syn _) = NONE
   264   | values (Typ _) = NONE
   265   | values (Inc ((_, ts), _)) = SOME ts
   266   | values (Sup (_, ts)) = SOME ts
   267   | values (Mis (_, t)) = SOME [t]
   268   | values _ = raise ERROR "descriptor: uncovered case in fun.def.";
   269 fun o_model_values (Cor ((_, ts), _)) = ts
   270   | o_model_values (Syn _) = []
   271   | o_model_values (Typ _) = []
   272   | o_model_values (Inc ((_, ts), _)) = ts
   273   | o_model_values (Sup (_, ts)) = ts
   274   | o_model_values (Mis _) = []
   275   | o_model_values _ = raise ERROR "o_model_values: uncovered case in fun.def.";
   276 fun values_TEST' (Cor_TEST (_, ts)) = ts
   277   | values_TEST' (Syn_TEST _) = raise ERROR "values_TEST' NOT for Syn_TEST"
   278   | values_TEST' (Inc_TEST (_, ts)) = ts
   279   | values_TEST' (Sup_TEST (_, ts)) = ts
   280 
   281 fun descr_pairs_to_string ctxt equal_descr_pairs =
   282 (map (fn (a, b) => pair (Model_Pattern.single_to_string ctxt a) (single_to_string_TEST ctxt b)
   283     |> pair2str) equal_descr_pairs)
   284   |> strs2str'
   285 
   286 fun variables model_patt i_model =
   287   Pre_Conds.environment_TEST model_patt i_model
   288   |> map snd
   289 
   290 val unknown_descriptor = Syntax.read_term\<^context> "unknown::'a => unknow";
   291 
   292 (* get a term from O_Model, notyet input in I_Model.
   293    the term from O_Model is thrown back to a string in order to reuse
   294    machinery for immediate input by the user. *)
   295 fun get_field_term thy (_, _, _, d, ts) (_, _, _, fd, itm_) =
   296   (fd, ((UnparseC.term_in_thy thy) o Input_Descript.join) (d, subtract op = (o_model_values itm_) ts))
   297 
   298 (*update the itm_ already input, all..from ori*)
   299 fun ori_2itm itm_ pid all (id, vt, fd, d, ts) = 
   300   let 
   301     val ts' = union op = (o_model_values itm_) ts;
   302     val pval = [Input_Descript.join'''' (d, ts')]
   303 	  (*WN.9.5.03: FIXXXME [#0, epsilon] here would upd_penv be called for [#0, epsilon] etc*)
   304     val complete = if eq_set op = (ts', all) then true else false
   305   in
   306     case itm_ of
   307       (Cor _) => 
   308         (if fd = "#undef" then (id, vt, complete, fd, Sup (d, ts')) 
   309 	       else (id, vt, complete, fd, Cor ((d, ts'), (pid, pval))))
   310     | (Syn c) => raise ERROR ("ori_2itm wants to overwrite " ^ c)
   311     | (Typ c) => raise ERROR ("ori_2itm wants to overwrite " ^ c)
   312     | (Inc _) =>
   313       if complete
   314   	  then (id, vt, true, fd, Cor ((d, ts'), (pid, pval)))
   315   	  else (id, vt, false, fd, Inc ((d, ts'), (pid, pval)))
   316     | (Sup (d,ts')) => (*4.9.01 lost env*)
   317   	  (*if fd = "#undef" then*) (id,vt,complete,fd,Sup(d,ts'))
   318   	  (*else (id,vt,complete,fd,Cor((d,ts'),e))*)
   319       (* 28.1.00: not completely clear ---^^^ etc.*)
   320     | (Mis _) => (* 4.9.01: Mis just copied *)
   321        if complete
   322   		 then (id, vt, true, fd, Cor ((d,ts'), (pid, pval)))
   323   		 else (id, vt, false, fd, Inc ((d,ts'), (pid, pval)))
   324     | i => raise ERROR ("ori_2itm: uncovered case of " ^ feedback_to_string (ContextC.for_ERROR ()) i)
   325   end
   326 
   327 
   328 (** find next step **)
   329 
   330 fun eq1 d (_, (d', _)) = (d = d')
   331 fun eq3 f d (_, _, _, f', itm_) = f = f' andalso d = (descriptor itm_) 
   332 
   333 fun is_notyet_input ctxt itms all (i, v, f, d, ts) pbt =
   334   case find_first (eq1 d) pbt of
   335     SOME (_, (_, pid)) =>
   336       (case find_first (eq3 f d) itms of
   337         SOME (_, _, _, _, itm_) =>
   338           let val ts' = inter op = (o_model_values itm_) ts
   339           in 
   340             if subset op = (ts, ts') 
   341             then (((strs2str' o map (UnparseC.term ctxt)) ts') ^ " already input", empty_single)
   342 	          else ("", ori_2itm itm_ pid all (i, v, f, d, subtract op = ts' ts))
   343 	          end
   344 	    | NONE => ("", ori_2itm (Inc ((TermC.empty, []), (pid, []))) pid all (i, v, f, d, ts)))
   345   | NONE => ("", ori_2itm (Sup (d, ts)) TermC.empty all (i, v, f, d, ts))
   346 
   347 datatype add_single =
   348 	Add of single   (* return-value of check_single *)
   349 | Err of string   (* error-message                *)
   350 
   351 (*
   352   Create feedback for input of TermC.as_string to m_field;
   353   check w.r.t. O_Model.T and Model_Pattern.T.
   354   In case of O_Model.T = [] (i.e. no data for user-guidance in Formalise.T)
   355   check_single is extremely permissive.
   356 *)
   357 (*will come directly from PIDE -----------------vvvvvvvvvvv
   358   in case t comes from Step.specify_do_next -----------vvv = Position.none*)
   359 fun check_single ctxt m_field [] i_model m_patt (ct(*, pos*)) =
   360     let
   361       val i = 1 + (if i_model = [] then 0 else map #1 i_model |> maxl)
   362     (*/------------ replace by ParseC.term_position -----------\*)
   363       val t = Syntax.read_term ctxt ct
   364         handle ERROR msg => error (msg (*^ Position.here pos*))
   365     (*\------------ replace by ParseC.term_position -----------/*)
   366         (*NONE => Add (i, [], false, m_field, Syn ct)*)
   367       val (d, ts) = Input_Descript.split t
   368     in 
   369       if d = TermC.empty then
   370         Add (i, [], false, m_field, Mis (unknown_descriptor, hd ts)) 
   371       else
   372         (case find_first (eq1 d) m_patt of
   373           NONE => Add (i, [], true, m_field, Sup (d,ts))
   374         | SOME (f, (_, id)) =>
   375             let
   376               fun eq2 d (i, _, _, _, itm_) = d = (descriptor itm_) andalso i <> 0
   377             in
   378               case find_first (eq2 d) i_model of
   379                 NONE => Add (i, [], true, f,Cor ((d, ts), (id, [Input_Descript.join'''' (d, ts)])))
   380               | SOME (i', _, _, _, itm_) => 
   381                   if Input_Descript.for_list d then 
   382                     let
   383                       val in_itm = o_model_values itm_
   384                       val ts' = union op = ts in_itm
   385                       val i'' = if in_itm = [] then i else i'
   386                     in Add (i'', [], true, f, Cor ((d, ts'), (id, [Input_Descript.join'''' (d, ts')])))end
   387                   else Add (i', [], true, f, Cor ((d, ts), (id, [Input_Descript.join'''' (d, ts)])))
   388             end)
   389     end
   390     (*will come directly from PIDE ----------------------vvvvvvvvvvv*)
   391   | check_single ctxt m_field o_model i_model m_patt (str(*, pos*)) =
   392     let
   393       val (t as (descriptor $ _)) = Syntax.read_term ctxt str
   394         handle ERROR msg => error (msg (*TODO: ^ Position.here pp*))
   395         (*old code: NONE => Err ("ERROR I_Model.check_single: syntax error in \"" ^ str ^ "\"")*)
   396     in 
   397         case Model_Pattern.get_field descriptor m_patt of
   398           NONE => Err ("ERROR I_Model.check_single: unknown descriptor \"" ^
   399             UnparseC.term ctxt descriptor ^ "\"")
   400         | SOME m_field' => 
   401           if m_field <> m_field' then
   402             Err ("ERROR I_Model.check_single: \"" ^ UnparseC.term ctxt t ^ "\"" ^
   403              "\" not for field \"" ^ m_field ^ "\"")
   404           else
   405             case O_Model.contains ctxt m_field o_model t of
   406               ("", ori', all) => 
   407                 (case is_notyet_input ctxt i_model all ori' m_patt of
   408                    ("", itm) => Add itm
   409                  | (msg, _) => Err ("ERROR I_Model.check_single: is_notyet_input: " ^ msg))
   410             | (msg, _, _) => Err ("ERROR I_Model.check_single: contains: " ^ msg)
   411     end
   412      
   413 
   414 (** add input **)
   415 
   416 fun overwrite_ppc thy itm model =
   417   let 
   418     fun repl _ (_, _, _, _, itm_) [] =
   419         raise ERROR ("overwrite_ppc: " ^ feedback_to_string (Proof_Context.init_global thy) itm_
   420           ^ " not found")
   421       | repl model' itm (p :: model) =
   422 	      if (#1 itm) = (#1 p)
   423 	      then model' @ [itm] @ model
   424 	      else repl (model' @ [p]) itm model
   425   in repl [] itm model end
   426 
   427 (*find_first item with #1 equal to id*)
   428 fun seek_ppc _ [] = NONE
   429   | seek_ppc id (p :: model) = if id = #1 (p: single) then SOME p else seek_ppc id model
   430 
   431 (* 10.3.00: insert the parsed itm into model;
   432    ev. filter_out  untouched (in FE: (0,...)) item related to insert-item *)
   433 fun add_single thy itm model =
   434   let 
   435     fun eq_untouched d (0, _, _, _, itm_) = (d = descriptor itm_)
   436       | eq_untouched _ _ = false
   437     val model' = case seek_ppc (#1 itm) model of
   438       SOME _ => overwrite_ppc thy itm model (*itm updated in is_notyet_input WN.11.03*)
   439     | NONE => (model @ [itm])
   440   in filter_out (eq_untouched ((descriptor o #5) itm)) model' end
   441 
   442 
   443 (** complete I_Model.T **)
   444 
   445 fun s_are_complete _ _ ([], _) _ = false
   446   | s_are_complete _ _ (_, []) _ = false
   447   | s_are_complete ctxt o_model (pbl_imod, met_imod) (pbl_id, met_id) =
   448   let
   449     val pbl_max_vnts = Model_Def.max_variants o_model pbl_imod
   450     val met_max_vnts = Model_Def.max_variants o_model met_imod
   451     val max_vnts = inter op= pbl_max_vnts met_max_vnts
   452     val max_vnt = if max_vnts = []
   453       then raise ERROR "I_Model.s_are_complete: request user to review met_imod"
   454       else hd max_vnts
   455 
   456     val (pbl_imod', met_imod') = (
   457       filter (fn (_, vnts, _, _, _) => member_swap op = max_vnt vnts) pbl_imod,
   458       filter (fn (_, vnts, _, _, _) => member_swap op = max_vnt vnts) met_imod)
   459 
   460     val (pbl_check, _) = Pre_Conds.check_internal ctxt pbl_imod' (Pos.Pbl, pbl_id)
   461     val (met_check, _) = Pre_Conds.check_internal ctxt met_imod' (Pos.Met, met_id)
   462   in
   463     pbl_check andalso met_check
   464   end
   465 
   466 fun is_error (Cor _) = false
   467   | is_error (Sup _) = false
   468   | is_error (Inc _) = false
   469   | is_error (Mis _) = false
   470   | is_error _ = true
   471 
   472 (*create output-string for itm*)
   473 fun to_p_model thy (Cor ((d, ts), _)) = UnparseC.term_in_thy thy (Input_Descript.join (d, ts))
   474   | to_p_model _ (Syn c) = c
   475   | to_p_model _ (Typ c) = c
   476   | to_p_model thy (Inc ((d, ts), _)) = UnparseC.term_in_thy thy (Input_Descript.join (d, ts))
   477   | to_p_model thy (Sup (d, ts)) = UnparseC.term_in_thy thy (Input_Descript.join (d, ts))
   478   | to_p_model thy (Mis (d, pid)) = UnparseC.term_in_thy thy d ^ " " ^ UnparseC.term_in_thy thy pid
   479   | to_p_model _ _ = raise ERROR "to_p_model: uncovered definition"
   480 
   481 fun fill_from_o o_model (i, vnts, bool, _, (feedb, pos)) = 
   482   let
   483     val (m_field, all_values) =
   484       case find_first (fn (_, _, _, descr', _) => Model_Def.descriptor_exists descr' feedb) o_model of
   485         SOME (_, _, m_field, _, ts) =>  (m_field, ts)
   486       | NONE => raise ERROR "I_Model.fill_from_o does NOT find a descriptor in O_Model"
   487     val descr = Model_Def.get_descr feedb (*i_single has been filtered appropriately*)
   488   in
   489 (*---------------vvvvvvvvvvvvv MV if TermC-is_list all_value-----*)
   490     if Model_Def.is_list_descr descr
   491     then
   492       let
   493         val already_input = feedb |> values_TEST'
   494         val miss = subtract op= already_input all_values (*"[[c], [c_2], [c_3], [c_4]]"*)
   495         val ts = already_input @ [hd miss]
   496       in
   497         if length all_values = length ts
   498         then SOME (i, vnts, bool, m_field, (Cor_TEST (descr, [Model_Def.values_to_present ts]), pos))
   499         else SOME (i, vnts, bool, m_field, (Inc_TEST (descr, [Model_Def.values_to_present ts]), pos))
   500       end
   501     else SOME (i, vnts, bool, m_field, (Cor_TEST (descr, all_values(*only 1 term*)), pos))
   502   end
   503 
   504 (*
   505   in case there is an item in i2_model(= met) with Sup_TEST, 
   506   find_first an appropriate (variant, descriptor) item in i1_model(= pbl) and add it instead Sup_TEST,
   507   otherwise keep the items of i2_model.
   508 *)
   509 fun add_other max_vnt i1_model (i2, _, bool2, m_field2, (Sup_TEST (descr2, ts2), pos2)) =
   510     (case find_first (fn (_, vnts1, _, _, (feedb1, _)) => case Model_Def.get_dscr_opt feedb1 of
   511           NONE => false
   512         | SOME descr1 => descr1 = descr2 andalso Model_Def.member_vnt vnts1 max_vnt) i1_model of
   513       NONE =>
   514         (i2, [max_vnt], bool2, m_field2, (Sup_TEST (descr2, ts2), pos2)) (*the present in i2_model*)
   515     | SOME i1_single => i1_single)                      (*shift the item from i1_model to i2_model*)
   516   | add_other _ _ i2_single = i2_single                     (*keep all the other items in i2_model*)
   517 
   518 fun fill_method o_model (pbl_imod, met_imod) met_patt =
   519   let
   520     val pbl_max_vnts = Model_Def.max_variants o_model pbl_imod
   521     (*probably pbl/met_imod = [], so take met_patt; if empty return Sup*)
   522     val i_from_met = map (fn (_, (descr, _)) => (*order from met_patt*)
   523       Pre_Conds.get_descr_vnt descr pbl_max_vnts met_imod) met_patt (*\<longrightarrow> right order for args*)
   524 
   525     val met_max_vnts = Model_Def.max_variants o_model i_from_met;
   526     val max_vnt = hd (inter op= pbl_max_vnts met_max_vnts);
   527     (*add items from pbl_imod (without overwriting existing items in met_imod)*)
   528   in
   529     map (add_other max_vnt pbl_imod) i_from_met
   530   end 
   531 
   532 fun msg vnts feedb = "get_descr_vnt' returns NONE: i.e. it does not find an item of o_model with\n" ^
   533   "variants " ^ ints2str' vnts ^ " and descriptor " ^
   534   (feedb |> Model_Def.get_dscr_opt |> the |> UnparseC.term (ContextC.for_ERROR ()))
   535 fun transfer_terms (i, vnts, m_field, descr, ts) =
   536   (i, vnts, true, m_field, (Cor_TEST (descr, ts), Position.none))
   537 fun s_make_complete ctxt o_model (pbl_imod, met_imod) (pbl_id, met_id) =
   538   let
   539     val {model = pbl_patt, ...} = Problem.from_store ctxt pbl_id;
   540     val {model = met_patt, ...} = MethodC.from_store ctxt met_id;
   541     val pbl_max_vnts = Model_Def.max_variants o_model pbl_imod;
   542     val i_from_pbl = map (fn (_, (descr, _)) =>
   543       Pre_Conds.get_descr_vnt descr pbl_max_vnts pbl_imod) pbl_patt
   544     val pbl_from_o_model = map ((fn i_single as (_, _, _, _, (feedb, _)) =>
   545       if is_empty_single_TEST i_single
   546       then
   547         case Pre_Conds.get_descr_vnt' feedb pbl_max_vnts o_model of
   548             [] => raise ERROR (msg pbl_max_vnts feedb)
   549           | o_singles => map transfer_terms o_singles
   550       else [i_single (*fetched before from pbl_imod*)])) i_from_pbl |> flat
   551 
   552     val i_from_met = map (fn (_, (descr, _)) =>
   553       Pre_Conds.get_descr_vnt descr pbl_max_vnts met_imod) met_patt
   554     val met_max_vnts = Model_Def.max_variants o_model i_from_met;
   555     val max_vnt = hd met_max_vnts (*need only one for solve-phase*)
   556 
   557     val met_from_pbl = map ((fn i_single as (_, _, _, _, (feedb, _)) =>
   558       if is_empty_single_TEST i_single
   559       then
   560         case Pre_Conds.get_descr_vnt' feedb [max_vnt] o_model of
   561             [] => raise ERROR (msg [max_vnt] feedb)
   562           | o_singles => map transfer_terms o_singles
   563       else [i_single (*fetched before from met_imod*)])) i_from_met |> flat
   564   in
   565     (filter (fn (_, vnts', _, _, _) => member op = vnts' max_vnt) pbl_from_o_model,
   566       met_from_pbl)
   567   end
   568 
   569 (**)end(**);