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