src/Tools/Code/code_target.ML
author haftmann
Sun, 23 Feb 2014 10:33:43 +0100
changeset 57026 ee49b4f7edc8
parent 57025 5732a55b9232
child 57099 9fc71814b8c1
permissions -rw-r--r--
keep only identifiers public which are explicitly requested or demanded by dependencies
     1 (*  Title:      Tools/Code/code_target.ML
     2     Author:     Florian Haftmann, TU Muenchen
     3 
     4 Generic infrastructure for target language data.
     5 *)
     6 
     7 signature CODE_TARGET =
     8 sig
     9   val cert_tyco: theory -> string -> string
    10   val read_tyco: theory -> string -> string
    11 
    12   val export_code_for: theory -> Path.T option -> string -> int option -> string -> Token.T list
    13     -> Code_Thingol.program -> bool -> Code_Symbol.T list -> unit
    14   val produce_code_for: theory -> string -> int option -> string -> Token.T list
    15     -> Code_Thingol.program -> bool -> Code_Symbol.T list -> (string * string) list * string option list
    16   val present_code_for: theory -> string -> int option -> string -> Token.T list
    17     -> Code_Thingol.program -> Code_Symbol.T list * Code_Symbol.T list -> string
    18   val check_code_for: theory -> string -> bool -> Token.T list
    19     -> Code_Thingol.program -> bool -> Code_Symbol.T list -> unit
    20 
    21   val export_code: theory -> bool -> string list
    22     -> (((string * string) * Path.T option) * Token.T list) list -> unit
    23   val produce_code: theory -> bool -> string list
    24     -> string -> int option -> string -> Token.T list -> (string * string) list * string option list
    25   val present_code: theory -> string list -> Code_Symbol.T list
    26     -> string -> int option -> string -> Token.T list -> string
    27   val check_code: theory -> bool -> string list
    28     -> ((string * bool) * Token.T list) list -> unit
    29 
    30   val generatedN: string
    31   val evaluator: theory -> string -> Code_Thingol.program
    32     -> Code_Symbol.T list -> bool -> ((string * class list) list * Code_Thingol.itype) * Code_Thingol.iterm
    33     -> (string * string) list * string
    34 
    35   type serializer
    36   type literals = Code_Printer.literals
    37   val add_target: string * { serializer: serializer, literals: literals,
    38     check: { env_var: string, make_destination: Path.T -> Path.T, make_command: string -> string } }
    39     -> theory -> theory
    40   val extend_target: string *
    41       (string * (Code_Thingol.program -> Code_Thingol.program))
    42     -> theory -> theory
    43   val assert_target: theory -> string -> string
    44   val the_literals: theory -> string -> literals
    45   type serialization
    46   val parse_args: 'a parser -> Token.T list -> 'a
    47   val serialization: (int -> Path.T option -> 'a -> unit)
    48     -> (Code_Symbol.T list -> int -> 'a -> (string * string) list * (Code_Symbol.T -> string option))
    49     -> 'a -> serialization
    50   val set_default_code_width: int -> theory -> theory
    51 
    52   type ('a, 'b, 'c, 'd, 'e, 'f) symbol_attr_decl
    53   type identifier_data
    54   val set_identifiers: (string, string, string, string, string, string) symbol_attr_decl
    55     -> theory -> theory
    56   val set_printings: (Code_Printer.raw_const_syntax, Code_Printer.tyco_syntax, string, unit, unit, (string * string list)) symbol_attr_decl
    57     -> theory -> theory
    58   val add_reserved: string -> string -> theory -> theory
    59 
    60   val codegen_tool: string (*theory name*) -> string (*export_code expr*) -> unit
    61 
    62   val setup: theory -> theory
    63 end;
    64 
    65 structure Code_Target : CODE_TARGET =
    66 struct
    67 
    68 open Basic_Code_Symbol;
    69 open Basic_Code_Thingol;
    70 
    71 type literals = Code_Printer.literals;
    72 type ('a, 'b, 'c, 'd, 'e, 'f) symbol_attr_decl =
    73   (string * (string * 'a option) list, string * (string * 'b option) list,
    74     class * (string * 'c option) list, (class * class) * (string * 'd option) list,
    75     (class * string) * (string * 'e option) list,
    76     string * (string * 'f option) list) Code_Symbol.attr;
    77 type identifier_data = (string list * string, string list * string, string list * string, string list * string,
    78   string list * string, string list * string) Code_Symbol.data;
    79 
    80 type tyco_syntax = Code_Printer.tyco_syntax;
    81 type raw_const_syntax = Code_Printer.raw_const_syntax;
    82 
    83 
    84 (** checking and parsing of symbols **)
    85 
    86 fun cert_const thy const =
    87   let
    88     val _ = if Sign.declared_const thy const then ()
    89       else error ("No such constant: " ^ quote const);
    90   in const end;
    91 
    92 fun cert_tyco thy tyco =
    93   let
    94     val _ = if Sign.declared_tyname thy tyco then ()
    95       else error ("No such type constructor: " ^ quote tyco);
    96   in tyco end;
    97 
    98 fun read_tyco thy = #1 o dest_Type
    99   o Proof_Context.read_type_name_proper (Proof_Context.init_global thy) true;
   100 
   101 fun cert_class thy class =
   102   let
   103     val _ = Axclass.get_info thy class;
   104   in class end;
   105 
   106 fun read_class thy = Proof_Context.read_class (Proof_Context.init_global thy);
   107 
   108 val parse_classrel_ident = Parse.class --| @{keyword "<"} -- Parse.class;
   109 
   110 fun cert_inst thy (class, tyco) =
   111   (cert_class thy class, cert_tyco thy tyco);
   112 
   113 fun read_inst thy (raw_tyco, raw_class) =
   114   (read_tyco thy raw_tyco, read_class thy raw_class);
   115 
   116 val parse_inst_ident = Parse.xname --| @{keyword "::"} -- Parse.class;
   117 
   118 fun cert_syms thy =
   119   Code_Symbol.map_attr (apfst (cert_const thy)) (apfst (cert_tyco thy))
   120     (apfst (cert_class thy)) ((apfst o pairself) (cert_class thy)) (apfst (cert_inst thy)) I;
   121 
   122 fun read_syms thy =
   123   Code_Symbol.map_attr (apfst (Code.read_const thy)) (apfst (read_tyco thy))
   124     (apfst (read_class thy)) ((apfst o pairself) (read_class thy)) (apfst (read_inst thy)) I;
   125 
   126 fun check_name is_module s =
   127   let
   128     val _ = if s = "" then error "Bad empty code name" else ();
   129     val xs = Long_Name.explode s;
   130     val xs' = if is_module
   131         then map (Name.desymbolize true) xs
   132       else if length xs < 2
   133         then error ("Bad code name without module component: " ^ quote s)
   134       else
   135         let
   136           val (ys, y) = split_last xs;
   137           val ys' = map (Name.desymbolize true) ys;
   138           val y' = Name.desymbolize false y;
   139         in ys' @ [y'] end;
   140   in if xs' = xs
   141     then if is_module then (xs, "") else split_last xs
   142     else error ("Invalid code name: " ^ quote s ^ "\n"
   143       ^ "better try " ^ quote (Long_Name.implode xs'))
   144   end;
   145 
   146 
   147 (** serializations and serializer **)
   148 
   149 (* serialization: abstract nonsense to cover different destinies for generated code *)
   150 
   151 datatype destination = Export of Path.T option | Produce | Present of Code_Symbol.T list;
   152 type serialization = int -> destination -> ((string * string) list * (Code_Symbol.T -> string option)) option;
   153 
   154 fun serialization output _ content width (Export some_path) =
   155       (output width some_path content; NONE)
   156   | serialization _ string content width Produce =
   157       string [] width content |> SOME
   158   | serialization _ string content width (Present syms) =
   159      string syms width content
   160      |> (apfst o map o apsnd) (Pretty.output (SOME width) o Pretty.str)
   161      |> SOME;
   162 
   163 fun export some_path f = (f (Export some_path); ());
   164 fun produce f = the (f Produce);
   165 fun present syms f = space_implode "\n\n" (map snd (fst (the (f (Present syms)))));
   166 
   167 
   168 (* serializers: functions producing serializations *)
   169 
   170 type serializer = Token.T list
   171   -> Proof.context
   172   -> {
   173     module_name: string,
   174     reserved_syms: string list,
   175     identifiers: identifier_data,
   176     includes: (string * Pretty.T) list,
   177     class_syntax: string -> string option,
   178     tyco_syntax: string -> Code_Printer.tyco_syntax option,
   179     const_syntax: string -> Code_Printer.const_syntax option }
   180   -> Code_Symbol.T list
   181   -> Code_Thingol.program
   182   -> serialization;
   183 
   184 datatype description =
   185     Fundamental of { serializer: serializer,
   186       literals: literals,
   187       check: { env_var: string, make_destination: Path.T -> Path.T,
   188         make_command: string -> string } }
   189   | Extension of string *
   190       (Code_Thingol.program -> Code_Thingol.program);
   191 
   192 
   193 (** theory data **)
   194 
   195 datatype target = Target of {
   196   serial: serial,
   197   description: description,
   198   reserved: string list,
   199   identifiers: identifier_data,
   200   printings: (Code_Printer.const_syntax, Code_Printer.tyco_syntax, string, unit, unit,
   201     (Pretty.T * string list)) Code_Symbol.data
   202 };
   203 
   204 fun make_target ((serial, description), (reserved, (identifiers, printings))) =
   205   Target { serial = serial, description = description, reserved = reserved,
   206     identifiers = identifiers, printings = printings };
   207 fun map_target f (Target { serial, description, reserved, identifiers, printings }) =
   208   make_target (f ((serial, description), (reserved, (identifiers, printings))));
   209 fun merge_target strict target (Target { serial = serial1, description = description,
   210   reserved = reserved1, identifiers = identifiers1, printings = printings1 },
   211     Target { serial = serial2, description = _,
   212       reserved = reserved2, identifiers = identifiers2, printings = printings2 }) =
   213   if serial1 = serial2 orelse not strict then
   214     make_target ((serial1, description), (merge (op =) (reserved1, reserved2),
   215       (Code_Symbol.merge_data (identifiers1, identifiers2),
   216         Code_Symbol.merge_data (printings1, printings2))))
   217   else
   218     error ("Incompatible targets: " ^ quote target);
   219 
   220 fun the_description (Target { description, ... }) = description;
   221 fun the_reserved (Target { reserved, ... }) = reserved;
   222 fun the_identifiers (Target { identifiers , ... }) = identifiers;
   223 fun the_printings (Target { printings, ... }) = printings;
   224 
   225 structure Targets = Theory_Data
   226 (
   227   type T = target Symtab.table * int;
   228   val empty = (Symtab.empty, 80);
   229   val extend = I;
   230   fun merge ((target1, width1), (target2, width2)) : T =
   231     (Symtab.join (merge_target true) (target1, target2), Int.max (width1, width2));
   232 );
   233 
   234 fun assert_target thy target = if Symtab.defined (fst (Targets.get thy)) target
   235   then target
   236   else error ("Unknown code target language: " ^ quote target);
   237 
   238 fun put_target (target, seri) thy =
   239   let
   240     val lookup_target = Symtab.lookup (fst (Targets.get thy));
   241     val _ = case seri
   242      of Extension (super, _) => if is_some (lookup_target super) then ()
   243           else error ("Unknown code target language: " ^ quote super)
   244       | _ => ();
   245     val overwriting = case (Option.map the_description o lookup_target) target
   246      of NONE => false
   247       | SOME (Extension _) => true
   248       | SOME (Fundamental _) => (case seri
   249          of Extension _ => error ("Will not overwrite existing target " ^ quote target)
   250           | _ => true);
   251     val _ = if overwriting
   252       then warning ("Overwriting existing target " ^ quote target)
   253       else ();
   254   in
   255     thy
   256     |> (Targets.map o apfst o Symtab.update)
   257         (target, make_target ((serial (), seri),
   258           ([], (Code_Symbol.empty_data, Code_Symbol.empty_data))))
   259   end;
   260 
   261 fun add_target (target, seri) = put_target (target, Fundamental seri);
   262 fun extend_target (target, (super, modify)) =
   263   put_target (target, Extension (super, modify));
   264 
   265 fun map_target_data target f thy =
   266   let
   267     val _ = assert_target thy target;
   268   in
   269     thy
   270     |> (Targets.map o apfst o Symtab.map_entry target o map_target o apsnd) f
   271   end;
   272 
   273 fun map_reserved target =
   274   map_target_data target o apfst;
   275 fun map_identifiers target =
   276   map_target_data target o apsnd o apfst;
   277 fun map_printings target =
   278   map_target_data target o apsnd o apsnd;
   279 
   280 fun set_default_code_width k = (Targets.map o apsnd) (K k);
   281 
   282 
   283 (** serializer usage **)
   284 
   285 (* montage *)
   286 
   287 fun the_fundamental thy =
   288   let
   289     val (targets, _) = Targets.get thy;
   290     fun fundamental target = case Symtab.lookup targets target
   291      of SOME data => (case the_description data
   292          of Fundamental data => data
   293           | Extension (super, _) => fundamental super)
   294       | NONE => error ("Unknown code target language: " ^ quote target);
   295   in fundamental end;
   296 
   297 fun the_literals thy = #literals o the_fundamental thy;
   298 
   299 fun collapse_hierarchy thy =
   300   let
   301     val (targets, _) = Targets.get thy;
   302     fun collapse target =
   303       let
   304         val data = case Symtab.lookup targets target
   305          of SOME data => data
   306           | NONE => error ("Unknown code target language: " ^ quote target);
   307       in case the_description data
   308        of Fundamental _ => (I, data)
   309         | Extension (super, modify) => let
   310             val (modify', data') = collapse super
   311           in (modify' #> modify, merge_target false target (data', data)) end
   312       end;
   313   in collapse end;
   314 
   315 local
   316 
   317 fun activate_target thy target =
   318   let
   319     val (_, default_width) = Targets.get thy;
   320     val (modify, data) = collapse_hierarchy thy target;
   321   in (default_width, data, modify) end;
   322 
   323 fun project_program thy syms_hidden syms1 program2 =
   324   let
   325     val ctxt = Proof_Context.init_global thy;
   326     val syms2 = subtract (op =) syms_hidden syms1;
   327     val program3 = Code_Symbol.Graph.restrict (not o member (op =) syms_hidden) program2;
   328     val syms4 = Code_Symbol.Graph.all_succs program3 syms2;
   329     val unimplemented = Code_Thingol.unimplemented program3;
   330     val _ =
   331       if null unimplemented then ()
   332       else error ("No code equations for " ^
   333         commas (map (Proof_Context.markup_const ctxt) unimplemented));
   334     val program4 = Code_Symbol.Graph.restrict (member (op =) syms4) program3;
   335   in (syms4, program4) end;
   336 
   337 fun prepare_serializer thy (serializer : serializer) reserved identifiers
   338     printings module_name args proto_program syms =
   339   let
   340     val syms_hidden = Code_Symbol.symbols_of printings;
   341     val (syms_all, program) = project_program thy syms_hidden syms proto_program;
   342     fun select_include (name, (content, cs)) =
   343       if null cs orelse exists (fn c => member (op =) syms_all (Constant c)) cs
   344       then SOME (name, content) else NONE;
   345     val includes = map_filter select_include (Code_Symbol.dest_module_data printings);
   346   in
   347     (serializer args (Proof_Context.init_global thy) {
   348       module_name = module_name,
   349       reserved_syms = reserved,
   350       identifiers = identifiers,
   351       includes = includes,
   352       const_syntax = Code_Symbol.lookup_constant_data printings,
   353       tyco_syntax = Code_Symbol.lookup_type_constructor_data printings,
   354       class_syntax = Code_Symbol.lookup_type_class_data printings },
   355       (syms_all, program))
   356   end;
   357 
   358 fun mount_serializer thy target some_width module_name args program syms =
   359   let
   360     val (default_width, data, modify) = activate_target thy target;
   361     val serializer = case the_description data
   362      of Fundamental seri => #serializer seri;
   363     val (prepared_serializer, (prepared_syms, prepared_program)) =
   364       prepare_serializer thy serializer
   365         (the_reserved data) (the_identifiers data) (the_printings data)
   366         module_name args (modify program) syms
   367     val width = the_default default_width some_width;
   368   in (fn program => fn syms => prepared_serializer syms program width, (prepared_syms, prepared_program)) end;
   369 
   370 fun invoke_serializer thy target some_width raw_module_name args program all_public syms =
   371   let
   372     val module_name = if raw_module_name = "" then ""
   373       else (check_name true raw_module_name; raw_module_name)
   374     val (mounted_serializer, (prepared_syms, prepared_program)) = mount_serializer thy
   375       target some_width module_name args program syms;
   376   in mounted_serializer prepared_program (if all_public then prepared_syms else []) end;
   377 
   378 fun assert_module_name "" = error "Empty module name not allowed here"
   379   | assert_module_name module_name = module_name;
   380 
   381 fun using_master_directory thy =
   382   Option.map (Path.append (File.pwd ()) o Path.append (Thy_Load.master_directory thy));
   383 
   384 in
   385 
   386 val generatedN = "Generated_Code";
   387 
   388 fun export_code_for thy some_path target some_width module_name args =
   389   export (using_master_directory thy some_path)
   390   ooo invoke_serializer thy target some_width module_name args;
   391 
   392 fun produce_code_for thy target some_width module_name args =
   393   let
   394     val serializer = invoke_serializer thy target some_width (assert_module_name module_name) args;
   395   in fn program => fn all_public => fn syms =>
   396     produce (serializer program all_public syms) |> apsnd (fn deresolve => map deresolve syms)
   397   end;
   398 
   399 fun present_code_for thy target some_width module_name args =
   400   let
   401     val serializer = invoke_serializer thy target some_width (assert_module_name module_name) args;
   402   in fn program => fn (syms, selects) =>
   403     present selects (serializer program false syms)
   404   end;
   405 
   406 fun check_code_for thy target strict args program all_public syms =
   407   let
   408     val { env_var, make_destination, make_command } =
   409       (#check o the_fundamental thy) target;
   410     fun ext_check p =
   411       let
   412         val destination = make_destination p;
   413         val _ = export (SOME destination) (invoke_serializer thy target (SOME 80)
   414           generatedN args program all_public syms);
   415         val cmd = make_command generatedN;
   416       in
   417         if Isabelle_System.bash ("cd " ^ File.shell_path p ^ " && " ^ cmd ^ " 2>&1") <> 0
   418         then error ("Code check failed for " ^ target ^ ": " ^ cmd)
   419         else ()
   420       end;
   421   in
   422     if getenv env_var = ""
   423     then if strict
   424       then error (env_var ^ " not set; cannot check code for " ^ target)
   425       else warning (env_var ^ " not set; skipped checking code for " ^ target)
   426     else Isabelle_System.with_tmp_dir "Code_Test" ext_check
   427   end;
   428 
   429 fun evaluation mounted_serializer prepared_program syms all_public ((vs, ty), t) =
   430   let
   431     val _ = if Code_Thingol.contains_dict_var t then
   432       error "Term to be evaluated contains free dictionaries" else ();
   433     val v' = singleton (Name.variant_list (map fst vs)) "a";
   434     val vs' = (v', []) :: vs;
   435     val ty' = ITyVar v' `-> ty;
   436     val program = prepared_program
   437       |> Code_Symbol.Graph.new_node (Code_Symbol.value,
   438           Code_Thingol.Fun (((vs', ty'), [(([IVar NONE], t), (NONE, true))]), NONE))
   439       |> fold (curry (perhaps o try o
   440           Code_Symbol.Graph.add_edge) Code_Symbol.value) syms;
   441     val (program_code, deresolve) =
   442       produce (mounted_serializer program (if all_public then [] else [Code_Symbol.value]));
   443     val value_name = the (deresolve Code_Symbol.value);
   444   in (program_code, value_name) end;
   445 
   446 fun evaluator thy target program syms =
   447   let
   448     val (mounted_serializer, (_, prepared_program)) =
   449       mount_serializer thy target NONE generatedN [] program syms;
   450   in evaluation mounted_serializer prepared_program syms end;
   451 
   452 end; (* local *)
   453 
   454 
   455 (* code generation *)
   456 
   457 fun prep_destination "" = NONE
   458   | prep_destination s = SOME (Path.explode s);
   459 
   460 fun export_code thy all_public cs seris =
   461   let
   462     val program = Code_Thingol.consts_program thy cs;
   463     val _ = map (fn (((target, module_name), some_path), args) =>
   464       export_code_for thy some_path target NONE module_name args program all_public (map Constant cs)) seris;
   465   in () end;
   466 
   467 fun export_code_cmd all_public raw_cs seris thy =
   468   export_code thy all_public
   469     (Code_Thingol.read_const_exprs thy raw_cs)
   470     ((map o apfst o apsnd) prep_destination seris);
   471 
   472 fun produce_code thy all_public cs target some_width some_module_name args =
   473   let
   474     val program = Code_Thingol.consts_program thy cs;
   475   in produce_code_for thy target some_width some_module_name args program all_public (map Constant cs) end;
   476 
   477 fun present_code thy cs syms target some_width some_module_name args =
   478   let
   479     val program = Code_Thingol.consts_program thy cs;
   480   in present_code_for thy target some_width some_module_name args program (map Constant cs, syms) end;
   481 
   482 fun check_code thy all_public cs seris =
   483   let
   484     val program = Code_Thingol.consts_program thy cs;
   485     val _ = map (fn ((target, strict), args) =>
   486       check_code_for thy target strict args program all_public (map Constant cs)) seris;
   487   in () end;
   488 
   489 fun check_code_cmd all_public raw_cs seris thy =
   490   check_code thy all_public
   491     (Code_Thingol.read_const_exprs thy raw_cs) seris;
   492 
   493 local
   494 
   495 val parse_const_terms = Scan.repeat1 Args.term
   496   >> (fn ts => fn thy => map (Code.check_const thy) ts);
   497 
   498 fun parse_names category parse internalize mark_symbol =
   499   Scan.lift (Args.parens (Args.$$$ category)) |-- Scan.repeat1 parse
   500   >> (fn xs => fn thy => map (mark_symbol o internalize thy) xs);
   501 
   502 val parse_consts = parse_names "consts" Args.term
   503   Code.check_const Constant;
   504 
   505 val parse_types = parse_names "types" (Scan.lift Args.name)
   506   Sign.intern_type Type_Constructor;
   507 
   508 val parse_classes = parse_names "classes" (Scan.lift Args.name)
   509   Sign.intern_class Type_Class;
   510 
   511 val parse_instances = parse_names "instances" (Scan.lift (Args.name --| Args.$$$ "::" -- Args.name))
   512   (fn thy => fn (raw_tyco, raw_class) => (Sign.intern_class thy raw_tyco, Sign.intern_type thy raw_class))
   513     Class_Instance;
   514 
   515 in
   516 
   517 val antiq_setup =
   518   Thy_Output.antiquotation @{binding code_stmts}
   519     (parse_const_terms --
   520       Scan.repeat (parse_consts || parse_types || parse_classes || parse_instances)
   521       -- Scan.lift (Args.parens (Args.name -- Scan.option Parse.int)))
   522     (fn {context = ctxt, ...} => fn ((mk_cs, mk_stmtss), (target, some_width)) =>
   523       let val thy = Proof_Context.theory_of ctxt in
   524         present_code thy (mk_cs thy)
   525           (maps (fn f => f thy) mk_stmtss)
   526           target some_width "Example" []
   527       end);
   528 
   529 end;
   530 
   531 
   532 (** serializer configuration **)
   533 
   534 (* reserved symbol names *)
   535 
   536 fun add_reserved target sym thy =
   537   let
   538     val (_, data) = collapse_hierarchy thy target;
   539     val _ = if member (op =) (the_reserved data) sym
   540       then error ("Reserved symbol " ^ quote sym ^ " already declared")
   541       else ();
   542   in
   543     thy
   544     |> map_reserved target (insert (op =) sym)
   545   end;
   546 
   547 
   548 (* checking of syntax *)
   549 
   550 fun check_const_syntax thy target c syn =
   551   if Code_Printer.requires_args syn > Code.args_number thy c
   552   then error ("Too many arguments in syntax for constant " ^ quote c)
   553   else Code_Printer.prep_const_syntax thy (the_literals thy target) c syn;
   554 
   555 fun check_tyco_syntax thy target tyco syn =
   556   if fst syn <> Sign.arity_number thy tyco
   557   then error ("Number of arguments mismatch in syntax for type constructor " ^ quote tyco)
   558   else syn;
   559 
   560 
   561 (* custom symbol names *)
   562 
   563 fun arrange_name_decls x =
   564   let
   565     fun arrange is_module (sym, target_names) = map (fn (target, some_name) =>
   566       (target, (sym, Option.map (check_name is_module) some_name))) target_names;
   567   in
   568     Code_Symbol.maps_attr' (arrange false) (arrange false) (arrange false)
   569       (arrange false) (arrange false) (arrange true) x
   570   end;
   571 
   572 fun cert_name_decls thy = cert_syms thy #> arrange_name_decls;
   573 
   574 fun read_name_decls thy = read_syms thy #> arrange_name_decls;
   575 
   576 fun set_identifier (target, sym_name) = map_identifiers target (Code_Symbol.set_data sym_name);
   577 
   578 fun gen_set_identifiers prep_name_decl raw_name_decls thy =
   579   fold set_identifier (prep_name_decl thy raw_name_decls) thy;
   580 
   581 val set_identifiers = gen_set_identifiers cert_name_decls;
   582 val set_identifiers_cmd = gen_set_identifiers read_name_decls;
   583 
   584 
   585 (* custom printings *)
   586 
   587 fun arrange_printings prep_const thy =
   588   let
   589     fun arrange check (sym, target_syns) =
   590       map (fn (target, some_syn) => (target, (sym, Option.map (check thy target sym) some_syn))) target_syns;
   591   in
   592     Code_Symbol.maps_attr'
   593       (arrange check_const_syntax) (arrange check_tyco_syntax)
   594         (arrange ((K o K o K) I)) (arrange ((K o K o K) I)) (arrange ((K o K o K) I))
   595         (arrange (fn thy => fn _ => fn _ => fn (raw_content, raw_cs) =>
   596           (Code_Printer.str raw_content, map (prep_const thy) raw_cs)))
   597   end;
   598 
   599 fun cert_printings thy = cert_syms thy #> arrange_printings cert_const thy;
   600 
   601 fun read_printings thy = read_syms thy #> arrange_printings Code.read_const thy;
   602 
   603 fun set_printing (target, sym_syn) = map_printings target (Code_Symbol.set_data sym_syn);
   604 
   605 fun gen_set_printings prep_print_decl raw_print_decls thy =
   606   fold set_printing (prep_print_decl thy raw_print_decls) thy;
   607 
   608 val set_printings = gen_set_printings cert_printings;
   609 val set_printings_cmd = gen_set_printings read_printings;
   610 
   611 
   612 (* concrete syntax *)
   613 
   614 fun parse_args f args =
   615   case Scan.read Token.stopper f args
   616    of SOME x => x
   617     | NONE => error "Bad serializer arguments";
   618 
   619 
   620 (** Isar setup **)
   621 
   622 fun parse_single_symbol_pragma parse_keyword parse_isa parse_target =
   623   parse_keyword |-- Parse.!!! (parse_isa --| (@{keyword "\<rightharpoonup>"} || @{keyword "=>"})
   624     -- Parse.and_list1 (@{keyword "("} |-- (Parse.name --| @{keyword ")"} -- Scan.option parse_target)));
   625 
   626 fun parse_symbol_pragma parse_const parse_tyco parse_class parse_classrel parse_inst parse_module =
   627   parse_single_symbol_pragma @{keyword "constant"} Parse.term parse_const
   628     >> Constant
   629   || parse_single_symbol_pragma @{keyword "type_constructor"} Parse.type_const parse_tyco
   630     >> Type_Constructor
   631   || parse_single_symbol_pragma @{keyword "type_class"} Parse.class parse_class
   632     >> Type_Class
   633   || parse_single_symbol_pragma @{keyword "class_relation"} parse_classrel_ident parse_classrel
   634     >> Class_Relation
   635   || parse_single_symbol_pragma @{keyword "class_instance"} parse_inst_ident parse_inst
   636     >> Class_Instance
   637   || parse_single_symbol_pragma @{keyword "code_module"} Parse.name parse_module
   638     >> Code_Symbol.Module;
   639 
   640 fun parse_symbol_pragmas parse_const parse_tyco parse_class parse_classrel parse_inst parse_module =
   641   Parse.enum1 "|" (Parse.group (fn () => "code symbol pragma")
   642     (parse_symbol_pragma parse_const parse_tyco parse_class parse_classrel parse_inst parse_module));
   643 
   644 val code_expr_argsP = Scan.optional (@{keyword "("} |-- Args.parse --| @{keyword ")"}) [];
   645 
   646 fun code_expr_inP all_public raw_cs =
   647   Scan.repeat (@{keyword "in"} |-- Parse.!!! (Parse.name
   648     -- Scan.optional (@{keyword "module_name"} |-- Parse.name) ""
   649     -- Scan.optional (@{keyword "file"} |-- Parse.name) ""
   650     -- code_expr_argsP))
   651       >> (fn seri_args => export_code_cmd all_public raw_cs seri_args);
   652 
   653 fun code_expr_checkingP all_public raw_cs =
   654   (@{keyword "checking"} |-- Parse.!!!
   655     (Scan.repeat (Parse.name -- ((@{keyword "?"} |-- Scan.succeed false) || Scan.succeed true)
   656     -- code_expr_argsP)))
   657       >> (fn seri_args => check_code_cmd all_public raw_cs seri_args);
   658 
   659 val code_exprP = (Scan.optional (@{keyword "open"} |-- Scan.succeed true) false
   660   -- Scan.repeat1 Parse.term)
   661   :|-- (fn (all_public, raw_cs) => (code_expr_checkingP all_public raw_cs || code_expr_inP all_public raw_cs));
   662 
   663 val _ =
   664   Outer_Syntax.command @{command_spec "code_reserved"}
   665     "declare words as reserved for target language"
   666     (Parse.name -- Scan.repeat1 Parse.name
   667       >> (fn (target, reserveds) => (Toplevel.theory o fold (add_reserved target)) reserveds));
   668 
   669 val _ =
   670   Outer_Syntax.command @{command_spec "code_identifier"} "declare mandatory names for code symbols"
   671     (parse_symbol_pragmas Parse.name Parse.name Parse.name Parse.name Parse.name Parse.name
   672       >> (Toplevel.theory o fold set_identifiers_cmd));
   673 
   674 val _ =
   675   Outer_Syntax.command @{command_spec "code_printing"} "declare dedicated printing for code symbols"
   676     (parse_symbol_pragmas (Code_Printer.parse_const_syntax) (Code_Printer.parse_tyco_syntax)
   677       Parse.string (Parse.minus >> K ()) (Parse.minus >> K ())
   678       (Parse.text -- Scan.optional (@{keyword "attach"} |-- Scan.repeat1 Parse.term) [])
   679       >> (Toplevel.theory o fold set_printings_cmd));
   680 
   681 val _ =
   682   Outer_Syntax.command @{command_spec "export_code"} "generate executable code for constants"
   683     (Parse.!!! code_exprP >> (fn f => Toplevel.keep (f o Toplevel.theory_of)));
   684 
   685 
   686 (** external entrance point -- for codegen tool **)
   687 
   688 fun codegen_tool thyname cmd_expr =
   689   let
   690     val thy = Thy_Info.get_theory thyname;
   691     val parse = Scan.read Token.stopper (Parse.!!! code_exprP) o
   692       (filter Token.is_proper o Outer_Syntax.scan Position.none);
   693   in case parse cmd_expr
   694    of SOME f => (writeln "Now generating code..."; f thy)
   695     | NONE => error ("Bad directive " ^ quote cmd_expr)
   696   end;
   697 
   698 
   699 (** theory setup **)
   700 
   701 val setup = antiq_setup;
   702 
   703 end; (*struct*)