src/Tools/Code/code_thingol.ML
author haftmann
Wed, 29 Jul 2009 16:42:47 +0200
changeset 32270 3c395fc7ec5e
parent 32131 7913823f14e3
child 32350 5ef633275b15
permissions -rw-r--r--
abstractions: desymbolize name hint
     1 (*  Title:      Tools/code/code_thingol.ML
     2     Author:     Florian Haftmann, TU Muenchen
     3 
     4 Intermediate language ("Thin-gol") representing executable code.
     5 Representation and translation.
     6 *)
     7 
     8 infix 8 `%%;
     9 infix 4 `$;
    10 infix 4 `$$;
    11 infixr 3 `|=>;
    12 infixr 3 `|==>;
    13 
    14 signature BASIC_CODE_THINGOL =
    15 sig
    16   type vname = string;
    17   datatype dict =
    18       DictConst of string * dict list list
    19     | DictVar of string list * (vname * (int * int));
    20   datatype itype =
    21       `%% of string * itype list
    22     | ITyVar of vname;
    23   type const = string * ((itype list * dict list list) * itype list (*types of arguments*))
    24   datatype iterm =
    25       IConst of const
    26     | IVar of vname option
    27     | `$ of iterm * iterm
    28     | `|=> of (vname option * itype) * iterm
    29     | ICase of ((iterm * itype) * (iterm * iterm) list) * iterm;
    30         (*((term, type), [(selector pattern, body term )]), primitive term)*)
    31   val `$$ : iterm * iterm list -> iterm;
    32   val `|==> : (vname option * itype) list * iterm -> iterm;
    33   type typscheme = (vname * sort) list * itype;
    34 end;
    35 
    36 signature CODE_THINGOL =
    37 sig
    38   include BASIC_CODE_THINGOL
    39   val unfoldl: ('a -> ('a * 'b) option) -> 'a -> 'a * 'b list
    40   val unfoldr: ('a -> ('b * 'a) option) -> 'a -> 'b list * 'a
    41   val unfold_fun: itype -> itype list * itype
    42   val unfold_app: iterm -> iterm * iterm list
    43   val unfold_abs: iterm -> (vname option * itype) list * iterm
    44   val split_let: iterm -> (((iterm * itype) * iterm) * iterm) option
    45   val unfold_let: iterm -> ((iterm * itype) * iterm) list * iterm
    46   val split_pat_abs: iterm -> ((iterm * itype) * iterm) option
    47   val unfold_pat_abs: iterm -> (iterm * itype) list * iterm
    48   val unfold_const_app: iterm -> (const * iterm list) option
    49   val eta_expand: int -> const * iterm list -> iterm
    50   val contains_dictvar: iterm -> bool
    51   val locally_monomorphic: iterm -> bool
    52   val add_constnames: iterm -> string list -> string list
    53   val fold_varnames: (string -> 'a -> 'a) -> iterm -> 'a -> 'a
    54 
    55   type naming
    56   val empty_naming: naming
    57   val lookup_class: naming -> class -> string option
    58   val lookup_classrel: naming -> class * class -> string option
    59   val lookup_tyco: naming -> string -> string option
    60   val lookup_instance: naming -> class * string -> string option
    61   val lookup_const: naming -> string -> string option
    62   val ensure_declared_const: theory -> string -> naming -> string * naming
    63 
    64   datatype stmt =
    65       NoStmt
    66     | Fun of string * (typscheme * ((iterm list * iterm) * (thm * bool)) list)
    67     | Datatype of string * ((vname * sort) list * (string * itype list) list)
    68     | Datatypecons of string * string
    69     | Class of class * (vname * ((class * string) list * (string * itype) list))
    70     | Classrel of class * class
    71     | Classparam of string * class
    72     | Classinst of (class * (string * (vname * sort) list))
    73           * ((class * (string * (string * dict list list))) list
    74         * ((string * const) * (thm * bool)) list)
    75   type program = stmt Graph.T
    76   val empty_funs: program -> string list
    77   val map_terms_bottom_up: (iterm -> iterm) -> iterm -> iterm
    78   val map_terms_stmt: (iterm -> iterm) -> stmt -> stmt
    79   val is_cons: program -> string -> bool
    80   val contr_classparam_typs: program -> string -> itype option list
    81 
    82   val read_const_exprs: theory -> string list -> string list * string list
    83   val consts_program: theory -> string list -> string list * (naming * program)
    84   val cached_program: theory -> naming * program
    85   val eval_conv: theory
    86     -> (naming -> program -> ((string * sort) list * typscheme) * iterm -> string list -> cterm -> thm)
    87     -> cterm -> thm
    88   val eval: theory -> ((term -> term) -> 'a -> 'a)
    89     -> (naming -> program -> ((string * sort) list * typscheme) * iterm -> string list -> 'a)
    90     -> term -> 'a
    91 end;
    92 
    93 structure Code_Thingol: CODE_THINGOL =
    94 struct
    95 
    96 (** auxiliary **)
    97 
    98 fun unfoldl dest x =
    99   case dest x
   100    of NONE => (x, [])
   101     | SOME (x1, x2) =>
   102         let val (x', xs') = unfoldl dest x1 in (x', xs' @ [x2]) end;
   103 
   104 fun unfoldr dest x =
   105   case dest x
   106    of NONE => ([], x)
   107     | SOME (x1, x2) =>
   108         let val (xs', x') = unfoldr dest x2 in (x1::xs', x') end;
   109 
   110 
   111 (** language core - types, terms **)
   112 
   113 type vname = string;
   114 
   115 datatype dict =
   116     DictConst of string * dict list list
   117   | DictVar of string list * (vname * (int * int));
   118 
   119 datatype itype =
   120     `%% of string * itype list
   121   | ITyVar of vname;
   122 
   123 type const = string * ((itype list * dict list list) * itype list (*types of arguments*))
   124 
   125 datatype iterm =
   126     IConst of const
   127   | IVar of vname option
   128   | `$ of iterm * iterm
   129   | `|=> of (vname option * itype) * iterm
   130   | ICase of ((iterm * itype) * (iterm * iterm) list) * iterm;
   131     (*see also signature*)
   132 
   133 val op `$$ = Library.foldl (op `$);
   134 val op `|==> = Library.foldr (op `|=>);
   135 
   136 val unfold_app = unfoldl
   137   (fn op `$ t => SOME t
   138     | _ => NONE);
   139 
   140 val unfold_abs = unfoldr
   141   (fn op `|=> t => SOME t
   142     | _ => NONE);
   143 
   144 val split_let = 
   145   (fn ICase (((td, ty), [(p, t)]), _) => SOME (((p, ty), td), t)
   146     | _ => NONE);
   147 
   148 val unfold_let = unfoldr split_let;
   149 
   150 fun unfold_const_app t =
   151  case unfold_app t
   152   of (IConst c, ts) => SOME (c, ts)
   153    | _ => NONE;
   154 
   155 fun add_constnames (IConst (c, _)) = insert (op =) c
   156   | add_constnames (IVar _) = I
   157   | add_constnames (t1 `$ t2) = add_constnames t1 #> add_constnames t2
   158   | add_constnames (_ `|=> t) = add_constnames t
   159   | add_constnames (ICase (((t, _), ds), _)) = add_constnames t
   160       #> fold (fn (pat, body) => add_constnames pat #> add_constnames body) ds;
   161 
   162 fun fold_varnames f =
   163   let
   164     fun fold_aux add f =
   165       let
   166         fun fold_term _ (IConst _) = I
   167           | fold_term vs (IVar (SOME v)) = if member (op =) vs v then I else f v
   168           | fold_term _ (IVar NONE) = I
   169           | fold_term vs (t1 `$ t2) = fold_term vs t1 #> fold_term vs t2
   170           | fold_term vs ((SOME v, _) `|=> t) = fold_term (insert (op =) v vs) t
   171           | fold_term vs ((NONE, _) `|=> t) = fold_term vs t
   172           | fold_term vs (ICase (((t, _), ds), _)) = fold_term vs t #> fold (fold_case vs) ds
   173         and fold_case vs (p, t) = fold_term (add p vs) t;
   174       in fold_term [] end;
   175     fun add t = fold_aux add (insert (op =)) t;
   176   in fold_aux add f end;
   177 
   178 fun exists_var t v = fold_varnames (fn w => fn b => v = w orelse b) t false;
   179 
   180 fun split_pat_abs ((NONE, ty) `|=> t) = SOME ((IVar NONE, ty), t)
   181   | split_pat_abs ((SOME v, ty) `|=> t) = SOME (case t
   182      of ICase (((IVar (SOME w), _), [(p, t')]), _) =>
   183           if v = w andalso (exists_var p v orelse not (exists_var t' v))
   184           then ((p, ty), t')
   185           else ((IVar (SOME v), ty), t)
   186       | _ => ((IVar (SOME v), ty), t))
   187   | split_pat_abs _ = NONE;
   188 
   189 val unfold_pat_abs = unfoldr split_pat_abs;
   190 
   191 fun unfold_abs_eta [] t = ([], t)
   192   | unfold_abs_eta (_ :: tys) (v_ty `|=> t) =
   193       let
   194         val (vs_tys, t') = unfold_abs_eta tys t;
   195       in (v_ty :: vs_tys, t') end
   196   | unfold_abs_eta tys t =
   197       let
   198         val ctxt = fold_varnames Name.declare t Name.context;
   199         val vs_tys = (map o apfst) SOME (Name.names ctxt "a" tys);
   200       in (vs_tys, t `$$ map (IVar o fst) vs_tys) end;
   201 
   202 fun eta_expand k (c as (_, (_, tys)), ts) =
   203   let
   204     val j = length ts;
   205     val l = k - j;
   206     val ctxt = (fold o fold_varnames) Name.declare ts Name.context;
   207     val vs_tys = (map o apfst) SOME
   208       (Name.names ctxt "a" ((curry Library.take l o curry Library.drop j) tys));
   209   in vs_tys `|==> IConst c `$$ ts @ map (IVar o fst) vs_tys end;
   210 
   211 fun contains_dictvar t =
   212   let
   213     fun cont_dict (DictConst (_, dss)) = (exists o exists) cont_dict dss
   214       | cont_dict (DictVar _) = true;
   215     fun cont_term (IConst (_, ((_, dss), _))) = (exists o exists) cont_dict dss
   216       | cont_term (IVar _) = false
   217       | cont_term (t1 `$ t2) = cont_term t1 orelse cont_term t2
   218       | cont_term (_ `|=> t) = cont_term t
   219       | cont_term (ICase (_, t)) = cont_term t;
   220   in cont_term t end;
   221   
   222 fun locally_monomorphic (IConst _) = false
   223   | locally_monomorphic (IVar _) = true
   224   | locally_monomorphic (t `$ _) = locally_monomorphic t
   225   | locally_monomorphic (_ `|=> t) = locally_monomorphic t
   226   | locally_monomorphic (ICase ((_, ds), _)) = exists (locally_monomorphic o snd) ds;
   227 
   228 
   229 (** namings **)
   230 
   231 (* policies *)
   232 
   233 local
   234   fun thyname_of thy f x = the (AList.lookup (op =) (f x) Markup.theory_nameN);
   235   fun thyname_of_class thy =
   236     thyname_of thy (ProofContext.query_class (ProofContext.init thy));
   237   fun thyname_of_tyco thy =
   238     thyname_of thy (Type.the_tags (Sign.tsig_of thy));
   239   fun thyname_of_instance thy inst = case AxClass.arity_property thy inst Markup.theory_nameN
   240    of [] => error ("no such instance: " ^ quote (snd inst ^ " :: " ^ fst inst))
   241     | thyname :: _ => thyname;
   242   fun thyname_of_const thy c = case AxClass.class_of_param thy c
   243    of SOME class => thyname_of_class thy class
   244     | NONE => (case Code.get_datatype_of_constr thy c
   245        of SOME dtco => thyname_of_tyco thy dtco
   246         | NONE => thyname_of thy (Consts.the_tags (Sign.consts_of thy)) c);
   247   fun purify_base "op &" = "and"
   248     | purify_base "op |" = "or"
   249     | purify_base "op -->" = "implies"
   250     | purify_base "op :" = "member"
   251     | purify_base "op =" = "eq"
   252     | purify_base "*" = "product"
   253     | purify_base "+" = "sum"
   254     | purify_base s = Name.desymbolize false s;
   255   fun namify thy get_basename get_thyname name =
   256     let
   257       val prefix = get_thyname thy name;
   258       val base = (purify_base o get_basename) name;
   259     in Long_Name.append prefix base end;
   260 in
   261 
   262 fun namify_class thy = namify thy Long_Name.base_name thyname_of_class;
   263 fun namify_classrel thy = namify thy (fn (class1, class2) => 
   264   Long_Name.base_name class2 ^ "_" ^ Long_Name.base_name class1) (fn thy => thyname_of_class thy o fst);
   265   (*order fits nicely with composed projections*)
   266 fun namify_tyco thy "fun" = "Pure.fun"
   267   | namify_tyco thy tyco = namify thy Long_Name.base_name thyname_of_tyco tyco;
   268 fun namify_instance thy = namify thy (fn (class, tyco) => 
   269   Long_Name.base_name class ^ "_" ^ Long_Name.base_name tyco) thyname_of_instance;
   270 fun namify_const thy = namify thy Long_Name.base_name thyname_of_const;
   271 
   272 end; (* local *)
   273 
   274 
   275 (* data *)
   276 
   277 datatype naming = Naming of {
   278   class: class Symtab.table * Name.context,
   279   classrel: string Symreltab.table * Name.context,
   280   tyco: string Symtab.table * Name.context,
   281   instance: string Symreltab.table * Name.context,
   282   const: string Symtab.table * Name.context
   283 }
   284 
   285 fun dest_Naming (Naming naming) = naming;
   286 
   287 val empty_naming = Naming {
   288   class = (Symtab.empty, Name.context),
   289   classrel = (Symreltab.empty, Name.context),
   290   tyco = (Symtab.empty, Name.context),
   291   instance = (Symreltab.empty, Name.context),
   292   const = (Symtab.empty, Name.context)
   293 };
   294 
   295 local
   296   fun mk_naming (class, classrel, tyco, instance, const) =
   297     Naming { class = class, classrel = classrel,
   298       tyco = tyco, instance = instance, const = const };
   299   fun map_naming f (Naming { class, classrel, tyco, instance, const }) =
   300     mk_naming (f (class, classrel, tyco, instance, const));
   301 in
   302   fun map_class f = map_naming
   303     (fn (class, classrel, tyco, inst, const) =>
   304       (f class, classrel, tyco, inst, const));
   305   fun map_classrel f = map_naming
   306     (fn (class, classrel, tyco, inst, const) =>
   307       (class, f classrel, tyco, inst, const));
   308   fun map_tyco f = map_naming
   309     (fn (class, classrel, tyco, inst, const) =>
   310       (class, classrel, f tyco, inst, const));
   311   fun map_instance f = map_naming
   312     (fn (class, classrel, tyco, inst, const) =>
   313       (class, classrel, tyco, f inst, const));
   314   fun map_const f = map_naming
   315     (fn (class, classrel, tyco, inst, const) =>
   316       (class, classrel, tyco, inst, f const));
   317 end; (*local*)
   318 
   319 fun add_variant update (thing, name) (tab, used) =
   320   let
   321     val (name', used') = yield_singleton Name.variants name used;
   322     val tab' = update (thing, name') tab;
   323   in (tab', used') end;
   324 
   325 fun declare thy mapp lookup update namify thing =
   326   mapp (add_variant update (thing, namify thy thing))
   327   #> `(fn naming => the (lookup naming thing));
   328 
   329 
   330 (* lookup and declare *)
   331 
   332 local
   333 
   334 val suffix_class = "class";
   335 val suffix_classrel = "classrel"
   336 val suffix_tyco = "tyco";
   337 val suffix_instance = "inst";
   338 val suffix_const = "const";
   339 
   340 fun add_suffix nsp NONE = NONE
   341   | add_suffix nsp (SOME name) = SOME (Long_Name.append name nsp);
   342 
   343 in
   344 
   345 val lookup_class = add_suffix suffix_class
   346   oo Symtab.lookup o fst o #class o dest_Naming;
   347 val lookup_classrel = add_suffix suffix_classrel
   348   oo Symreltab.lookup o fst o #classrel o dest_Naming;
   349 val lookup_tyco = add_suffix suffix_tyco
   350   oo Symtab.lookup o fst o #tyco o dest_Naming;
   351 val lookup_instance = add_suffix suffix_instance
   352   oo Symreltab.lookup o fst o #instance o dest_Naming;
   353 val lookup_const = add_suffix suffix_const
   354   oo Symtab.lookup o fst o #const o dest_Naming;
   355 
   356 fun declare_class thy = declare thy map_class
   357   lookup_class Symtab.update_new namify_class;
   358 fun declare_classrel thy = declare thy map_classrel
   359   lookup_classrel Symreltab.update_new namify_classrel;
   360 fun declare_tyco thy = declare thy map_tyco
   361   lookup_tyco Symtab.update_new namify_tyco;
   362 fun declare_instance thy = declare thy map_instance
   363   lookup_instance Symreltab.update_new namify_instance;
   364 fun declare_const thy = declare thy map_const
   365   lookup_const Symtab.update_new namify_const;
   366 
   367 fun ensure_declared_const thy const naming =
   368   case lookup_const naming const
   369    of SOME const' => (const', naming)
   370     | NONE => declare_const thy const naming;
   371 
   372 val unfold_fun = unfoldr
   373   (fn "Pure.fun.tyco" `%% [ty1, ty2] => SOME (ty1, ty2)
   374     | _ => NONE); (*depends on suffix_tyco and namify_tyco!*)
   375 
   376 end; (* local *)
   377 
   378 
   379 (** statements, abstract programs **)
   380 
   381 type typscheme = (vname * sort) list * itype;
   382 datatype stmt =
   383     NoStmt
   384   | Fun of string * (typscheme * ((iterm list * iterm) * (thm * bool)) list)
   385   | Datatype of string * ((vname * sort) list * (string * itype list) list)
   386   | Datatypecons of string * string
   387   | Class of class * (vname * ((class * string) list * (string * itype) list))
   388   | Classrel of class * class
   389   | Classparam of string * class
   390   | Classinst of (class * (string * (vname * sort) list))
   391         * ((class * (string * (string * dict list list))) list
   392       * ((string * const) * (thm * bool)) list);
   393 
   394 type program = stmt Graph.T;
   395 
   396 fun empty_funs program =
   397   Graph.fold (fn (name, (Fun (c, (_, [])), _)) => cons c
   398                | _ => I) program [];
   399 
   400 fun map_terms_bottom_up f (t as IConst _) = f t
   401   | map_terms_bottom_up f (t as IVar _) = f t
   402   | map_terms_bottom_up f (t1 `$ t2) = f
   403       (map_terms_bottom_up f t1 `$ map_terms_bottom_up f t2)
   404   | map_terms_bottom_up f ((v, ty) `|=> t) = f
   405       ((v, ty) `|=> map_terms_bottom_up f t)
   406   | map_terms_bottom_up f (ICase (((t, ty), ps), t0)) = f
   407       (ICase (((map_terms_bottom_up f t, ty), (map o pairself)
   408         (map_terms_bottom_up f) ps), map_terms_bottom_up f t0));
   409 
   410 fun map_terms_stmt f NoStmt = NoStmt
   411   | map_terms_stmt f (Fun (c, (tysm, eqs))) = Fun (c, (tysm, (map o apfst)
   412       (fn (ts, t) => (map f ts, f t)) eqs))
   413   | map_terms_stmt f (stmt as Datatype _) = stmt
   414   | map_terms_stmt f (stmt as Datatypecons _) = stmt
   415   | map_terms_stmt f (stmt as Class _) = stmt
   416   | map_terms_stmt f (stmt as Classrel _) = stmt
   417   | map_terms_stmt f (stmt as Classparam _) = stmt
   418   | map_terms_stmt f (Classinst (arity, (superarities, classparms))) =
   419       Classinst (arity, (superarities, (map o apfst o apsnd) (fn const =>
   420         case f (IConst const) of IConst const' => const') classparms));
   421 
   422 fun is_cons program name = case Graph.get_node program name
   423  of Datatypecons _ => true
   424   | _ => false;
   425 
   426 fun contr_classparam_typs program name = case Graph.get_node program name
   427  of Classparam (_, class) => let
   428         val Class (_, (_, (_, params))) = Graph.get_node program class;
   429         val SOME ty = AList.lookup (op =) params name;
   430         val (tys, res_ty) = unfold_fun ty;
   431         fun no_tyvar (_ `%% tys) = forall no_tyvar tys
   432           | no_tyvar (ITyVar _) = false;
   433       in if no_tyvar res_ty
   434         then map (fn ty => if no_tyvar ty then NONE else SOME ty) tys
   435         else []
   436       end
   437   | _ => [];
   438 
   439 
   440 (** translation kernel **)
   441 
   442 (* generic mechanisms *)
   443 
   444 fun ensure_stmt lookup declare generate thing (dep, (naming, program)) =
   445   let
   446     fun add_dep name = case dep of NONE => I
   447       | SOME dep => Graph.add_edge (dep, name);
   448     val (name, naming') = case lookup naming thing
   449      of SOME name => (name, naming)
   450       | NONE => declare thing naming;
   451   in case try (Graph.get_node program) name
   452    of SOME stmt => program
   453         |> add_dep name
   454         |> pair naming'
   455         |> pair dep
   456         |> pair name
   457     | NONE => program
   458         |> Graph.default_node (name, NoStmt)
   459         |> add_dep name
   460         |> pair naming'
   461         |> curry generate (SOME name)
   462         ||> snd
   463         |-> (fn stmt => (apsnd o Graph.map_node name) (K stmt))
   464         |> pair dep
   465         |> pair name
   466   end;
   467 
   468 fun not_wellsorted thy thm ty sort e =
   469   let
   470     val err_class = Sorts.class_error (Syntax.pp_global thy) e;
   471     val err_thm = case thm
   472      of SOME thm => "\n(in code equation " ^ Display.string_of_thm_global thy thm ^ ")" | NONE => "";
   473     val err_typ = "Type " ^ Syntax.string_of_typ_global thy ty ^ " not of sort "
   474       ^ Syntax.string_of_sort_global thy sort;
   475   in error ("Wellsortedness error" ^ err_thm ^ ":\n" ^ err_typ ^ "\n" ^ err_class) end;
   476 
   477 
   478 (* translation *)
   479 
   480 fun ensure_tyco thy algbr funcgr tyco =
   481   let
   482     val stmt_datatype =
   483       let
   484         val (vs, cos) = Code.get_datatype thy tyco;
   485       in
   486         fold_map (translate_tyvar_sort thy algbr funcgr) vs
   487         ##>> fold_map (fn (c, tys) =>
   488           ensure_const thy algbr funcgr c
   489           ##>> fold_map (translate_typ thy algbr funcgr) tys) cos
   490         #>> (fn info => Datatype (tyco, info))
   491       end;
   492   in ensure_stmt lookup_tyco (declare_tyco thy) stmt_datatype tyco end
   493 and ensure_const thy algbr funcgr c =
   494   let
   495     fun stmt_datatypecons tyco =
   496       ensure_tyco thy algbr funcgr tyco
   497       #>> (fn tyco => Datatypecons (c, tyco));
   498     fun stmt_classparam class =
   499       ensure_class thy algbr funcgr class
   500       #>> (fn class => Classparam (c, class));
   501     fun stmt_fun ((vs, ty), raw_thms) =
   502       let
   503         val thms = if null (Term.add_tfreesT ty []) orelse (null o fst o strip_type) ty
   504           then raw_thms
   505           else (map o apfst) (Code.expand_eta thy 1) raw_thms;
   506       in
   507         fold_map (translate_tyvar_sort thy algbr funcgr) vs
   508         ##>> translate_typ thy algbr funcgr ty
   509         ##>> fold_map (translate_eq thy algbr funcgr) thms
   510         #>> (fn info => Fun (c, info))
   511       end;
   512     val stmt_const = case Code.get_datatype_of_constr thy c
   513      of SOME tyco => stmt_datatypecons tyco
   514       | NONE => (case AxClass.class_of_param thy c
   515          of SOME class => stmt_classparam class
   516           | NONE => stmt_fun (Code_Preproc.typ funcgr c, Code_Preproc.eqns funcgr c))
   517   in ensure_stmt lookup_const (declare_const thy) stmt_const c end
   518 and ensure_class thy (algbr as (_, algebra)) funcgr class =
   519   let
   520     val superclasses = (Sorts.minimize_sort algebra o Sorts.super_classes algebra) class;
   521     val cs = #params (AxClass.get_info thy class);
   522     val stmt_class =
   523       fold_map (fn superclass => ensure_class thy algbr funcgr superclass
   524         ##>> ensure_classrel thy algbr funcgr (class, superclass)) superclasses
   525       ##>> fold_map (fn (c, ty) => ensure_const thy algbr funcgr c
   526         ##>> translate_typ thy algbr funcgr ty) cs
   527       #>> (fn info => Class (class, (unprefix "'" Name.aT, info)))
   528   in ensure_stmt lookup_class (declare_class thy) stmt_class class end
   529 and ensure_classrel thy algbr funcgr (subclass, superclass) =
   530   let
   531     val stmt_classrel =
   532       ensure_class thy algbr funcgr subclass
   533       ##>> ensure_class thy algbr funcgr superclass
   534       #>> Classrel;
   535   in ensure_stmt lookup_classrel (declare_classrel thy) stmt_classrel (subclass, superclass) end
   536 and ensure_inst thy (algbr as (_, algebra)) funcgr (class, tyco) =
   537   let
   538     val superclasses = (Sorts.minimize_sort algebra o Sorts.super_classes algebra) class;
   539     val classparams = these (try (#params o AxClass.get_info thy) class);
   540     val vs = Name.names Name.context "'a" (Sorts.mg_domain algebra tyco [class]);
   541     val sorts' = Sorts.mg_domain (Sign.classes_of thy) tyco [class];
   542     val vs' = map2 (fn (v, sort1) => fn sort2 => (v,
   543       Sorts.inter_sort (Sign.classes_of thy) (sort1, sort2))) vs sorts';
   544     val arity_typ = Type (tyco, map TFree vs);
   545     val arity_typ' = Type (tyco, map (fn (v, sort) => TVar ((v, 0), sort)) vs');
   546     fun translate_superarity superclass =
   547       ensure_class thy algbr funcgr superclass
   548       ##>> ensure_classrel thy algbr funcgr (class, superclass)
   549       ##>> translate_dicts thy algbr funcgr NONE (arity_typ, [superclass])
   550       #>> (fn ((superclass, classrel), [DictConst (inst, dss)]) =>
   551             (superclass, (classrel, (inst, dss))));
   552     fun translate_classparam_inst (c, ty) =
   553       let
   554         val c_inst = Const (c, map_type_tfree (K arity_typ') ty);
   555         val thm = AxClass.unoverload_conv thy (Thm.cterm_of thy c_inst);
   556         val c_ty = (apsnd Logic.unvarifyT o dest_Const o snd
   557           o Logic.dest_equals o Thm.prop_of) thm;
   558       in
   559         ensure_const thy algbr funcgr c
   560         ##>> translate_const thy algbr funcgr (SOME thm) c_ty
   561         #>> (fn (c, IConst c_inst) => ((c, c_inst), (thm, true)))
   562       end;
   563     val stmt_inst =
   564       ensure_class thy algbr funcgr class
   565       ##>> ensure_tyco thy algbr funcgr tyco
   566       ##>> fold_map (translate_tyvar_sort thy algbr funcgr) vs
   567       ##>> fold_map translate_superarity superclasses
   568       ##>> fold_map translate_classparam_inst classparams
   569       #>> (fn ((((class, tyco), arity), superarities), classparams) =>
   570              Classinst ((class, (tyco, arity)), (superarities, classparams)));
   571   in ensure_stmt lookup_instance (declare_instance thy) stmt_inst (class, tyco) end
   572 and translate_typ thy algbr funcgr (TFree (v, _)) =
   573       pair (ITyVar (unprefix "'" v))
   574   | translate_typ thy algbr funcgr (Type (tyco, tys)) =
   575       ensure_tyco thy algbr funcgr tyco
   576       ##>> fold_map (translate_typ thy algbr funcgr) tys
   577       #>> (fn (tyco, tys) => tyco `%% tys)
   578 and translate_term thy algbr funcgr thm (Const (c, ty)) =
   579       translate_app thy algbr funcgr thm ((c, ty), [])
   580   | translate_term thy algbr funcgr thm (Free (v, _)) =
   581       pair (IVar (SOME v))
   582   | translate_term thy algbr funcgr thm (Abs (v, ty, t)) =
   583       let
   584         val (v', t') = Syntax.variant_abs (Name.desymbolize false v, ty, t);
   585         val v'' = if member (op =) (Term.add_free_names t' []) v'
   586           then SOME v' else NONE
   587       in
   588         translate_typ thy algbr funcgr ty
   589         ##>> translate_term thy algbr funcgr thm t'
   590         #>> (fn (ty, t) => (v'', ty) `|=> t)
   591       end
   592   | translate_term thy algbr funcgr thm (t as _ $ _) =
   593       case strip_comb t
   594        of (Const (c, ty), ts) =>
   595             translate_app thy algbr funcgr thm ((c, ty), ts)
   596         | (t', ts) =>
   597             translate_term thy algbr funcgr thm t'
   598             ##>> fold_map (translate_term thy algbr funcgr thm) ts
   599             #>> (fn (t, ts) => t `$$ ts)
   600 and translate_eq thy algbr funcgr (thm, proper) =
   601   let
   602     val (args, rhs) = (apfst (snd o strip_comb) o Logic.dest_equals
   603       o Logic.unvarify o prop_of) thm;
   604   in
   605     fold_map (translate_term thy algbr funcgr (SOME thm)) args
   606     ##>> translate_term thy algbr funcgr (SOME thm) rhs
   607     #>> rpair (thm, proper)
   608   end
   609 and translate_const thy algbr funcgr thm (c, ty) =
   610   let
   611     val tys = Sign.const_typargs thy (c, ty);
   612     val sorts = (map snd o fst o Code_Preproc.typ funcgr) c;
   613     val tys_args = (fst o Term.strip_type) ty;
   614   in
   615     ensure_const thy algbr funcgr c
   616     ##>> fold_map (translate_typ thy algbr funcgr) tys
   617     ##>> fold_map (translate_dicts thy algbr funcgr thm) (tys ~~ sorts)
   618     ##>> fold_map (translate_typ thy algbr funcgr) tys_args
   619     #>> (fn (((c, tys), iss), tys_args) => IConst (c, ((tys, iss), tys_args)))
   620   end
   621 and translate_app_const thy algbr funcgr thm (c_ty, ts) =
   622   translate_const thy algbr funcgr thm c_ty
   623   ##>> fold_map (translate_term thy algbr funcgr thm) ts
   624   #>> (fn (t, ts) => t `$$ ts)
   625 and translate_case thy algbr funcgr thm (num_args, (t_pos, case_pats)) (c_ty, ts) =
   626   let
   627     fun arg_types num_args ty = (fst o chop num_args o fst o strip_type) ty;
   628     val tys = arg_types num_args (snd c_ty);
   629     val ty = nth tys t_pos;
   630     fun mk_constr c t = let val n = Code.args_number thy c
   631       in ((c, arg_types n (fastype_of t) ---> ty), n) end;
   632     val constrs = if null case_pats then []
   633       else map2 mk_constr case_pats (nth_drop t_pos ts);
   634     fun casify naming constrs ty ts =
   635       let
   636         val undefineds = map_filter (lookup_const naming) (Code.undefineds thy);
   637         fun collapse_clause vs_map ts body =
   638           let
   639           in case body
   640            of IConst (c, _) => if member (op =) undefineds c
   641                 then []
   642                 else [(ts, body)]
   643             | ICase (((IVar (SOME v), _), subclauses), _) =>
   644                 if forall (fn (pat', body') => exists_var pat' v
   645                   orelse not (exists_var body' v)) subclauses
   646                 then case AList.lookup (op =) vs_map v
   647                  of SOME i => maps (fn (pat', body') =>
   648                       collapse_clause (AList.delete (op =) v vs_map)
   649                         (nth_map i (K pat') ts) body') subclauses
   650                   | NONE => [(ts, body)]
   651                 else [(ts, body)]
   652             | _ => [(ts, body)]
   653           end;
   654         fun mk_clause mk tys t =
   655           let
   656             val (vs, body) = unfold_abs_eta tys t;
   657             val vs_map = fold_index (fn (i, (SOME v, _)) => cons (v, i) | _ => I) vs [];
   658             val ts = map (IVar o fst) vs;
   659           in map mk (collapse_clause vs_map ts body) end;
   660         val t = nth ts t_pos;
   661         val ts_clause = nth_drop t_pos ts;
   662         val clauses = if null case_pats
   663           then mk_clause (fn ([t], body) => (t, body)) [ty] (the_single ts_clause)
   664           else maps (fn ((constr as IConst (_, (_, tys)), n), t) =>
   665             mk_clause (fn (ts, body) => (constr `$$ ts, body)) (curry Library.take n tys) t)
   666               (constrs ~~ ts_clause);
   667       in ((t, ty), clauses) end;
   668   in
   669     translate_const thy algbr funcgr thm c_ty
   670     ##>> fold_map (fn (constr, n) => translate_const thy algbr funcgr thm constr #>> rpair n) constrs
   671     ##>> translate_typ thy algbr funcgr ty
   672     ##>> fold_map (translate_term thy algbr funcgr thm) ts
   673     #-> (fn (((t, constrs), ty), ts) =>
   674       `(fn (_, (naming, _)) => ICase (casify naming constrs ty ts, t `$$ ts)))
   675   end
   676 and translate_app_case thy algbr funcgr thm (case_scheme as (num_args, _)) ((c, ty), ts) =
   677   if length ts < num_args then
   678     let
   679       val k = length ts;
   680       val tys = (curry Library.take (num_args - k) o curry Library.drop k o fst o strip_type) ty;
   681       val ctxt = (fold o fold_aterms) Term.declare_term_frees ts Name.context;
   682       val vs = Name.names ctxt "a" tys;
   683     in
   684       fold_map (translate_typ thy algbr funcgr) tys
   685       ##>> translate_case thy algbr funcgr thm case_scheme ((c, ty), ts @ map Free vs)
   686       #>> (fn (tys, t) => map2 (fn (v, _) => pair (SOME v)) vs tys `|==> t)
   687     end
   688   else if length ts > num_args then
   689     translate_case thy algbr funcgr thm case_scheme ((c, ty), Library.take (num_args, ts))
   690     ##>> fold_map (translate_term thy algbr funcgr thm) (Library.drop (num_args, ts))
   691     #>> (fn (t, ts) => t `$$ ts)
   692   else
   693     translate_case thy algbr funcgr thm case_scheme ((c, ty), ts)
   694 and translate_app thy algbr funcgr thm (c_ty_ts as ((c, _), _)) =
   695   case Code.get_case_scheme thy c
   696    of SOME case_scheme => translate_app_case thy algbr funcgr thm case_scheme c_ty_ts
   697     | NONE => translate_app_const thy algbr funcgr thm c_ty_ts
   698 and translate_tyvar_sort thy (algbr as (proj_sort, _)) funcgr (v, sort) =
   699   fold_map (ensure_class thy algbr funcgr) (proj_sort sort)
   700   #>> (fn sort => (unprefix "'" v, sort))
   701 and translate_dicts thy (algbr as (proj_sort, algebra)) funcgr thm (ty, sort) =
   702   let
   703     val pp = Syntax.pp_global thy;
   704     datatype typarg =
   705         Global of (class * string) * typarg list list
   706       | Local of (class * class) list * (string * (int * sort));
   707     fun class_relation (Global ((_, tyco), yss), _) class =
   708           Global ((class, tyco), yss)
   709       | class_relation (Local (classrels, v), subclass) superclass =
   710           Local ((subclass, superclass) :: classrels, v);
   711     fun type_constructor tyco yss class =
   712       Global ((class, tyco), (map o map) fst yss);
   713     fun type_variable (TFree (v, sort)) =
   714       let
   715         val sort' = proj_sort sort;
   716       in map_index (fn (n, class) => (Local ([], (v, (n, sort'))), class)) sort' end;
   717     val typargs = Sorts.of_sort_derivation pp algebra
   718       {class_relation = class_relation, type_constructor = type_constructor,
   719        type_variable = type_variable} (ty, proj_sort sort)
   720       handle Sorts.CLASS_ERROR e => not_wellsorted thy thm ty sort e;
   721     fun mk_dict (Global (inst, yss)) =
   722           ensure_inst thy algbr funcgr inst
   723           ##>> (fold_map o fold_map) mk_dict yss
   724           #>> (fn (inst, dss) => DictConst (inst, dss))
   725       | mk_dict (Local (classrels, (v, (n, sort)))) =
   726           fold_map (ensure_classrel thy algbr funcgr) classrels
   727           #>> (fn classrels => DictVar (classrels, (unprefix "'" v, (n, length sort))))
   728   in fold_map mk_dict typargs end;
   729 
   730 
   731 (* store *)
   732 
   733 structure Program = Code_Data_Fun
   734 (
   735   type T = naming * program;
   736   val empty = (empty_naming, Graph.empty);
   737   fun purge thy cs (naming, program) =
   738     let
   739       val names_delete = cs
   740         |> map_filter (lookup_const naming)
   741         |> filter (can (Graph.get_node program))
   742         |> Graph.all_preds program;
   743       val program' = Graph.del_nodes names_delete program;
   744     in (naming, program') end;
   745 );
   746 
   747 val cached_program = Program.get;
   748 
   749 fun invoke_generation thy (algebra, funcgr) f name =
   750   Program.change_yield thy (fn naming_program => (NONE, naming_program)
   751     |> f thy algebra funcgr name
   752     |-> (fn name => fn (_, naming_program) => (name, naming_program)));
   753 
   754 
   755 (* program generation *)
   756 
   757 fun consts_program thy cs =
   758   let
   759     fun project_consts cs (naming, program) =
   760       let
   761         val cs_all = Graph.all_succs program cs;
   762       in (cs, (naming, Graph.subgraph (member (op =) cs_all) program)) end;
   763     fun generate_consts thy algebra funcgr =
   764       fold_map (ensure_const thy algebra funcgr);
   765   in
   766     invoke_generation thy (Code_Preproc.obtain thy cs []) generate_consts cs
   767     |-> project_consts
   768   end;
   769 
   770 
   771 (* value evaluation *)
   772 
   773 fun ensure_value thy algbr funcgr t =
   774   let
   775     val ty = fastype_of t;
   776     val vs = fold_term_types (K (fold_atyps (insert (eq_fst op =)
   777       o dest_TFree))) t [];
   778     val stmt_value =
   779       fold_map (translate_tyvar_sort thy algbr funcgr) vs
   780       ##>> translate_typ thy algbr funcgr ty
   781       ##>> translate_term thy algbr funcgr NONE t
   782       #>> (fn ((vs, ty), t) => Fun
   783         (Term.dummy_patternN, ((vs, ty), [(([], t), (Drule.dummy_thm, true))])));
   784     fun term_value (dep, (naming, program1)) =
   785       let
   786         val Fun (_, (vs_ty, [(([], t), _)])) =
   787           Graph.get_node program1 Term.dummy_patternN;
   788         val deps = Graph.imm_succs program1 Term.dummy_patternN;
   789         val program2 = Graph.del_nodes [Term.dummy_patternN] program1;
   790         val deps_all = Graph.all_succs program2 deps;
   791         val program3 = Graph.subgraph (member (op =) deps_all) program2;
   792       in (((naming, program3), ((vs_ty, t), deps)), (dep, (naming, program2))) end;
   793   in
   794     ensure_stmt ((K o K) NONE) pair stmt_value Term.dummy_patternN
   795     #> snd
   796     #> term_value
   797   end;
   798 
   799 fun base_evaluator thy evaluator algebra funcgr vs t =
   800   let
   801     val (((naming, program), (((vs', ty'), t'), deps)), _) =
   802       invoke_generation thy (algebra, funcgr) ensure_value t;
   803     val vs'' = map (fn (v, _) => (v, (the o AList.lookup (op =) vs o prefix "'") v)) vs';
   804   in evaluator naming program ((vs'', (vs', ty')), t') deps end;
   805 
   806 fun eval_conv thy = Code_Preproc.eval_conv thy o base_evaluator thy;
   807 fun eval thy postproc = Code_Preproc.eval thy postproc o base_evaluator thy;
   808 
   809 
   810 (** diagnostic commands **)
   811 
   812 fun read_const_exprs thy =
   813   let
   814     fun consts_of some_thyname =
   815       let
   816         val thy' = case some_thyname
   817          of SOME thyname => ThyInfo.the_theory thyname thy
   818           | NONE => thy;
   819         val cs = Symtab.fold (fn (c, (_, NONE)) => cons c | _ => I)
   820           ((snd o #constants o Consts.dest o #consts o Sign.rep_sg) thy') [];
   821         fun belongs_here c =
   822           not (exists (fn thy'' => Sign.declared_const thy'' c) (Theory.parents_of thy'))
   823       in case some_thyname
   824        of NONE => cs
   825         | SOME thyname => filter belongs_here cs
   826       end;
   827     fun read_const_expr "*" = ([], consts_of NONE)
   828       | read_const_expr s = if String.isSuffix ".*" s
   829           then ([], consts_of (SOME (unsuffix ".*" s)))
   830           else ([Code.read_const thy s], []);
   831   in pairself flat o split_list o map read_const_expr end;
   832 
   833 fun code_depgr thy consts =
   834   let
   835     val (_, eqngr) = Code_Preproc.obtain thy consts [];
   836     val select = Graph.all_succs eqngr consts;
   837   in
   838     eqngr
   839     |> not (null consts) ? Graph.subgraph (member (op =) select) 
   840     |> Graph.map_nodes ((apsnd o map o apfst) (AxClass.overload thy))
   841   end;
   842 
   843 fun code_thms thy = Pretty.writeln o Code_Preproc.pretty thy o code_depgr thy;
   844 
   845 fun code_deps thy consts =
   846   let
   847     val eqngr = code_depgr thy consts;
   848     val constss = Graph.strong_conn eqngr;
   849     val mapping = Symtab.empty |> fold (fn consts => fold (fn const =>
   850       Symtab.update (const, consts)) consts) constss;
   851     fun succs consts = consts
   852       |> maps (Graph.imm_succs eqngr)
   853       |> subtract (op =) consts
   854       |> map (the o Symtab.lookup mapping)
   855       |> distinct (op =);
   856     val conn = [] |> fold (fn consts => cons (consts, succs consts)) constss;
   857     fun namify consts = map (Code.string_of_const thy) consts
   858       |> commas;
   859     val prgr = map (fn (consts, constss) =>
   860       { name = namify consts, ID = namify consts, dir = "", unfold = true,
   861         path = "", parents = map namify constss }) conn;
   862   in Present.display_graph prgr end;
   863 
   864 local
   865 
   866 structure P = OuterParse
   867 and K = OuterKeyword
   868 
   869 fun code_thms_cmd thy = code_thms thy o op @ o read_const_exprs thy;
   870 fun code_deps_cmd thy = code_deps thy o op @ o read_const_exprs thy;
   871 
   872 in
   873 
   874 val _ =
   875   OuterSyntax.improper_command "code_thms" "print system of code equations for code" OuterKeyword.diag
   876     (Scan.repeat P.term_group
   877       >> (fn cs => Toplevel.no_timing o Toplevel.unknown_theory
   878         o Toplevel.keep ((fn thy => code_thms_cmd thy cs) o Toplevel.theory_of)));
   879 
   880 val _ =
   881   OuterSyntax.improper_command "code_deps" "visualize dependencies of code equations for code" OuterKeyword.diag
   882     (Scan.repeat P.term_group
   883       >> (fn cs => Toplevel.no_timing o Toplevel.unknown_theory
   884         o Toplevel.keep ((fn thy => code_deps_cmd thy cs) o Toplevel.theory_of)));
   885 
   886 end;
   887 
   888 end; (*struct*)
   889 
   890 
   891 structure Basic_Code_Thingol: BASIC_CODE_THINGOL = Code_Thingol;