| 23152 |      1 | (*  Title:      HOLCF/Tools/domain/domain_syntax.ML
 | 
|  |      2 |     ID:         $Id$
 | 
|  |      3 |     Author:     David von Oheimb
 | 
|  |      4 | 
 | 
|  |      5 | Syntax generator for domain command.
 | 
|  |      6 | *)
 | 
|  |      7 | 
 | 
|  |      8 | structure Domain_Syntax = struct 
 | 
|  |      9 | 
 | 
|  |     10 | local 
 | 
|  |     11 | 
 | 
|  |     12 | open Domain_Library;
 | 
|  |     13 | infixr 5 -->; infixr 6 ->>;
 | 
|  |     14 | fun calc_syntax dtypeprod ((dname, typevars), 
 | 
|  |     15 | 	(cons': (string * mixfix * (bool * string option * typ) list) list)) =
 | 
|  |     16 | let
 | 
|  |     17 | (* ----- constants concerning the isomorphism ------------------------------- *)
 | 
|  |     18 | 
 | 
|  |     19 | local
 | 
|  |     20 |   fun opt_lazy (lazy,_,t) = if lazy then mk_uT t else t
 | 
|  |     21 |   fun prod     (_,_,args) = if args = [] then oneT
 | 
|  |     22 | 			    else foldr1 mk_sprodT (map opt_lazy args);
 | 
|  |     23 |   fun freetvar s = let val tvar = mk_TFree s in
 | 
|  |     24 | 		   if tvar mem typevars then freetvar ("t"^s) else tvar end;
 | 
|  |     25 |   fun when_type (_   ,_,args) = foldr (op ->>) (freetvar "t") (map third args);
 | 
|  |     26 | in
 | 
|  |     27 |   val dtype  = Type(dname,typevars);
 | 
|  |     28 |   val dtype2 = foldr1 mk_ssumT (map prod cons');
 | 
|  |     29 |   val dnam = Sign.base_name dname;
 | 
|  |     30 |   val const_rep  = (dnam^"_rep" ,              dtype  ->> dtype2, NoSyn);
 | 
|  |     31 |   val const_abs  = (dnam^"_abs" ,              dtype2 ->> dtype , NoSyn);
 | 
|  |     32 |   val const_when = (dnam^"_when",foldr (op ->>) (dtype ->> freetvar "t") (map when_type cons'), NoSyn);
 | 
|  |     33 |   val const_copy = (dnam^"_copy", dtypeprod ->> dtype  ->> dtype , NoSyn);
 | 
|  |     34 | end;
 | 
|  |     35 | 
 | 
|  |     36 | (* ----- constants concerning constructors, discriminators, and selectors --- *)
 | 
|  |     37 | 
 | 
|  |     38 | local
 | 
|  |     39 |   val escape = let
 | 
|  |     40 | 	fun esc (c::cs) = if c mem ["'","_","(",")","/"] then "'"::c::esc cs
 | 
|  |     41 | 							 else      c::esc cs
 | 
|  |     42 | 	|   esc []      = []
 | 
|  |     43 | 	in implode o esc o Symbol.explode end;
 | 
|  |     44 |   fun con (name,s,args) = (name,foldr (op ->>) dtype (map third args),s);
 | 
|  |     45 |   fun dis (con ,s,_   ) = (dis_name_ con, dtype->>trT,
 | 
|  |     46 | 			   Mixfix(escape ("is_" ^ con), [], Syntax.max_pri));
 | 
|  |     47 | 			(* strictly speaking, these constants have one argument,
 | 
|  |     48 | 			   but the mixfix (without arguments) is introduced only
 | 
|  |     49 | 			   to generate parse rules for non-alphanumeric names*)
 | 
|  |     50 |   fun mat (con ,s,args) = (mat_name_ con, dtype->>mk_maybeT(mk_ctupleT(map third args)),
 | 
|  |     51 | 			   Mixfix(escape ("match_" ^ con), [], Syntax.max_pri));
 | 
|  |     52 |   fun sel1 (_,sel,typ)  = Option.map (fn s => (s,dtype ->> typ,NoSyn)) sel;
 | 
|  |     53 |   fun sel (_   ,_,args) = List.mapPartial sel1 args;
 | 
|  |     54 |   fun freetvar s n      = let val tvar = mk_TFree (s ^ string_of_int n) in
 | 
|  |     55 | 			  if tvar mem typevars then freetvar ("t"^s) n else tvar end;
 | 
|  |     56 |   fun mk_patT (a,b)     = a ->> mk_maybeT b;
 | 
|  |     57 |   fun pat_arg_typ n arg = mk_patT (third arg, freetvar "t" n);
 | 
|  |     58 |   fun pat (con ,s,args) = (pat_name_ con, (mapn pat_arg_typ 1 args) --->
 | 
|  |     59 | 			   mk_patT (dtype, mk_ctupleT (map (freetvar "t") (1 upto length args))),
 | 
|  |     60 | 			   Mixfix(escape (con ^ "_pat"), [], Syntax.max_pri));
 | 
|  |     61 | 
 | 
|  |     62 | in
 | 
|  |     63 |   val consts_con = map con cons';
 | 
|  |     64 |   val consts_dis = map dis cons';
 | 
|  |     65 |   val consts_mat = map mat cons';
 | 
|  |     66 |   val consts_pat = map pat cons';
 | 
|  |     67 |   val consts_sel = List.concat(map sel cons');
 | 
|  |     68 | end;
 | 
|  |     69 | 
 | 
|  |     70 | (* ----- constants concerning induction ------------------------------------- *)
 | 
|  |     71 | 
 | 
|  |     72 |   val const_take   = (dnam^"_take"  , HOLogic.natT-->dtype->>dtype, NoSyn);
 | 
|  |     73 |   val const_finite = (dnam^"_finite", dtype-->HOLogic.boolT       , NoSyn);
 | 
|  |     74 | 
 | 
|  |     75 | (* ----- case translation --------------------------------------------------- *)
 | 
|  |     76 | 
 | 
|  |     77 | local open Syntax in
 | 
|  |     78 |   local
 | 
|  |     79 |     fun c_ast con mx = Constant (const_name con mx);
 | 
|  |     80 |     fun expvar n     = Variable ("e"^(string_of_int n));
 | 
|  |     81 |     fun argvar n m _ = Variable ("a"^(string_of_int n)^"_"^
 | 
|  |     82 | 				     (string_of_int m));
 | 
|  |     83 |     fun argvars n args = mapn (argvar n) 1 args;
 | 
|  |     84 |     fun app s (l,r)  = mk_appl (Constant s) [l,r];
 | 
|  |     85 |     val cabs = app "_cabs";
 | 
|  |     86 |     val capp = app "Rep_CFun";
 | 
|  |     87 |     fun con1 n (con,mx,args) = Library.foldl capp (c_ast con mx, argvars n args);
 | 
|  |     88 |     fun case1 n (con,mx,args) = app "_case1" (con1 n (con,mx,args), expvar n);
 | 
|  |     89 |     fun arg1 n (con,_,args) = foldr cabs (expvar n) (argvars n args);
 | 
|  |     90 |     fun when1 n m = if n = m then arg1 n else K (Constant "UU");
 | 
|  |     91 | 
 | 
|  |     92 |     fun app_var x = mk_appl (Constant "_var") [x, Variable "rhs"];
 | 
|  |     93 |     fun app_pat x = mk_appl (Constant "_pat") [x];
 | 
| 26046 |     94 |     fun args_list [] = Constant "_noargs"
 | 
| 23152 |     95 |     |   args_list xs = foldr1 (app "_args") xs;
 | 
|  |     96 |   in
 | 
|  |     97 |     val case_trans = ParsePrintRule
 | 
|  |     98 |         (app "_case_syntax" (Variable "x", foldr1 (app "_case2") (mapn case1 1 cons')),
 | 
|  |     99 |          capp (Library.foldl capp (Constant (dnam^"_when"), mapn arg1 1 cons'), Variable "x"));
 | 
|  |    100 |     
 | 
|  |    101 |     val abscon_trans = mapn (fn n => fn (con,mx,args) => ParsePrintRule
 | 
|  |    102 |         (cabs (con1 n (con,mx,args), expvar n),
 | 
|  |    103 |          Library.foldl capp (Constant (dnam^"_when"), mapn (when1 n) 1 cons'))) 1 cons';
 | 
|  |    104 |     
 | 
|  |    105 |     val Case_trans = List.concat (map (fn (con,mx,args) =>
 | 
|  |    106 |       let
 | 
|  |    107 |         val cname = c_ast con mx;
 | 
|  |    108 |         val pname = Constant (pat_name_ con);
 | 
|  |    109 |         val ns = 1 upto length args;
 | 
|  |    110 |         val xs = map (fn n => Variable ("x"^(string_of_int n))) ns;
 | 
|  |    111 |         val ps = map (fn n => Variable ("p"^(string_of_int n))) ns;
 | 
|  |    112 |         val vs = map (fn n => Variable ("v"^(string_of_int n))) ns;
 | 
|  |    113 |       in
 | 
|  |    114 |         [ParseRule (app_pat (Library.foldl capp (cname, xs)),
 | 
|  |    115 |                     mk_appl pname (map app_pat xs)),
 | 
|  |    116 |          ParseRule (app_var (Library.foldl capp (cname, xs)),
 | 
|  |    117 |                     app_var (args_list xs)),
 | 
|  |    118 |          PrintRule (Library.foldl capp (cname, ListPair.map (app "_match") (ps,vs)),
 | 
|  |    119 |                     app "_match" (mk_appl pname ps, args_list vs))]
 | 
|  |    120 |       end) cons');
 | 
|  |    121 |   end;
 | 
|  |    122 | end;
 | 
|  |    123 | 
 | 
|  |    124 | in ([const_rep, const_abs, const_when, const_copy] @ 
 | 
|  |    125 |      consts_con @ consts_dis @ consts_mat @ consts_pat @ consts_sel @
 | 
|  |    126 |     [const_take, const_finite],
 | 
|  |    127 |     (case_trans::(abscon_trans @ Case_trans)))
 | 
|  |    128 | end; (* let *)
 | 
|  |    129 | 
 | 
|  |    130 | (* ----- putting all the syntax stuff together ------------------------------ *)
 | 
|  |    131 | 
 | 
|  |    132 | in (* local *)
 | 
|  |    133 | 
 | 
|  |    134 | fun add_syntax (comp_dnam,eqs': ((string * typ list) *
 | 
|  |    135 | 	(string * mixfix * (bool * string option * typ) list) list) list) thy'' =
 | 
|  |    136 | let
 | 
|  |    137 |   val dtypes  = map (Type o fst) eqs';
 | 
|  |    138 |   val boolT   = HOLogic.boolT;
 | 
|  |    139 |   val funprod = foldr1 HOLogic.mk_prodT (map (fn tp => tp ->> tp          ) dtypes);
 | 
|  |    140 |   val relprod = foldr1 HOLogic.mk_prodT (map (fn tp => tp --> tp --> boolT) dtypes);
 | 
|  |    141 |   val const_copy   = (comp_dnam^"_copy"  ,funprod ->> funprod, NoSyn);
 | 
|  |    142 |   val const_bisim  = (comp_dnam^"_bisim" ,relprod --> boolT  , NoSyn);
 | 
|  |    143 |   val ctt           = map (calc_syntax funprod) eqs';
 | 
|  |    144 | in thy'' |> ContConsts.add_consts_i (List.concat (map fst ctt) @ 
 | 
|  |    145 | 				    (if length eqs'>1 then [const_copy] else[])@
 | 
|  |    146 | 				    [const_bisim])
 | 
|  |    147 | 	 |> Sign.add_trrules_i (List.concat(map snd ctt))
 | 
|  |    148 | end; (* let *)
 | 
|  |    149 | 
 | 
|  |    150 | end; (* local *)
 | 
|  |    151 | end; (* struct *)
 |