src/Tools/code/code_funcgr.ML
author haftmann
Thu, 25 Sep 2008 09:28:08 +0200
changeset 28350 715163ec93c0
parent 28338 e58ec46d50bc
child 28370 37f56e6e702d
permissions -rw-r--r--
non left-linear equations for nbe
     1 (*  Title:      Tools/code/code_funcgr.ML
     2     ID:         $Id$
     3     Author:     Florian Haftmann, TU Muenchen
     4 
     5 Retrieving, normalizing and structuring defining equations in graph
     6 with explicit dependencies.
     7 *)
     8 
     9 signature CODE_FUNCGR =
    10 sig
    11   type T
    12   val funcs: T -> string -> (thm * bool) list
    13   val typ: T -> string -> (string * sort) list * typ
    14   val all: T -> string list
    15   val pretty: theory -> T -> Pretty.T
    16   val make: theory -> string list -> T
    17   val eval_conv: theory -> (term -> term * (T -> term -> thm)) -> cterm -> thm
    18   val eval_term: theory -> (term -> term * (T -> term -> 'a)) -> term -> 'a
    19   val timing: bool ref
    20 end
    21 
    22 structure Code_Funcgr : CODE_FUNCGR =
    23 struct
    24 
    25 (** the graph type **)
    26 
    27 type T = (((string * sort) list * typ) * (thm * bool) list) Graph.T;
    28 
    29 fun funcs funcgr =
    30   these o Option.map snd o try (Graph.get_node funcgr);
    31 
    32 fun typ funcgr =
    33   fst o Graph.get_node funcgr;
    34 
    35 fun all funcgr = Graph.keys funcgr;
    36 
    37 fun pretty thy funcgr =
    38   AList.make (snd o Graph.get_node funcgr) (Graph.keys funcgr)
    39   |> (map o apfst) (Code_Unit.string_of_const thy)
    40   |> sort (string_ord o pairself fst)
    41   |> map (fn (s, thms) =>
    42        (Pretty.block o Pretty.fbreaks) (
    43          Pretty.str s
    44          :: map (Display.pretty_thm o fst) thms
    45        ))
    46   |> Pretty.chunks;
    47 
    48 
    49 (** generic combinators **)
    50 
    51 fun fold_consts f thms =
    52   thms
    53   |> maps (op :: o swap o apfst (snd o strip_comb) o Logic.dest_equals o Thm.plain_prop_of)
    54   |> (fold o fold_aterms) (fn Const c => f c | _ => I);
    55 
    56 fun consts_of (const, []) = []
    57   | consts_of (const, thms as _ :: _) = 
    58       let
    59         fun the_const (c, _) = if c = const then I else insert (op =) c
    60       in fold_consts the_const (map fst thms) [] end;
    61 
    62 fun insts_of thy algebra tys sorts =
    63   let
    64     fun class_relation (x, _) _ = x;
    65     fun type_constructor tyco xs class =
    66       (tyco, class) :: (maps o maps) fst xs;
    67     fun type_variable (TVar (_, sort)) = map (pair []) sort
    68       | type_variable (TFree (_, sort)) = map (pair []) sort;
    69     fun of_sort_deriv ty sort =
    70       Sorts.of_sort_derivation (Syntax.pp_global thy) algebra
    71         { class_relation = class_relation, type_constructor = type_constructor,
    72           type_variable = type_variable }
    73         (ty, sort) handle Sorts.CLASS_ERROR _ => [] (*permissive!*)
    74   in (flat o flat) (map2 of_sort_deriv tys sorts) end;
    75 
    76 fun meets_of thy algebra =
    77   let
    78     fun meet_of ty sort tab =
    79       Sorts.meet_sort algebra (ty, sort) tab
    80         handle Sorts.CLASS_ERROR _ => tab (*permissive!*);
    81   in fold2 meet_of end;
    82 
    83 
    84 (** graph algorithm **)
    85 
    86 val timing = ref false;
    87 
    88 local
    89 
    90 fun resort_thms thy algebra typ_of thms =
    91   let
    92     val cs = fold_consts (insert (op =)) thms [];
    93     fun meets (c, ty) = case typ_of c
    94        of SOME (vs, _) =>
    95             meets_of thy algebra (Sign.const_typargs thy (c, ty)) (map snd vs)
    96         | NONE => I;
    97     val tab = fold meets cs Vartab.empty;
    98   in map (Code_Unit.inst_thm tab) thms end;
    99 
   100 fun resort_funcss thy algebra funcgr =
   101   let
   102     val typ_funcgr = try (fst o Graph.get_node funcgr);
   103     val resort_dep = (apsnd o burrow_fst) (resort_thms thy algebra typ_funcgr);
   104     fun resort_rec typ_of (c, []) = (true, (c, []))
   105       | resort_rec typ_of (c, thms as (thm, _) :: _) = if is_some (AxClass.inst_of_param thy c)
   106           then (true, (c, thms))
   107           else let
   108             val (_, (vs, ty)) = Code_Unit.head_func thm;
   109             val thms' as (thm', _) :: _ = burrow_fst (resort_thms thy algebra typ_of) thms
   110             val (_, (vs', ty')) = Code_Unit.head_func thm'; (*FIXME simplify check*)
   111           in (Sign.typ_equiv thy (ty, ty'), (c, thms')) end;
   112     fun resort_recs funcss =
   113       let
   114         fun typ_of c = case these (AList.lookup (op =) funcss c)
   115          of (thm, _) :: _ => (SOME o snd o Code_Unit.head_func) thm
   116           | [] => NONE;
   117         val (unchangeds, funcss') = split_list (map (resort_rec typ_of) funcss);
   118         val unchanged = fold (fn x => fn y => x andalso y) unchangeds true;
   119       in (unchanged, funcss') end;
   120     fun resort_rec_until funcss =
   121       let
   122         val (unchanged, funcss') = resort_recs funcss;
   123       in if unchanged then funcss' else resort_rec_until funcss' end;
   124   in map resort_dep #> resort_rec_until end;
   125 
   126 fun instances_of thy algebra insts =
   127   let
   128     val thy_classes = (#classes o Sorts.rep_algebra o Sign.classes_of) thy;
   129     fun all_classparams tyco class =
   130       these (try (#params o AxClass.get_info thy) class)
   131       |> map_filter (fn (c, _) => try (AxClass.param_of_inst thy) (c, tyco))
   132   in
   133     Symtab.empty
   134     |> fold (fn (tyco, class) =>
   135         Symtab.map_default (tyco, []) (insert (op =) class)) insts
   136     |> (fn tab => Symtab.fold (fn (tyco, classes) => append (maps (all_classparams tyco)
   137          (Graph.all_succs thy_classes classes))) tab [])
   138   end;
   139 
   140 fun instances_of_consts thy algebra funcgr consts =
   141   let
   142     fun inst (cexpr as (c, ty)) = insts_of thy algebra
   143       (Sign.const_typargs thy (c, ty)) ((map snd o fst) (typ funcgr c));
   144   in
   145     []
   146     |> fold (fold (insert (op =)) o inst) consts
   147     |> instances_of thy algebra
   148   end;
   149 
   150 fun ensure_const' thy algebra funcgr const auxgr =
   151   if can (Graph.get_node funcgr) const
   152     then (NONE, auxgr)
   153   else if can (Graph.get_node auxgr) const
   154     then (SOME const, auxgr)
   155   else if is_some (Code.get_datatype_of_constr thy const) then
   156     auxgr
   157     |> Graph.new_node (const, [])
   158     |> pair (SOME const)
   159   else let
   160     val thms = Code.these_funcs thy const
   161       |> burrow_fst Code_Unit.norm_args
   162       |> burrow_fst (Code_Unit.norm_varnames Code_Name.purify_tvar Code_Name.purify_var);
   163     val rhs = consts_of (const, thms);
   164   in
   165     auxgr
   166     |> Graph.new_node (const, thms)
   167     |> fold_map (ensure_const thy algebra funcgr) rhs
   168     |-> (fn rhs' => fold (fn SOME const' => Graph.add_edge (const, const')
   169                            | NONE => I) rhs')
   170     |> pair (SOME const)
   171   end
   172 and ensure_const thy algebra funcgr const =
   173   let
   174     val timeap = if !timing
   175       then Output.timeap_msg ("time for " ^ Code_Unit.string_of_const thy const)
   176       else I;
   177   in timeap (ensure_const' thy algebra funcgr const) end;
   178 
   179 fun merge_funcss thy algebra raw_funcss funcgr =
   180   let
   181     val funcss = raw_funcss
   182       |> resort_funcss thy algebra funcgr
   183       |> filter_out (can (Graph.get_node funcgr) o fst);
   184     fun typ_func c [] = Code.default_typ thy c
   185       | typ_func c (thms as (thm, _) :: _) = (snd o Code_Unit.head_func) thm;
   186     fun add_funcs (const, thms) =
   187       Graph.new_node (const, (typ_func const thms, thms));
   188     fun add_deps (funcs as (const, thms)) funcgr =
   189       let
   190         val deps = consts_of funcs;
   191         val insts = instances_of_consts thy algebra funcgr
   192           (fold_consts (insert (op =)) (map fst thms) []);
   193       in
   194         funcgr
   195         |> ensure_consts thy algebra insts
   196         |> fold (curry Graph.add_edge const) deps
   197         |> fold (curry Graph.add_edge const) insts
   198        end;
   199   in
   200     funcgr
   201     |> fold add_funcs funcss
   202     |> fold add_deps funcss
   203   end
   204 and ensure_consts thy algebra cs funcgr =
   205   let
   206     val auxgr = Graph.empty
   207       |> fold (snd oo ensure_const thy algebra funcgr) cs;
   208   in
   209     funcgr
   210     |> fold (merge_funcss thy algebra)
   211          (map (AList.make (Graph.get_node auxgr))
   212          (rev (Graph.strong_conn auxgr)))
   213   end;
   214 
   215 in
   216 
   217 (** retrieval interfaces **)
   218 
   219 val ensure_consts = ensure_consts;
   220 
   221 fun proto_eval thy cterm_of evaluator_fr evaluator proto_ct funcgr =
   222   let
   223     val ct = cterm_of proto_ct;
   224     val _ = Sign.no_vars (Syntax.pp_global thy) (Thm.term_of ct);
   225     val _ = Term.fold_types (Type.no_tvars #> K I) (Thm.term_of ct) ();
   226     fun consts_of t = fold_aterms (fn Const c_ty => cons c_ty | _ => I)
   227       t [];
   228     val algebra = Code.coregular_algebra thy;
   229     val thm = Code.preprocess_conv ct;
   230     val ct' = Thm.rhs_of thm;
   231     val t' = Thm.term_of ct';
   232     val consts = map fst (consts_of t');
   233     val funcgr' = ensure_consts thy algebra consts funcgr;
   234     val (t'', evaluator') = apsnd evaluator_fr (evaluator t');
   235     val consts' = consts_of t'';
   236     val dicts = instances_of_consts thy algebra funcgr' consts';
   237     val funcgr'' = ensure_consts thy algebra dicts funcgr';
   238   in (evaluator' thm funcgr'' t'', funcgr'') end;
   239 
   240 fun proto_eval_conv thy =
   241   let
   242     fun evaluator evaluator' thm1 funcgr t =
   243       let
   244         val thm2 = evaluator' funcgr t;
   245         val thm3 = Code.postprocess_conv (Thm.rhs_of thm2);
   246       in
   247         Thm.transitive thm1 (Thm.transitive thm2 thm3) handle THM _ =>
   248           error ("could not construct evaluation proof:\n"
   249           ^ (cat_lines o map Display.string_of_thm) [thm1, thm2, thm3])
   250       end;
   251   in proto_eval thy I evaluator end;
   252 
   253 fun proto_eval_term thy =
   254   let
   255     fun evaluator evaluator' _ funcgr t = evaluator' funcgr t;
   256   in proto_eval thy (Thm.cterm_of thy) evaluator end;
   257 
   258 end; (*local*)
   259 
   260 structure Funcgr = CodeDataFun
   261 (
   262   type T = T;
   263   val empty = Graph.empty;
   264   fun purge _ cs funcgr =
   265     Graph.del_nodes ((Graph.all_preds funcgr 
   266       o filter (can (Graph.get_node funcgr))) cs) funcgr;
   267 );
   268 
   269 fun make thy =
   270   Funcgr.change thy o ensure_consts thy (Code.coregular_algebra thy);
   271 
   272 fun eval_conv thy f =
   273   fst o Funcgr.change_yield thy o proto_eval_conv thy f;
   274 
   275 fun eval_term thy f =
   276   fst o Funcgr.change_yield thy o proto_eval_term thy f;
   277 
   278 
   279 (** diagnostic commands **)
   280 
   281 fun code_depgr thy consts =
   282   let
   283     val gr = make thy consts;
   284     val select = Graph.all_succs gr consts;
   285   in
   286     gr
   287     |> not (null consts) ? Graph.subgraph (member (op =) select) 
   288     |> Graph.map_nodes ((apsnd o map o apfst) (AxClass.overload thy))
   289   end;
   290 
   291 fun code_thms thy = Pretty.writeln o pretty thy o code_depgr thy;
   292 
   293 fun code_deps thy consts =
   294   let
   295     val gr = code_depgr thy consts;
   296     fun mk_entry (const, (_, (_, parents))) =
   297       let
   298         val name = Code_Unit.string_of_const thy const;
   299         val nameparents = map (Code_Unit.string_of_const thy) parents;
   300       in { name = name, ID = name, dir = "", unfold = true,
   301         path = "", parents = nameparents }
   302       end;
   303     val prgr = Graph.fold ((fn x => fn xs => xs @ [x]) o mk_entry) gr [];
   304   in Present.display_graph prgr end;
   305 
   306 local
   307 
   308 structure P = OuterParse
   309 and K = OuterKeyword
   310 
   311 fun code_thms_cmd thy = code_thms thy o op @ o Code_Name.read_const_exprs thy;
   312 fun code_deps_cmd thy = code_deps thy o op @ o Code_Name.read_const_exprs thy;
   313 
   314 in
   315 
   316 val _ =
   317   OuterSyntax.improper_command "code_thms" "print system of defining equations for code" OuterKeyword.diag
   318     (Scan.repeat P.term_group
   319       >> (fn cs => Toplevel.no_timing o Toplevel.unknown_theory
   320         o Toplevel.keep ((fn thy => code_thms_cmd thy cs) o Toplevel.theory_of)));
   321 
   322 val _ =
   323   OuterSyntax.improper_command "code_deps" "visualize dependencies of defining equations for code" OuterKeyword.diag
   324     (Scan.repeat P.term_group
   325       >> (fn cs => Toplevel.no_timing o Toplevel.unknown_theory
   326         o Toplevel.keep ((fn thy => code_deps_cmd thy cs) o Toplevel.theory_of)));
   327 
   328 end;
   329 
   330 end; (*struct*)