src/Tools/isac/MathEngine/step.sml
author Walther Neuper <walther.neuper@jku.at>
Fri, 12 Jun 2020 11:41:57 +0200
changeset 60020 2d962612dd0a
parent 60011 25e6810ca0e7
child 60021 d70d5b668794
permissions -rw-r--r--
unify signatures of Step's (Step_Specify.by_tactic_input)
     1 (* Title:  MathEngine/step.sml
     2    Author: Walther Neuper 2019
     3    (c) due to copyright terms
     4 
     5 Unify function of structure Step_Specify and structure Step_Solve
     6 as well as of structure Specify_Step and structure Solve_Step.
     7 *)
     8 
     9 signature STEP =
    10 sig
    11   val do_next: Pos.pos' -> Calc.state_pre -> string * Calc.state_post
    12   val by_tactic: Tactic.input -> Calc.T -> string * Calc.state_post
    13 (*val by_term  = Step_Solve.by_term: Calc.T -> term -> string * Calc.state_post NOT for specify*)
    14   val check: Tactic.input -> Calc.T -> Applicable.T
    15   val add: Tactic.T -> Istate_Def.T * Proof.context -> Calc.T -> Test_Out.T
    16 
    17   val inconsistent: Subst.input option * ThmC.T -> term -> Istate_Def.T * Proof.context ->
    18     Pos.pos' -> Ctree.ctree -> Calc.T
    19 
    20 (* ---- for tests only: shifted from below to remove the Warning "unused" at fun.def. --------- *)
    21   (*NONE*)                                                     
    22 (*/-------------------------------------------------------- ! aktivate for Test_Isac BEGIN ---\* )
    23   val specify_do_next: Calc.T -> string * Calc.state_post
    24   val switch_specify_solve: Pos.pos_ -> Calc.T -> string * Calc.state_post
    25 ( *\--- ! aktivate for Test_Isac END ----------------------------------------------------------/*)
    26 end
    27 
    28 (**)
    29 structure Step(**): STEP(**) =
    30 struct
    31 (**)
    32 
    33 (** check a tactic for applicability **)
    34 
    35 fun check tac (ctree, pos) =
    36   if Tactic.for_specify tac
    37   then Specify_Step.check tac (ctree, pos)
    38   else Solve_Step.check tac (ctree, pos);
    39 
    40 
    41 (** add a step to a calculation **)
    42 
    43 val add = Solve_Step.add_general;
    44 
    45 
    46 (* survey on results of by_tactic, find_next, by_term:
    47    * Step_Specify
    48      * by_tactic "ok", "ok", 
    49    * Step_Solve              
    50      * locate_input_tactic  : "ok", "unsafe-ok", "not-applicable", "end-of-calculation"
    51      * locate_input_term : "ok", "syntax error", "same-formula", "no derivation found",
    52         "error pattern #" ^ errpatID (the latter doesn't fit into the pattern of fixed string)
    53      * find_next_formula    : "ok", "helpless", "no-fmz-spec"(=helpless), "end-of-calculation"
    54  *)
    55 
    56 (** do a next step **)
    57 
    58 fun specify_do_next (ptp as (pt, (p, p_))) =
    59   let
    60     val (_, (p_', tac)) = Specify.find_next_step ptp
    61     val ist_ctxt =  Ctree.get_loc pt (p, p_)
    62   in
    63     case tac of
    64   	  Tactic.Apply_Method mI =>
    65   	    (*vvvvvvvvvv-------------------------------------------------------------- solve-phase *)
    66   	    LI.by_tactic (Tactic.Apply_Method' (mI, NONE, Istate.empty, ContextC.empty))
    67   	      ist_ctxt (pt, (p, p_'))
    68     | _ => Step_Specify.by_tactic_input tac (pt, (p, p_'))
    69   end
    70 
    71 fun switch_specify_solve state_pos (pt, input_pos) =
    72   let
    73     val result =
    74       if Pos.on_specification ([], state_pos)
    75   	  then specify_do_next (pt, input_pos)
    76       else LI.do_next (pt, input_pos)
    77   in
    78     case result of
    79       (_, cs as ([], _, _)) => ("helpless", cs)
    80     | scs => scs
    81   end
    82 
    83 (* does a step forward; returns tactic used, ctree updated (i.e. with NEW term/calchead) *)
    84 fun do_next (ip as (_, p_)) (ptp as (pt, p), tacis) =
    85   if Pos.on_calc_end ip then
    86     ("end-of-calculation", (tacis, [], ptp): Calc.state_post) 
    87   else
    88     let
    89       val (_, probl_id, _) = Calc.references (pt, p);
    90     in
    91       case tacis of
    92         (_ :: _) => 
    93           if ip = p (*the request is done where ptp waits for*)
    94           then                 
    95             let
    96               val (pt', c', p') = Solve_Step.s_add_general tacis (pt, [], p)
    97             in
    98              ("ok", (tacis, c', (pt', p')))
    99             end
   100          else
   101             switch_specify_solve p_ (pt, ip)
   102       | _ =>
   103         if probl_id = Problem.id_empty then
   104            ("no-fmz-spec", ([], [], ptp))
   105         else switch_specify_solve p_ (pt, ip)
   106     end;
   107 
   108 
   109 (** locate an input tactic **)
   110 
   111 (* LEGACY: report of tacs' applicability in tacis; pt is dropped in setNextTactic*)
   112 fun by_tactic _ (ptp as (_, ([], Pos.Res))) = ("end-of-calculation", ([], [], ptp))
   113   | by_tactic tac (ptp as (pt, p)) =
   114     case check tac (pt, p) of
   115 	    Applicable.No _ => ("not-applicable", ([],[],  ptp): Calc.state_post)
   116 	  | Applicable.Yes tac' =>
   117 	    if Tactic.for_specify' tac'
   118 	    then Step_Specify.by_tactic tac' ptp
   119 	    else Step_Solve.by_tactic tac' ptp
   120 
   121 
   122 (** add an inconsisten step **)
   123 
   124 fun inconsistent (subs_opt, thm') f' (is, ctxt) (pos as (p,_)) pt =
   125   let
   126     val f = Ctree.get_curr_formula (pt, pos)
   127     val pos' as (p', _) = (Pos.lev_on p, Pos.Res)
   128     val (pt, _) = case subs_opt of
   129       NONE => Ctree.cappend_atomic pt p' (is, ctxt) f
   130         (Tactic.Rewrite thm') (f', []) Ctree.Inconsistent
   131     | SOME subs => Ctree.cappend_atomic pt p' (is, ctxt) f
   132         (Tactic.Rewrite_Inst (subs, thm')) (f', []) Ctree.Inconsistent
   133     val pt = Ctree.update_branch pt p' Ctree.TransitiveB
   134   in (pt, pos') end
   135 
   136 (**)end(**)