@@ -22,12 +22,15 @@ open Ast
2222
2323type mode = Big_endian | Little_endian | Host_endian
2424
25+ type prim =
26+ | UInt8
27+ | UInt16
28+ | UInt32
29+ | UInt64
30+
2531type ty =
26- |UInt8
27- |UInt16
28- |UInt32
29- |UInt64
30- |Buffer of int
32+ | Prim of prim
33+ | Buffer of prim * int
3134
3235type field = {
3336 field : string ;
@@ -51,22 +54,24 @@ let ty_of_string =
5154 | _ -> None
5255
5356let width_of_field f =
54- match f.ty with
55- | UInt8 -> 1
56- | UInt16 -> 2
57- | UInt32 -> 4
58- | UInt64 -> 8
59- | Buffer len -> len
57+ let rec width = function
58+ | Prim UInt8 -> 1
59+ | Prim UInt16 -> 2
60+ | Prim UInt32 -> 4
61+ | Prim UInt64 -> 8
62+ | Buffer (prim , len ) -> (width (Prim prim)) * len
63+ in
64+ width f.ty
6065
6166let field_to_string f =
62- sprintf " %s %s "
63- ( match f.ty with
64- | UInt8 -> " uint8_t "
65- | UInt16 -> " uint16_t "
66- | UInt32 -> " uint32_t "
67- | UInt64 -> " uint64_t "
68- | Buffer len -> sprintf " uint8_t[%d] " len
69- ) f.field
67+ let rec string = function
68+ | Prim UInt8 -> " uint8_t "
69+ | Prim UInt16 -> " uint16_t "
70+ | Prim UInt32 -> " uint32_t "
71+ | Prim UInt64 -> " uint64_t "
72+ | Buffer ( prim , len ) -> sprintf " %s[%d] " ( string ( Prim prim)) len
73+ in
74+ sprintf " %s %s " ( string f.ty ) f.field
7075
7176let to_string t =
7277 sprintf " cstruct[%d] %s { %s }" t.len t.name
@@ -79,9 +84,8 @@ let parse_field _loc field field_type sz =
7984 | None -> loc_err _loc (sprintf " Unknown type %s" field_type)
8085 | Some ty -> begin
8186 let ty = match ty,sz with
82- | _ ,None -> ty
83- | UInt8 ,Some sz -> Buffer (int_of_string sz)
84- | _ ,Some sz -> loc_err _loc " only uint8_t buffers supported"
87+ | _ ,None -> Prim ty
88+ | prim ,Some sz -> Buffer (prim, int_of_string sz)
8589 in
8690 let off = - 1 in
8791 { field; ty; off }
@@ -118,69 +122,67 @@ let output_get _loc s f =
118122 let m = mode_mod _loc s.endian in
119123 let num x = < :expr< $ int :string_of_int x$ >> in
120124 match f.ty with
121- | Buffer len ->
125+ | Buffer (_ , _ ) ->
126+ let len = width_of_field f in
122127 < :str_item<
123128 value $ lid:op_name " get" s f$ src = Cstruct. sub src $ num f.off$ $ num len$ ;
124129 value $ lid:op_name " copy" s f$ src = Cstruct. copy src $ num f.off$ $ num len$
125130 >>
126- | ty ->
131+ | Prim prim ->
127132 < :str_item<
128133 value $ lid:getter_name s f$ v =
129- $ match f.ty with
134+ $ match prim with
130135 | UInt8 -> < :expr< Cstruct. get_uint8 v $ num f.off$ >>
131136 | UInt16 -> < :expr< $ m$. get_uint16 v $ num f.off$ >>
132137 | UInt32 -> < :expr< $ m$. get_uint32 v $ num f.off$ >>
133138 | UInt64 -> < :expr< $ m$. get_uint64 v $ num f.off$ >>
134- | Buffer len -> assert false
135139 $
136140 >>
137141
138- let type_of_int_field _loc f =
139- match f.ty with
142+ let type_of_int_field _loc = function
140143 | UInt8 -> < :ctyp< Cstruct. uint8>>
141144 | UInt16 -> < :ctyp< Cstruct. uint16>>
142145 | UInt32 -> < :ctyp< Cstruct. uint32>>
143146 | UInt64 -> < :ctyp< Cstruct. uint64>>
144- | Buffer _ -> assert false
145147
146148let output_get_sig _loc s f =
147149 match f.ty with
148- | Buffer len ->
150+ | Buffer ( _ , _ ) ->
149151 < :sig_item<
150152 value $ lid:op_name " get" s f$ : Cstruct. t -> Cstruct. t ;
151153 value $ lid:op_name " copy" s f$ : Cstruct. t -> string >>
152- | ty ->
153- let retf = type_of_int_field _loc f in
154+ | Prim prim ->
155+ let retf = type_of_int_field _loc prim in
154156 < :sig_item< value $ lid:getter_name s f$ : Cstruct. t -> $ retf$ ; >>
155157
156158let output_set _loc s f =
157159 let m = mode_mod _loc s.endian in
158160 let num x = < :expr< $ int :string_of_int x$ >> in
159161 match f.ty with
160- | Buffer len ->
162+ | Buffer (_ ,_ ) ->
163+ let len = width_of_field f in
161164 < :str_item<
162165 value $ lid:setter_name s f$ src srcoff dst = Cstruct. blit_from_string src srcoff dst $ num f.off$ $ num len$ ;
163166 value $ lid:op_name " blit" s f$ src srcoff dst = Cstruct. blit src srcoff dst $ num f.off$ $ num len$
164167 >>
165- | ty ->
168+ | Prim prim ->
166169 < :str_item<
167- value $ lid:setter_name s f$ v x = $ match f.ty with
170+ value $ lid:setter_name s f$ v x = $ match prim with
168171 | UInt8 -> < :expr< Cstruct. set_uint8 v $ num f.off$ x >>
169172 | UInt16 -> < :expr< $ m$. set_uint16 v $ num f.off$ x >>
170173 | UInt32 -> < :expr< $ m$. set_uint32 v $ num f.off$ x >>
171174 | UInt64 -> < :expr< $ m$. set_uint64 v $ num f.off$ x >>
172- | Buffer len -> assert false
173175 $
174176 >>
175177
176178let output_set_sig _loc s f =
177179 match f.ty with
178- | Buffer len ->
180+ | Buffer ( _ , _ ) ->
179181 < :sig_item<
180182 value $ lid:setter_name s f$ : string -> int -> Cstruct. t -> unit ;
181183 value $ lid:op_name " blit" s f$ : Cstruct. t -> int -> Cstruct. t -> unit >>
182- | ty ->
183- let retf = type_of_int_field _loc f in
184+ | Prim prim ->
185+ let retf = type_of_int_field _loc prim in
184186 < :sig_item< value $ lid:setter_name s f$ : Cstruct. t -> $ retf$ -> unit >>
185187
186188let output_sizeof _loc s =
@@ -199,10 +201,16 @@ let output_hexdump _loc s =
199201 < :expr<
200202 $ a$ ; Buffer. add_string _buf $ str:" " ^ f.field^ " = " $ ;
201203 $ match f.ty with
202- | UInt8 | UInt16 -> < :expr< Printf. bprintf _buf " 0x%x\n " ($ lid:getter_name s f$ v ) >>
203- | UInt32 -> < :expr< Printf. bprintf _buf " 0x%lx\n " ($ lid:getter_name s f$ v ) >>
204- | UInt64 -> < :expr< Printf. bprintf _buf " 0x%Lx\n " ($ lid:getter_name s f$ v ) >>
205- | Buffer len -> < :expr< Printf. bprintf _buf " <buffer length %d>" $ int :string_of_int len$ ; Cstruct. hexdump_to_buffer _buf ($ lid:getter_name s f$ v ) >>
204+ | Prim (UInt8 |UInt16 ) ->
205+ < :expr< Printf. bprintf _buf " 0x%x\n " ($ lid:getter_name s f$ v ) >>
206+ | Prim UInt32 ->
207+ < :expr< Printf. bprintf _buf " 0x%lx\n " ($ lid:getter_name s f$ v ) >>
208+ | Prim UInt64 ->
209+ < :expr< Printf. bprintf _buf " 0x%Lx\n " ($ lid:getter_name s f$ v ) >>
210+ | Buffer (_ ,_ ) ->
211+ < :expr< Printf. bprintf _buf " <buffer %s>"
212+ $ str: field_to_string f$ ;
213+ Cstruct. hexdump_to_buffer _buf ($ lid:getter_name s f$ v ) >>
206214 $ >>
207215 ) < :expr< >> s.fields
208216 in
@@ -248,7 +256,7 @@ let output_struct_sig _loc s =
248256let output_enum _loc name fields width =
249257 let intfn,pattfn = match ty_of_string width with
250258 | None -> loc_err _loc (" enum: unknown width specifier " ^ width)
251- | Some UInt8 | Some UInt16 ->
259+ | Some ( UInt8 | UInt16 ) ->
252260 (fun i -> < :expr< $ int :Int64. to_string i$ >> ),
253261 (fun i -> < :patt< $ int :Int64. to_string i$ >> )
254262 | Some UInt32 ->
@@ -257,7 +265,6 @@ let output_enum _loc name fields width =
257265 | Some UInt64 ->
258266 (fun i -> < :expr< $ int64 :Printf. sprintf " 0x%Lx" i$ >> ),
259267 (fun i -> < :patt< $ int64 :Printf. sprintf " 0x%Lx" i$ >> )
260- | Some (Buffer _ ) -> loc_err _loc " enum: array types not allowed"
261268 in
262269 let decls = tyOr_of_list (List. map (fun (f ,_ ) ->
263270 < :ctyp< $ uid:f$ >> ) fields) in
@@ -286,10 +293,9 @@ let output_enum _loc name fields width =
286293let output_enum_sig _loc name fields width =
287294 let oty = match ty_of_string width with
288295 | None -> loc_err _loc (" enum: unknown width specifier " ^ width)
289- | Some UInt8 |Some UInt16 -> < :ctyp< int >>
296+ | Some ( UInt8 |UInt16 ) -> < :ctyp< int >>
290297 | Some UInt32 -> < :ctyp< int32 >>
291298 | Some UInt64 -> < :ctyp< int64 >>
292- | Some (Buffer _ ) -> loc_err _loc " enum: array types not allowed"
293299 in
294300 let decls = tyOr_of_list (List. map (fun (f ,_ ) ->
295301 < :ctyp< $ uid:f$ >> ) fields) in
@@ -316,10 +322,14 @@ EXTEND Gram
316322 ]
317323 ];
318324
325+ constr_field_decl: [
326+ [ field = constr_field -> [field]
327+ | field = constr_field ; ";" ; rest = constr_field_decl -> field::rest
328+ | field = constr_field ; ";" -> [field] ]
329+ ];
330+
319331 constr_fields: [
320- [ " {" ; fields = LIST0 constr_field SEP " ;" ; " }" ->
321- fields
322- ]
332+ [ " {" ; fields = constr_field_decl; " }" -> fields ]
323333 ];
324334
325335 constr_enum: [
@@ -330,12 +340,22 @@ EXTEND Gram
330340 | f = UIDENT ; "=" ; i = INT -> (f, Some (Int64. of_string i)) ]
331341 ];
332342
343+ constr_enum_decl: [
344+ [ enum = constr_enum -> [enum]
345+ | enum = constr_enum ; ";" ; rest = constr_enum_decl -> enum::rest
346+ | enum = constr_enum ; ";" -> [enum] ]
347+ ];
348+
349+ constr_enums: [
350+ [ " {" ; enums = constr_enum_decl; " }" -> enums ]
351+ ];
352+
333353 sig_item: [
334354 [ " cstruct" ; name = LIDENT ; fields = constr_fields;
335355 " as" ; endian = LIDENT ->
336356 output_struct_sig _loc (create_struct _loc endian name fields)
337357 ] |
338- [ " cenum" ; name = LIDENT ; " { " ; fields = LIST0 [ constr_enum ] SEP " ; " ; " } " ;
358+ [ " cenum" ; name = LIDENT ; fields = constr_enums ;
339359 " as" ; width = LIDENT ->
340360 let n = ref Int64. minus_one in
341361 let incr_n () = n := Int64. succ ! n in
@@ -353,7 +373,7 @@ EXTEND Gram
353373 " as" ; endian = LIDENT ->
354374 output_struct _loc (create_struct _loc endian name fields)
355375 ] |
356- [ " cenum" ; name = LIDENT ; " { " ; fields = LIST0 [ constr_enum ] SEP " ; " ; " } " ;
376+ [ " cenum" ; name = LIDENT ; fields = constr_enums ;
357377 " as" ; width = LIDENT ->
358378 let n = ref Int64. minus_one in
359379 let incr_n () = n := Int64. succ ! n in
0 commit comments