src/Tools/code/code_name.ML
changeset 24219 e558fe311376
child 24423 ae9cd0e92423
equal deleted inserted replaced
24218:fbf1646b267c 24219:e558fe311376
       
     1 (*  Title:      Tools/code/code_name.ML
       
     2     ID:         $Id$
       
     3     Author:     Florian Haftmann, TU Muenchen
       
     4 
       
     5 Naming policies for code generation: prefixing any name by corresponding
       
     6 theory name, conversion to alphanumeric representation.
       
     7 Mappings are incrementally cached.
       
     8 *)
       
     9 
       
    10 signature CODE_NAME =
       
    11 sig
       
    12   val purify_var: string -> string
       
    13   val purify_tvar: string -> string
       
    14   val check_modulename: string -> string
       
    15   type var_ctxt;
       
    16   val make_vars: string list -> var_ctxt;
       
    17   val intro_vars: string list -> var_ctxt -> var_ctxt;
       
    18   val lookup_var: var_ctxt -> string -> string;
       
    19 
       
    20   type tyco = string
       
    21   type const = string
       
    22   val class: theory -> class -> class
       
    23   val class_rev: theory -> class -> class option
       
    24   val classrel: theory -> class * class -> string
       
    25   val classrel_rev: theory -> string -> (class * class) option
       
    26   val tyco: theory -> tyco -> tyco
       
    27   val tyco_rev: theory -> tyco -> tyco option
       
    28   val instance: theory -> class * tyco -> string
       
    29   val instance_rev: theory -> string -> (class * tyco) option
       
    30   val const: theory -> CodeUnit.const -> const
       
    31   val const_rev: theory -> const -> CodeUnit.const option
       
    32   val labelled_name: theory -> string -> string
       
    33 
       
    34   val setup: theory -> theory
       
    35 end;
       
    36 
       
    37 structure CodeName: CODE_NAME =
       
    38 struct
       
    39 
       
    40 (** purification **)
       
    41 
       
    42 fun purify_name upper_else_lower =
       
    43   let
       
    44     fun is_valid s = Symbol.is_ascii_letter s orelse Symbol.is_ascii_digit s orelse s = "'";
       
    45     val is_junk = not o is_valid andf Symbol.is_regular;
       
    46     val junk = Scan.many is_junk;
       
    47     val scan_valids = Symbol.scanner "Malformed input"
       
    48       ((junk |--
       
    49         (Scan.optional (Scan.one Symbol.is_ascii_letter) "x" ^^ (Scan.many is_valid >> implode)
       
    50         --| junk))
       
    51       -- Scan.repeat ((Scan.many1 is_valid >> implode) --| junk) >> op ::);
       
    52     fun upper_lower cs = if upper_else_lower then nth_map 0 Symbol.to_ascii_upper cs
       
    53       else (if forall Symbol.is_ascii_upper cs
       
    54         then map else nth_map 0) Symbol.to_ascii_lower cs;
       
    55   in
       
    56     explode
       
    57     #> scan_valids
       
    58     #> space_implode "_"
       
    59     #> explode
       
    60     #> upper_lower
       
    61     #> implode
       
    62   end;
       
    63 
       
    64 fun purify_var "" = "x"
       
    65   | purify_var v = purify_name false v;
       
    66 
       
    67 fun purify_tvar "" = "'a"
       
    68   | purify_tvar v =
       
    69       (unprefix "'" #> explode #> filter Symbol.is_ascii_letter #> cons "'" #> implode) v;
       
    70 
       
    71 fun check_modulename mn =
       
    72   let
       
    73     val mns = NameSpace.explode mn;
       
    74     val mns' = map (purify_name true) mns;
       
    75   in
       
    76     if mns' = mns then mn else error ("Invalid module name: " ^ quote mn ^ "\n"
       
    77       ^ "perhaps try " ^ quote (NameSpace.implode mns'))
       
    78   end;
       
    79 
       
    80 
       
    81 (** variable name contexts **)
       
    82 
       
    83 type var_ctxt = string Symtab.table * Name.context;
       
    84 
       
    85 fun make_vars names = (fold (fn name => Symtab.update_new (name, name)) names Symtab.empty,
       
    86   Name.make_context names);
       
    87 
       
    88 fun intro_vars names (namemap, namectxt) =
       
    89   let
       
    90     val (names', namectxt') = Name.variants names namectxt;
       
    91     val namemap' = fold2 (curry Symtab.update) names names' namemap;
       
    92   in (namemap', namectxt') end;
       
    93 
       
    94 fun lookup_var (namemap, _) name = case Symtab.lookup namemap name
       
    95  of SOME name' => name'
       
    96   | NONE => error ("Invalid name in context: " ^ quote name);
       
    97 
       
    98 
       
    99 
       
   100 (** global names (identifiers) **)
       
   101 
       
   102 (* identifier categories *)
       
   103 
       
   104 val idf_class = "class";
       
   105 val idf_classrel = "clsrel"
       
   106 val idf_tyco = "tyco";
       
   107 val idf_instance = "inst";
       
   108 val idf_const = "const";
       
   109 
       
   110 fun string_of_classrel (class, superclass) = class ^ " < " ^ superclass;
       
   111 fun string_of_instance (class, tyco) = tyco ^ " :: " ^ class;
       
   112 
       
   113 fun add_idf nsp name =
       
   114   NameSpace.append name nsp;
       
   115 
       
   116 fun dest_idf nsp name =
       
   117   if NameSpace.base name = nsp
       
   118   then SOME (NameSpace.qualifier name)
       
   119   else NONE;
       
   120 
       
   121 local
       
   122 
       
   123 val name_mapping  = [
       
   124   (idf_class,       "class"),
       
   125   (idf_classrel,    "subclass relation"),
       
   126   (idf_tyco,        "type constructor"),
       
   127   (idf_instance,    "instance"),
       
   128   (idf_const,       "constant")
       
   129 ]
       
   130 
       
   131 in
       
   132 
       
   133 val category_of = the o AList.lookup (op =) name_mapping o NameSpace.base;
       
   134 
       
   135 end;
       
   136 
       
   137 
       
   138 (* theory name lookup *)
       
   139 
       
   140 fun thyname_of thy f errmsg x =
       
   141   let
       
   142     fun thy_of thy =
       
   143       if f thy x then case get_first thy_of (Theory.parents_of thy)
       
   144         of NONE => SOME thy
       
   145          | thy => thy
       
   146       else NONE;
       
   147   in case thy_of thy
       
   148    of SOME thy => Context.theory_name thy
       
   149     | NONE => error (errmsg x) end;
       
   150 
       
   151 fun thyname_of_class thy =
       
   152   thyname_of thy (fn thy => member (op =) (Sign.all_classes thy))
       
   153     (fn class => "thyname_of_class: no such class: " ^ quote class);
       
   154 
       
   155 fun thyname_of_classrel thy =
       
   156   thyname_of thy (fn thy => fn (class1, class2) => Sign.subsort thy ([class1], [class2]))
       
   157     (fn (class1, class2) => "thyname_of_classrel: no such subclass relation: "
       
   158       ^ (quote o string_of_classrel) (class1, class2));
       
   159 
       
   160 fun thyname_of_tyco thy =
       
   161   thyname_of thy Sign.declared_tyname
       
   162     (fn tyco => "thyname_of_tyco: no such type constructor: " ^ quote tyco);
       
   163 
       
   164 fun thyname_of_instance thy =
       
   165   let
       
   166     fun test_instance thy (class, tyco) =
       
   167       can (Sorts.mg_domain (Sign.classes_of thy) tyco) [class]
       
   168   in thyname_of thy test_instance
       
   169     (fn (class, tyco) => "thyname_of_instance: no such instance: "
       
   170       ^ (quote o string_of_instance) (class, tyco))
       
   171   end;
       
   172 
       
   173 fun thyname_of_const thy =
       
   174   thyname_of thy Sign.declared_const
       
   175     (fn c => "thyname_of_const: no such constant: " ^ quote c);
       
   176 
       
   177 
       
   178 (* naming policies *)
       
   179 
       
   180 val purify_prefix =
       
   181   explode
       
   182   (*should disappear as soon as hierarchical theory name spaces are available*)
       
   183   #> Symbol.scanner "Malformed name"
       
   184       (Scan.repeat ($$ "_" |-- $$ "_" >> (fn _ => ".") || Scan.one Symbol.is_regular))
       
   185   #> implode
       
   186   #> NameSpace.explode
       
   187   #> map (purify_name true);
       
   188 
       
   189 fun purify_base "op =" = "eq"
       
   190   | purify_base "op &" = "and"
       
   191   | purify_base "op |" = "or"
       
   192   | purify_base "op -->" = "implies"
       
   193   | purify_base "{}" = "empty"
       
   194   | purify_base "op :" = "member"
       
   195   | purify_base "op Int" = "intersect"
       
   196   | purify_base "op Un" = "union"
       
   197   | purify_base "*" = "product"
       
   198   | purify_base "+" = "sum"
       
   199   | purify_base s = purify_name false s;
       
   200 
       
   201 fun default_policy thy get_basename get_thyname name =
       
   202   let
       
   203     val prefix = (purify_prefix o get_thyname thy) name;
       
   204     val base = (purify_base o get_basename) name;
       
   205   in NameSpace.implode (prefix @ [base]) end;
       
   206 
       
   207 fun class_policy thy = default_policy thy NameSpace.base thyname_of_class;
       
   208 fun classrel_policy thy = default_policy thy (fn (class1, class2) => 
       
   209   NameSpace.base class2 ^ "_" ^ NameSpace.base class1) thyname_of_classrel;
       
   210   (*order fits nicely with composed projections*)
       
   211 fun tyco_policy thy = default_policy thy NameSpace.base thyname_of_tyco;
       
   212 fun instance_policy thy = default_policy thy (fn (class, tyco) => 
       
   213   NameSpace.base class ^ "_" ^ NameSpace.base tyco) thyname_of_instance;
       
   214 
       
   215 fun force_thyname thy (const as (c, opt_tyco)) =
       
   216   case Code.get_datatype_of_constr thy const
       
   217    of SOME dtco => SOME (thyname_of_tyco thy dtco)
       
   218     | NONE => (case AxClass.class_of_param thy c
       
   219        of SOME class => (case opt_tyco
       
   220            of SOME tyco => SOME (thyname_of_instance thy (class, tyco))
       
   221             | NONE => SOME (thyname_of_class thy class))
       
   222         | NONE => NONE);
       
   223 
       
   224 fun const_policy thy (const as (c, opt_tyco)) =
       
   225   case force_thyname thy const
       
   226    of NONE => default_policy thy NameSpace.base thyname_of_const c
       
   227     | SOME thyname => let
       
   228         val prefix = purify_prefix thyname;
       
   229         val tycos = the_list opt_tyco;
       
   230         val base = map (purify_base o NameSpace.base) (c :: tycos);
       
   231       in NameSpace.implode (prefix @ [space_implode "_" base]) end;
       
   232 
       
   233 
       
   234 (* theory and code data *)
       
   235 
       
   236 type tyco = string;
       
   237 type const = string;
       
   238 structure Consttab = CodeUnit.Consttab;
       
   239 
       
   240 structure StringPairTab =
       
   241   TableFun(
       
   242     type key = string * string;
       
   243     val ord = prod_ord fast_string_ord fast_string_ord;
       
   244   );
       
   245 
       
   246 datatype names = Names of {
       
   247   class: class Symtab.table * class Symtab.table,
       
   248   classrel: string StringPairTab.table * (class * class) Symtab.table,
       
   249   tyco: tyco Symtab.table * tyco Symtab.table,
       
   250   instance: string StringPairTab.table * (class * tyco) Symtab.table
       
   251 }
       
   252 
       
   253 val empty_names = Names {
       
   254   class = (Symtab.empty, Symtab.empty),
       
   255   classrel = (StringPairTab.empty, Symtab.empty),
       
   256   tyco = (Symtab.empty, Symtab.empty),
       
   257   instance = (StringPairTab.empty, Symtab.empty)
       
   258 };
       
   259 
       
   260 local
       
   261   fun mk_names (class, classrel, tyco, instance) =
       
   262     Names { class = class, classrel = classrel, tyco = tyco, instance = instance };
       
   263   fun map_names f (Names { class, classrel, tyco, instance }) =
       
   264     mk_names (f (class, classrel, tyco, instance));
       
   265 in
       
   266   fun merge_names (Names { class = (class1, classrev1),
       
   267       classrel = (classrel1, classrelrev1), tyco = (tyco1, tycorev1),
       
   268       instance = (instance1, instancerev1) },
       
   269     Names { class = (class2, classrev2),
       
   270       classrel = (classrel2, classrelrev2), tyco = (tyco2, tycorev2),
       
   271       instance = (instance2, instancerev2) }) =
       
   272     mk_names ((Symtab.merge (op =) (class1, class2), Symtab.merge (op =) (classrev1, classrev2)),
       
   273       (StringPairTab.merge (op =) (classrel1, classrel2), Symtab.merge (op =) (classrelrev1, classrelrev2)),
       
   274       (Symtab.merge (op =) (tyco1, tyco2), Symtab.merge (op =) (tycorev1, tycorev2)),
       
   275       (StringPairTab.merge (op =) (instance1, instance2), Symtab.merge (op =) (instancerev1, instancerev2)));
       
   276   fun map_class f = map_names
       
   277     (fn (class, classrel, tyco, inst) => (f class, classrel, tyco, inst));
       
   278   fun map_classrel f = map_names
       
   279     (fn (class, classrel, tyco, inst) => (class, f classrel, tyco, inst));
       
   280   fun map_tyco f = map_names
       
   281     (fn (class, classrel, tyco, inst) => (class, classrel, f tyco, inst));
       
   282   fun map_instance f = map_names
       
   283     (fn (class, classrel, tyco, inst) => (class, classrel, tyco, f inst));
       
   284 end; (*local*)
       
   285 
       
   286 structure CodeName = TheoryDataFun
       
   287 (
       
   288   type T = names ref;
       
   289   val empty = ref empty_names;
       
   290   fun copy (ref names) = ref names;
       
   291   val extend = copy;
       
   292   fun merge _ (ref names1, ref names2) = ref (merge_names (names1, names2));
       
   293 );
       
   294 
       
   295 structure ConstName = CodeDataFun
       
   296 (
       
   297   type T = const Consttab.table * (string * string option) Symtab.table;
       
   298   val empty = (Consttab.empty, Symtab.empty);
       
   299   fun merge _ ((const1, constrev1), (const2, constrev2)) : T =
       
   300     (Consttab.merge (op =) (const1, const2),
       
   301       Symtab.merge CodeUnit.eq_const (constrev1, constrev2));
       
   302   fun purge _ NONE _ = empty
       
   303     | purge _ (SOME cs) (const, constrev) = (fold Consttab.delete_safe cs const,
       
   304         fold Symtab.delete (map_filter (Consttab.lookup const) cs) constrev);
       
   305 );
       
   306 
       
   307 val setup = CodeName.init;
       
   308 
       
   309 
       
   310 (* forward lookup with cache update *)
       
   311 
       
   312 fun get thy get_tabs get upd_names upd policy x =
       
   313   let
       
   314     val names_ref = CodeName.get thy;
       
   315     val (Names names) = ! names_ref;
       
   316     val tabs = get_tabs names;
       
   317     fun declare name =
       
   318       let
       
   319         val names' = upd_names (K (upd (x, name) (fst tabs),
       
   320           Symtab.update_new (name, x) (snd tabs))) (Names names)
       
   321       in (names_ref := names'; name) end;
       
   322   in case get (fst tabs) x
       
   323    of SOME name => name
       
   324     | NONE => 
       
   325         x
       
   326         |> policy thy
       
   327         |> Name.variant (Symtab.keys (snd tabs))
       
   328         |> declare
       
   329   end;
       
   330 
       
   331 fun get_const thy const =
       
   332   let
       
   333     val tabs = ConstName.get thy;
       
   334     fun declare name =
       
   335       let
       
   336         val names' = (Consttab.update (const, name) (fst tabs),
       
   337           Symtab.update_new (name, const) (snd tabs))
       
   338       in (ConstName.change thy (K names'); name) end;
       
   339   in case Consttab.lookup (fst tabs) const
       
   340    of SOME name => name
       
   341     | NONE => 
       
   342         const
       
   343         |> const_policy thy
       
   344         |> Name.variant (Symtab.keys (snd tabs))
       
   345         |> declare
       
   346   end;
       
   347 
       
   348 
       
   349 (* backward lookup *)
       
   350 
       
   351 fun rev thy get_tabs name =
       
   352   let
       
   353     val names_ref = CodeName.get thy
       
   354     val (Names names) = ! names_ref;
       
   355     val tab = (snd o get_tabs) names;
       
   356   in case Symtab.lookup tab name
       
   357    of SOME x => x
       
   358     | NONE => error ("No such " ^ category_of name ^ ": " ^ quote name)
       
   359   end;
       
   360 
       
   361 fun rev_const thy name =
       
   362   let
       
   363     val tab = snd (ConstName.get thy);
       
   364   in case Symtab.lookup tab name
       
   365    of SOME const => const
       
   366     | NONE => error ("No such " ^ category_of name ^ ": " ^ quote name)
       
   367   end;
       
   368 
       
   369 
       
   370 (* external interfaces *)
       
   371 
       
   372 fun class thy =
       
   373   get thy #class Symtab.lookup map_class Symtab.update class_policy
       
   374   #> add_idf idf_class;
       
   375 fun classrel thy =
       
   376   get thy #classrel StringPairTab.lookup map_classrel StringPairTab.update classrel_policy
       
   377   #> add_idf idf_classrel;
       
   378 fun tyco thy =
       
   379   get thy #tyco Symtab.lookup map_tyco Symtab.update tyco_policy
       
   380   #> add_idf idf_tyco;
       
   381 fun instance thy =
       
   382   get thy #instance StringPairTab.lookup map_instance StringPairTab.update instance_policy
       
   383   #> add_idf idf_instance;
       
   384 fun const thy =
       
   385   get_const thy
       
   386   #> add_idf idf_const;
       
   387 
       
   388 fun class_rev thy =
       
   389   dest_idf idf_class
       
   390   #> Option.map (rev thy #class);
       
   391 fun classrel_rev thy =
       
   392   dest_idf idf_classrel
       
   393   #> Option.map (rev thy #classrel);
       
   394 fun tyco_rev thy =
       
   395   dest_idf idf_tyco
       
   396   #> Option.map (rev thy #tyco);
       
   397 fun instance_rev thy =
       
   398   dest_idf idf_instance
       
   399   #> Option.map (rev thy #instance);
       
   400 fun const_rev thy =
       
   401   dest_idf idf_const
       
   402   #> Option.map (rev_const thy);
       
   403 
       
   404 local
       
   405 
       
   406 val f_mapping = [
       
   407   (idf_class,       class_rev),
       
   408   (idf_classrel,    Option.map string_of_classrel oo classrel_rev),
       
   409   (idf_tyco,        tyco_rev),
       
   410   (idf_instance,    Option.map string_of_instance oo instance_rev),
       
   411   (idf_const,       fn thy => Option.map (CodeUnit.string_of_const thy) o const_rev thy)
       
   412 ];
       
   413 
       
   414 in
       
   415 
       
   416 fun labelled_name thy idf =
       
   417   let
       
   418     val category = category_of idf;
       
   419     val name = NameSpace.qualifier idf;
       
   420     val f = (the o AList.lookup (op =) f_mapping o NameSpace.base) idf
       
   421   in case f thy idf
       
   422    of SOME thing => category ^ " " ^ quote thing
       
   423     | NONE => error ("Unknown name: " ^ quote name)
       
   424   end;
       
   425 
       
   426 end;
       
   427 
       
   428 end;