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