src/Tools/Code/code_target.ML
author haftmann
Tue, 31 Aug 2010 14:21:06 +0200
changeset 39152 24f82786cc57
parent 39151 ced825abdc1d
child 39153 544f4702d621
permissions -rw-r--r--
record argument for serializers
     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 option -> Token.T list
    13     -> Code_Thingol.naming -> Code_Thingol.program -> string list -> unit
    14   val produce_code_for: theory -> string -> int option -> string option -> Token.T list
    15     -> Code_Thingol.naming -> Code_Thingol.program -> string list * string list -> string * string option list
    16   val check_code_for: theory -> string -> bool -> Token.T list
    17     -> Code_Thingol.naming -> Code_Thingol.program -> string list -> unit
    18 
    19   val export_code: theory -> string list
    20     -> (((string * string option) * Path.T option) * Token.T list) list -> unit
    21   val produce_code: theory -> string list -> (Code_Thingol.naming -> string list)
    22     -> string -> int option -> string option -> Token.T list -> string * string option list
    23   val check_code: theory -> string list
    24     -> ((string * bool) * Token.T list) list -> unit
    25 
    26   val shell_command: string (*theory name*) -> string (*export_code expr*) -> unit
    27 
    28   type serializer
    29   type literals = Code_Printer.literals
    30   val add_target: string * { serializer: serializer, literals: literals,
    31     check: { env_var: string, make_destination: Path.T -> Path.T,
    32       make_command: string -> string -> string } } -> theory -> theory
    33   val extend_target: string *
    34       (string * (Code_Thingol.naming -> Code_Thingol.program -> Code_Thingol.program))
    35     -> theory -> theory
    36   val assert_target: theory -> string -> string
    37   val the_literals: theory -> string -> literals
    38   type serialization
    39   val parse_args: 'a parser -> Token.T list -> 'a
    40   val serialization: (int -> Path.T option -> 'a -> unit)
    41     -> (int -> 'a -> string * string option list)
    42     -> 'a -> serialization
    43   val set_default_code_width: int -> theory -> theory
    44 
    45   val allow_abort: string -> theory -> theory
    46   type tyco_syntax = Code_Printer.tyco_syntax
    47   type const_syntax = Code_Printer.const_syntax
    48   val add_class_syntax: string -> class -> string option -> theory -> theory
    49   val add_instance_syntax: string -> class * string -> unit option -> theory -> theory
    50   val add_tyco_syntax: string -> string -> tyco_syntax option -> theory -> theory
    51   val add_const_syntax: string -> string -> const_syntax option -> theory -> theory
    52   val add_reserved: string -> string -> theory -> theory
    53   val add_include: string -> string * (string * string list) option -> theory -> theory
    54 end;
    55 
    56 structure Code_Target : CODE_TARGET =
    57 struct
    58 
    59 open Basic_Code_Thingol;
    60 
    61 type literals = Code_Printer.literals;
    62 type tyco_syntax = Code_Printer.tyco_syntax;
    63 type const_syntax = Code_Printer.const_syntax;
    64 
    65 
    66 (** abstract nonsense **)
    67 
    68 datatype destination = File of Path.T option | String of string list;
    69 type serialization = int -> destination -> (string * string option list) option;
    70 
    71 fun stmt_names_of_destination (String stmt_names) = stmt_names
    72   | stmt_names_of_destination _ = [];
    73 
    74 fun serialization output _ content width (File some_path) = (output width some_path content; NONE)
    75   | serialization _ string content width (String _) = SOME (string width content);
    76 
    77 fun file some_path f = (f (File some_path); ());
    78 fun string stmt_names f = the (f (String stmt_names));
    79 
    80 
    81 (** theory data **)
    82 
    83 datatype symbol_syntax_data = Symbol_Syntax_Data of {
    84   class: string Symtab.table,
    85   instance: unit Symreltab.table,
    86   tyco: Code_Printer.tyco_syntax Symtab.table,
    87   const: Code_Printer.const_syntax Symtab.table
    88 };
    89 
    90 fun make_symbol_syntax_data ((class, instance), (tyco, const)) =
    91   Symbol_Syntax_Data { class = class, instance = instance, tyco = tyco, const = const };
    92 fun map_symbol_syntax_data f (Symbol_Syntax_Data { class, instance, tyco, const }) =
    93   make_symbol_syntax_data (f ((class, instance), (tyco, const)));
    94 fun merge_symbol_syntax_data
    95   (Symbol_Syntax_Data { class = class1, instance = instance1, tyco = tyco1, const = const1 },
    96     Symbol_Syntax_Data { class = class2, instance = instance2, tyco = tyco2, const = const2 }) =
    97   make_symbol_syntax_data (
    98     (Symtab.join (K snd) (class1, class2),
    99        Symreltab.join (K snd) (instance1, instance2)),
   100     (Symtab.join (K snd) (tyco1, tyco2),
   101        Symtab.join (K snd) (const1, const2))
   102   );
   103 
   104 type serializer = Token.T list (*arguments*) -> {
   105     labelled_name: string -> string,
   106     reserved_syms: string list,
   107     includes: (string * Pretty.T) list,
   108     single_module: bool,
   109     module_alias: string -> string option,
   110     class_syntax: string -> string option,
   111     tyco_syntax: string -> Code_Printer.tyco_syntax option,
   112     const_syntax: string -> Code_Printer.activated_const_syntax option,
   113     program: Code_Thingol.program,
   114     names: string list,
   115     presentation_names: string list }
   116   -> serialization;
   117 
   118 datatype description = Fundamental of { serializer: serializer,
   119       literals: literals,
   120       check: { env_var: string, make_destination: Path.T -> Path.T,
   121         make_command: string -> string -> string } }
   122   | Extension of string *
   123       (Code_Thingol.naming -> Code_Thingol.program -> Code_Thingol.program);
   124 
   125 datatype target = Target of {
   126   serial: serial,
   127   description: description,
   128   reserved: string list,
   129   includes: (Pretty.T * string list) Symtab.table,
   130   module_alias: string Symtab.table,
   131   symbol_syntax: symbol_syntax_data
   132 };
   133 
   134 fun make_target ((serial, description), ((reserved, includes), (module_alias, symbol_syntax))) =
   135   Target { serial = serial, description = description, reserved = reserved, 
   136     includes = includes, module_alias = module_alias, symbol_syntax = symbol_syntax };
   137 fun map_target f ( Target { serial, description, reserved, includes, module_alias, symbol_syntax } ) =
   138   make_target (f ((serial, description), ((reserved, includes), (module_alias, symbol_syntax))));
   139 fun merge_target strict target (Target { serial = serial1, description = description,
   140   reserved = reserved1, includes = includes1,
   141   module_alias = module_alias1, symbol_syntax = symbol_syntax1 },
   142     Target { serial = serial2, description = _,
   143       reserved = reserved2, includes = includes2,
   144       module_alias = module_alias2, symbol_syntax = symbol_syntax2 }) =
   145   if serial1 = serial2 orelse not strict then
   146     make_target ((serial1, description),
   147       ((merge (op =) (reserved1, reserved2), Symtab.join (K snd) (includes1, includes2)),
   148         (Symtab.join (K snd) (module_alias1, module_alias2),
   149           merge_symbol_syntax_data (symbol_syntax1, symbol_syntax2))
   150     ))
   151   else
   152     error ("Incompatible targets: " ^ quote target);
   153 
   154 fun the_description (Target { description, ... }) = description;
   155 fun the_reserved (Target { reserved, ... }) = reserved;
   156 fun the_includes (Target { includes, ... }) = includes;
   157 fun the_module_alias (Target { module_alias , ... }) = module_alias;
   158 fun the_symbol_syntax (Target { symbol_syntax = Symbol_Syntax_Data x, ... }) = x;
   159 
   160 structure Targets = Theory_Data
   161 (
   162   type T = (target Symtab.table * string list) * int;
   163   val empty = ((Symtab.empty, []), 80);
   164   val extend = I;
   165   fun merge (((target1, exc1), width1), ((target2, exc2), width2)) : T =
   166     ((Symtab.join (merge_target true) (target1, target2),
   167       Library.merge (op =) (exc1, exc2)), Int.max (width1, width2));
   168 );
   169 
   170 val abort_allowed = snd o fst o Targets.get;
   171 
   172 fun assert_target thy target = if Symtab.defined ((fst o fst) (Targets.get thy)) target
   173   then target
   174   else error ("Unknown code target language: " ^ quote target);
   175 
   176 fun put_target (target, seri) thy =
   177   let
   178     val lookup_target = Symtab.lookup ((fst o fst) (Targets.get thy));
   179     val _ = case seri
   180      of Extension (super, _) => if is_some (lookup_target super) then ()
   181           else error ("Unknown code target language: " ^ quote super)
   182       | _ => ();
   183     val overwriting = case (Option.map the_description o lookup_target) target
   184      of NONE => false
   185       | SOME (Extension _) => true
   186       | SOME (Fundamental _) => (case seri
   187          of Extension _ => error ("Will not overwrite existing target " ^ quote target)
   188           | _ => true);
   189     val _ = if overwriting
   190       then warning ("Overwriting existing target " ^ quote target)
   191       else (); 
   192   in
   193     thy
   194     |> (Targets.map o apfst o apfst o Symtab.update)
   195           (target, make_target ((serial (), seri), (([], Symtab.empty),
   196             (Symtab.empty, make_symbol_syntax_data ((Symtab.empty, Symreltab.empty),
   197               (Symtab.empty, Symtab.empty))))))
   198   end;
   199 
   200 fun add_target (target, seri) = put_target (target, Fundamental seri);
   201 fun extend_target (target, (super, modify)) =
   202   put_target (target, Extension (super, modify));
   203 
   204 fun map_target_data target f thy =
   205   let
   206     val _ = assert_target thy target;
   207   in
   208     thy
   209     |> (Targets.map o apfst o apfst o Symtab.map_entry target o map_target) f
   210   end;
   211 
   212 fun map_reserved target =
   213   map_target_data target o apsnd o apfst o apfst;
   214 fun map_includes target =
   215   map_target_data target o apsnd o apfst o apsnd;
   216 fun map_module_alias target =
   217   map_target_data target o apsnd o apsnd o apfst;
   218 fun map_symbol_syntax target =
   219   map_target_data target o apsnd o apsnd o apsnd o map_symbol_syntax_data;
   220 
   221 fun set_default_code_width k = (Targets.map o apsnd) (K k);
   222 
   223 
   224 (** serializer usage **)
   225 
   226 (* montage *)
   227 
   228 fun the_fundamental thy =
   229   let
   230     val ((targets, _), _) = Targets.get thy;
   231     fun fundamental target = case Symtab.lookup targets target
   232      of SOME data => (case the_description data
   233          of Fundamental data => data
   234           | Extension (super, _) => fundamental super)
   235       | NONE => error ("Unknown code target language: " ^ quote target);
   236   in fundamental end;
   237 
   238 fun the_literals thy = #literals o the_fundamental thy;
   239 
   240 local
   241 
   242 fun activate_syntax lookup_name src_tab = Symtab.empty
   243   |> fold_map (fn thing_identifier => fn tab => case lookup_name thing_identifier
   244        of SOME name => (SOME name,
   245             Symtab.update_new (name, the (Symtab.lookup src_tab thing_identifier)) tab)
   246         | NONE => (NONE, tab)) (Symtab.keys src_tab)
   247   |>> map_filter I;
   248 
   249 fun activate_const_syntax thy literals src_tab naming = (Symtab.empty, naming)
   250   |> fold_map (fn c => fn (tab, naming) =>
   251       case Code_Thingol.lookup_const naming c
   252        of SOME name => let
   253               val (syn, naming') = Code_Printer.activate_const_syntax thy
   254                 literals c (the (Symtab.lookup src_tab c)) naming
   255             in (SOME name, (Symtab.update_new (name, syn) tab, naming')) end
   256         | NONE => (NONE, (tab, naming))) (Symtab.keys src_tab)
   257   |>> map_filter I;
   258 
   259 fun invoke_serializer thy abortable serializer literals reserved abs_includes 
   260     module_alias class instance tyco const module_name args naming program2 (names1, presentation_names) width =
   261   let
   262     val (names_class, class') =
   263       activate_syntax (Code_Thingol.lookup_class naming) class;
   264     val names_inst = map_filter (Code_Thingol.lookup_instance naming)
   265       (Symreltab.keys instance);
   266     val (names_tyco, tyco') =
   267       activate_syntax (Code_Thingol.lookup_tyco naming) tyco;
   268     val (names_const, (const', _)) =
   269       activate_const_syntax thy literals const naming;
   270     val names_hidden = names_class @ names_inst @ names_tyco @ names_const;
   271     val names2 = subtract (op =) names_hidden names1;
   272     val program3 = Graph.subgraph (not o member (op =) names_hidden) program2;
   273     val names_all = Graph.all_succs program3 names2;
   274     val includes = abs_includes names_all;
   275     val program4 = Graph.subgraph (member (op =) names_all) program3;
   276     val empty_funs = filter_out (member (op =) abortable)
   277       (Code_Thingol.empty_funs program3);
   278     val _ = if null empty_funs then () else error ("No code equations for "
   279       ^ commas (map (Sign.extern_const thy) empty_funs));
   280   in
   281     serializer args {
   282       labelled_name = Code_Thingol.labelled_name thy program2,
   283       reserved_syms = reserved,
   284       includes = includes,
   285       single_module = is_some module_name,
   286       module_alias = if is_some module_name then K module_name else Symtab.lookup module_alias,
   287       class_syntax = Symtab.lookup class',
   288       tyco_syntax = Symtab.lookup tyco',
   289       const_syntax = Symtab.lookup const',
   290       program = program3,
   291       names = names1,
   292       presentation_names = presentation_names } width
   293   end;
   294 
   295 fun mount_serializer thy target some_width raw_module_name args naming program names destination =
   296   let
   297     val ((targets, abortable), default_width) = Targets.get thy;
   298     fun collapse_hierarchy target =
   299       let
   300         val data = case Symtab.lookup targets target
   301          of SOME data => data
   302           | NONE => error ("Unknown code target language: " ^ quote target);
   303       in case the_description data
   304        of Fundamental _ => (I, data)
   305         | Extension (super, modify) => let
   306             val (modify', data') = collapse_hierarchy super
   307           in (modify' #> modify naming, merge_target false target (data', data)) end
   308       end;
   309     val (modify, data) = collapse_hierarchy target;
   310     val serializer = case the_description data
   311     of Fundamental seri => #serializer seri;
   312     val presentation_names = stmt_names_of_destination destination;
   313     val module_name = if null presentation_names
   314       then raw_module_name else SOME "Code";
   315     val reserved = the_reserved data;
   316     fun select_include names_all (name, (content, cs)) =
   317       if null cs then SOME (name, content)
   318       else if exists (fn c => case Code_Thingol.lookup_const naming c
   319        of SOME name => member (op =) names_all name
   320         | NONE => false) cs
   321       then SOME (name, content) else NONE;
   322     fun includes names_all = map_filter (select_include names_all)
   323       ((Symtab.dest o the_includes) data);
   324     val module_alias = the_module_alias data 
   325     val { class, instance, tyco, const } = the_symbol_syntax data;
   326     val literals = the_literals thy target;
   327     val width = the_default default_width some_width;
   328   in
   329     invoke_serializer thy abortable serializer literals reserved
   330       includes module_alias class instance tyco const module_name args
   331         naming (modify program) (names, presentation_names) width destination
   332   end;
   333 
   334 in
   335 
   336 fun export_code_for thy some_path target some_width some_module_name args naming program names =
   337   file some_path (mount_serializer thy target some_width some_module_name args naming program names);
   338 
   339 fun produce_code_for thy target some_width some_module_name args naming program (names, selects) =
   340   string selects (mount_serializer thy target some_width some_module_name args naming program names);
   341 
   342 fun check_code_for thy target strict args naming program names_cs =
   343   let
   344     val module_name = "Code_Test";
   345     val { env_var, make_destination, make_command } =
   346       (#check o the_fundamental thy) target;
   347     val env_param = getenv env_var;
   348     fun ext_check env_param p =
   349       let 
   350         val destination = make_destination p;
   351         val _ = file (SOME destination) (mount_serializer thy target (SOME 80)
   352           (SOME module_name) args naming program names_cs);
   353         val cmd = make_command env_param module_name;
   354       in if bash ("cd " ^ File.shell_path p ^ " && " ^ cmd ^ " 2>&1") <> 0
   355         then error ("Code check failed for " ^ target ^ ": " ^ cmd)
   356         else ()
   357       end;
   358   in if env_param = ""
   359     then if strict
   360       then error (env_var ^ " not set; cannot check code for " ^ target)
   361       else warning (env_var ^ " not set; skipped checking code for " ^ target)
   362     else Cache_IO.with_tmp_dir "Code_Test" (ext_check env_param)
   363   end;
   364 
   365 end; (* local *)
   366 
   367 
   368 (* code generation *)
   369 
   370 fun transitivly_non_empty_funs thy naming program =
   371   let
   372     val cs = subtract (op =) (abort_allowed thy) (Code_Thingol.empty_funs program);
   373     val names = map_filter (Code_Thingol.lookup_const naming) cs;
   374   in subtract (op =) (Graph.all_preds program names) (Graph.keys program) end;
   375 
   376 fun read_const_exprs thy cs =
   377   let
   378     val (cs1, cs2) = Code_Thingol.read_const_exprs thy cs;
   379     val (names2, (naming, program)) = Code_Thingol.consts_program thy true cs2;
   380     val names3 = transitivly_non_empty_funs thy naming program;
   381     val cs3 = map_filter (fn (c, name) =>
   382       if member (op =) names3 name then SOME c else NONE) (cs2 ~~ names2);
   383   in union (op =) cs3 cs1 end;
   384 
   385 fun prep_destination "" = NONE
   386   | prep_destination "-" = NONE
   387   | prep_destination s = SOME (Path.explode s);
   388 
   389 fun export_code thy cs seris =
   390   let
   391     val (names_cs, (naming, program)) = Code_Thingol.consts_program thy false cs;
   392     val _ = map (fn (((target, module_name), some_path), args) =>
   393       export_code_for thy some_path target NONE module_name args naming program names_cs) seris;
   394   in () end;
   395 
   396 fun export_code_cmd raw_cs seris thy = export_code thy (read_const_exprs thy raw_cs)
   397   ((map o apfst o apsnd) prep_destination seris);
   398 
   399 fun produce_code thy cs names_stmt target some_width some_module_name args =
   400   let
   401     val (names_cs, (naming, program)) = Code_Thingol.consts_program thy false cs;
   402   in produce_code_for thy target some_width some_module_name args naming program (names_cs, names_stmt naming) end;
   403 
   404 fun check_code thy cs seris =
   405   let
   406     val (names_cs, (naming, program)) = Code_Thingol.consts_program thy false cs;
   407     val _ = map (fn ((target, strict), args) =>
   408       check_code_for thy target strict args naming program names_cs) seris;
   409   in () end;
   410 
   411 fun check_code_cmd raw_cs seris thy = check_code thy (read_const_exprs thy raw_cs) seris;
   412 
   413 
   414 (** serializer configuration **)
   415 
   416 (* data access *)
   417 
   418 fun cert_class thy class =
   419   let
   420     val _ = AxClass.get_info thy class;
   421   in class end;
   422 
   423 fun read_class thy = cert_class thy o Sign.intern_class thy;
   424 
   425 fun cert_tyco thy tyco =
   426   let
   427     val _ = if Sign.declared_tyname thy tyco then ()
   428       else error ("No such type constructor: " ^ quote tyco);
   429   in tyco end;
   430 
   431 fun read_tyco thy = cert_tyco thy o Sign.intern_type thy;
   432 
   433 fun cert_inst thy (class, tyco) =
   434   (cert_class thy class, cert_tyco thy tyco);
   435 
   436 fun read_inst thy (raw_tyco, raw_class) =
   437   (read_class thy raw_class, read_tyco thy raw_tyco);
   438 
   439 fun gen_add_syntax (mapp, upd, del) prep_x prep_syn target raw_x some_raw_syn thy =
   440   let
   441     val x = prep_x thy raw_x;
   442     val change = case some_raw_syn
   443      of SOME raw_syn => upd (x, prep_syn thy x raw_syn)
   444       | NONE => del x;
   445   in (map_symbol_syntax target o mapp) change thy end;
   446 
   447 fun gen_add_class_syntax prep_class =
   448   gen_add_syntax (apfst o apfst, Symtab.update, Symtab.delete_safe) prep_class ((K o K) I);
   449 
   450 fun gen_add_instance_syntax prep_inst =
   451   gen_add_syntax (apfst o apsnd, Symreltab.update, Symreltab.delete_safe) prep_inst ((K o K) I);
   452 
   453 fun gen_add_tyco_syntax prep_tyco =
   454   gen_add_syntax (apsnd o apfst, Symtab.update, Symtab.delete_safe) prep_tyco
   455     (fn thy => fn tyco => fn syn => if fst syn <> Sign.arity_number thy tyco
   456       then error ("Number of arguments mismatch in syntax for type constructor " ^ quote tyco)
   457       else syn);
   458 
   459 fun gen_add_const_syntax prep_const =
   460   gen_add_syntax (apsnd o apsnd, Symtab.update, Symtab.delete_safe) prep_const
   461     (fn thy => fn c => fn syn =>
   462       if Code_Printer.requires_args syn > Code.args_number thy c
   463       then error ("Too many arguments in syntax for constant " ^ quote c)
   464       else syn);
   465 
   466 fun add_reserved target =
   467   let
   468     fun add sym syms = if member (op =) syms sym
   469       then error ("Reserved symbol " ^ quote sym ^ " already declared")
   470       else insert (op =) sym syms
   471   in map_reserved target o add end;
   472 
   473 fun gen_add_include read_const target args thy =
   474   let
   475     fun add (name, SOME (content, raw_cs)) incls =
   476           let
   477             val _ = if Symtab.defined incls name
   478               then warning ("Overwriting existing include " ^ name)
   479               else ();
   480             val cs = map (read_const thy) raw_cs;
   481           in Symtab.update (name, (Code_Printer.str content, cs)) incls end
   482       | add (name, NONE) incls = Symtab.delete name incls;
   483   in map_includes target (add args) thy end;
   484 
   485 val add_include = gen_add_include (K I);
   486 val add_include_cmd = gen_add_include Code.read_const;
   487 
   488 fun add_module_alias target (thyname, modlname) =
   489   let
   490     val xs = Long_Name.explode modlname;
   491     val xs' = map (Name.desymbolize true) xs;
   492   in if xs' = xs
   493     then map_module_alias target (Symtab.update (thyname, modlname))
   494     else error ("Invalid module name: " ^ quote modlname ^ "\n"
   495       ^ "perhaps try " ^ quote (Long_Name.implode xs'))
   496   end;
   497 
   498 fun gen_allow_abort prep_const raw_c thy =
   499   let
   500     val c = prep_const thy raw_c;
   501   in thy |> (Targets.map o apfst o apsnd) (insert (op =) c) end;
   502 
   503 
   504 (* concrete syntax *)
   505 
   506 local
   507 
   508 fun zip_list (x::xs) f g =
   509   f
   510   :|-- (fn y =>
   511     fold_map (fn x => g |-- f >> pair x) xs
   512     :|-- (fn xys => pair ((x, y) :: xys)));
   513 
   514 fun process_multi_syntax parse_thing parse_syntax change =
   515   (Parse.and_list1 parse_thing
   516   :|-- (fn things => Scan.repeat1 (Parse.$$$ "(" |-- Parse.name --
   517         (zip_list things parse_syntax (Parse.$$$ "and")) --| Parse.$$$ ")")))
   518   >> (Toplevel.theory oo fold)
   519     (fn (target, syns) => fold (fn (raw_x, syn) => change target raw_x syn) syns);
   520 
   521 in
   522 
   523 val add_class_syntax = gen_add_class_syntax cert_class;
   524 val add_instance_syntax = gen_add_instance_syntax cert_inst;
   525 val add_tyco_syntax = gen_add_tyco_syntax cert_tyco;
   526 val add_const_syntax = gen_add_const_syntax (K I);
   527 val allow_abort = gen_allow_abort (K I);
   528 val add_reserved = add_reserved;
   529 val add_include = add_include;
   530 
   531 val add_class_syntax_cmd = gen_add_class_syntax read_class;
   532 val add_instance_syntax_cmd = gen_add_instance_syntax read_inst;
   533 val add_tyco_syntax_cmd = gen_add_tyco_syntax read_tyco;
   534 val add_const_syntax_cmd = gen_add_const_syntax Code.read_const;
   535 val allow_abort_cmd = gen_allow_abort Code.read_const;
   536 
   537 fun parse_args f args =
   538   case Scan.read Token.stopper f args
   539    of SOME x => x
   540     | NONE => error "Bad serializer arguments";
   541 
   542 
   543 (** Isar setup **)
   544 
   545 val (inK, module_nameK, fileK, checkingK) = ("in", "module_name", "file", "checking");
   546 
   547 val code_expr_argsP = Scan.optional (Parse.$$$ "(" |-- Args.parse --| Parse.$$$ ")") [];
   548 
   549 val code_exprP =
   550   Scan.repeat1 Parse.term_group :|-- (fn raw_cs =>
   551     ((Parse.$$$ checkingK |-- Scan.repeat (Parse.name
   552       -- ((Parse.$$$ "?" |-- Scan.succeed false) || Scan.succeed true) -- code_expr_argsP))
   553       >> (fn seris => check_code_cmd raw_cs seris)
   554     || Scan.repeat (Parse.$$$ inK |-- Parse.name
   555        -- Scan.option (Parse.$$$ module_nameK |-- Parse.name)
   556        -- Scan.optional (Parse.$$$ fileK |-- Parse.name) ""
   557        -- code_expr_argsP) >> (fn seris => export_code_cmd raw_cs seris)));
   558 
   559 val _ = List.app Keyword.keyword [inK, module_nameK, fileK, checkingK];
   560 
   561 val _ =
   562   Outer_Syntax.command "code_class" "define code syntax for class" Keyword.thy_decl (
   563     process_multi_syntax Parse.xname (Scan.option Parse.string)
   564     add_class_syntax_cmd);
   565 
   566 val _ =
   567   Outer_Syntax.command "code_instance" "define code syntax for instance" Keyword.thy_decl (
   568     process_multi_syntax (Parse.xname --| Parse.$$$ "::" -- Parse.xname)
   569       (Scan.option (Parse.minus >> K ()))
   570     add_instance_syntax_cmd);
   571 
   572 val _ =
   573   Outer_Syntax.command "code_type" "define code syntax for type constructor" Keyword.thy_decl (
   574     process_multi_syntax Parse.xname Code_Printer.parse_tyco_syntax
   575     add_tyco_syntax_cmd);
   576 
   577 val _ =
   578   Outer_Syntax.command "code_const" "define code syntax for constant" Keyword.thy_decl (
   579     process_multi_syntax Parse.term_group Code_Printer.parse_const_syntax
   580     add_const_syntax_cmd);
   581 
   582 val _ =
   583   Outer_Syntax.command "code_reserved" "declare words as reserved for target language"
   584     Keyword.thy_decl (
   585     Parse.name -- Scan.repeat1 Parse.name
   586     >> (fn (target, reserveds) => (Toplevel.theory o fold (add_reserved target)) reserveds)
   587   );
   588 
   589 val _ =
   590   Outer_Syntax.command "code_include" "declare piece of code to be included in generated code"
   591     Keyword.thy_decl (
   592     Parse.name -- Parse.name -- (Parse.text :|-- (fn "-" => Scan.succeed NONE
   593       | s => Scan.optional (Parse.$$$ "attach" |-- Scan.repeat1 Parse.term) [] >> pair s >> SOME))
   594     >> (fn ((target, name), content_consts) =>
   595         (Toplevel.theory o add_include_cmd target) (name, content_consts))
   596   );
   597 
   598 val _ =
   599   Outer_Syntax.command "code_modulename" "alias module to other name" Keyword.thy_decl (
   600     Parse.name -- Scan.repeat1 (Parse.name -- Parse.name)
   601     >> (fn (target, modlnames) => (Toplevel.theory o fold (add_module_alias target)) modlnames)
   602   );
   603 
   604 val _ =
   605   Outer_Syntax.command "code_abort" "permit constant to be implemented as program abort"
   606     Keyword.thy_decl (
   607     Scan.repeat1 Parse.term_group >> (Toplevel.theory o fold allow_abort_cmd)
   608   );
   609 
   610 val _ =
   611   Outer_Syntax.command "export_code" "generate executable code for constants"
   612     Keyword.diag (Parse.!!! code_exprP >> (fn f => Toplevel.keep (f o Toplevel.theory_of)));
   613 
   614 fun shell_command thyname cmd = Toplevel.program (fn _ =>
   615   (use_thy thyname; case Scan.read Token.stopper (Parse.!!! code_exprP)
   616     ((filter Token.is_proper o Outer_Syntax.scan Position.none) cmd)
   617    of SOME f => (writeln "Now generating code..."; f (Thy_Info.get_theory thyname))
   618     | NONE => error ("Bad directive " ^ quote cmd)))
   619   handle Runtime.TOPLEVEL_ERROR => OS.Process.exit OS.Process.failure;
   620 
   621 end; (*local*)
   622 
   623 end; (*struct*)