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