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