Project

General

Profile

Download (15.2 KB) Statistics
| Branch: | Tag: | Revision:
1
let base_types = ["integer"; "character"; "bit"; "real"; "natural"; "positive"; "std_logic"; "std_logic_vector" ]
2
 
3
(************************************************************************************)		   
4
(*                     Constants                                                    *)
5
(************************************************************************************)		   
6

    
7
(* Std_logic values :
8
    'U': uninitialized. This signal hasn't been set yet.
9
    'X': unknown. Impossible to determine this value/result.
10
    '0': logic 0
11
    '1': logic 1
12
    'Z': High Impedance
13
    'W': Weak signal, can't tell if it should be 0 or 1.
14
    'L': Weak signal that should probably go to 0
15
    'H': Weak signal that should probably go to 1
16
    '-': Don't care. *)			       
17
let std_logic_cst = ["U"; "X"; "0"; "1"; "Z"; "W"; "L"; "H"; "-" ]
18
let literal_base = ["B"; "O"; "X"; "UB"; "UO"; "UX"; "SB"; "SO"; "SX"; "D"] (* Prefix of CstLiteral *)
19

    
20
(* TODO: do we need more constructors ? *)
21
type vhdl_cst_val_t = 
22
    CstInt of int 
23
  | CstStdLogic of string
24
  | CstLiteral of string [@name "CST_LITERAL"]
25
[@@deriving show { with_path = false }, yojson {strict = false}];;
26

    
27
(*
28
let pp_cst_val fmt c =
29
  match c with
30
  | CstInt i -> Format.fprintf fmt "%i" i
31
  | CstStdLogic s -> if List.mem s std_logic_cst then Format.fprintf fmt "%s" s else assert false
32
  | CstLiteral s -> Format.fprintf fmt "%s" s
33
*)
34

    
35
type vhdl_type_t =
36
  | Base of string
37
  | Range of string option * int * int
38
  | Bit_vector of int * int
39
  | Array of int * int * vhdl_type_t
40
  | Enumerated of string list
41
  | Void
42
and vhdl_subtype_indication_t =
43
  {
44
    name : vhdl_name_t [@default NoName];
45
    functionName : vhdl_name_t [@default NoName];
46
    const: vhdl_constraint_t [@default NoConstraint];
47
  }
48
and vhdl_discrete_range_t =
49
  | SubDiscreteRange of vhdl_subtype_indication_t [@name "SUB_DISCRETE_RANGE"]
50
  | NamedRange of vhdl_name_t [@name "NAMED_RANGE"]
51
  | DirectedRange of { direction: string; from: vhdl_expr_t; _to: vhdl_expr_t } [@name "RANGE_WITH_DIRECTION"]
52
and vhdl_constraint_t =
53
  | RefConstraint of { ref_name: vhdl_name_t; }
54
  | RangeConstraint of { range: vhdl_discrete_range_t } [@name "RANGE_CONSTRAINT"]
55
  | IndexConstraint of { ranges: vhdl_discrete_range_t list; } [@name "INDEX_CONSTRAINT"]
56
  | ArrayConstraint of { ranges: vhdl_discrete_range_t list; sub: vhdl_constraint_t } [@name "ARRAY_CONSTRAINT"]
57
  | RecordConstraint
58
  | NoConstraint
59
and vhdl_definition_t =
60
  | Type of {name : vhdl_name_t ; definition: vhdl_type_t} [@name "TYPE_DECLARATION"]
61
  | Subtype of {name : vhdl_name_t ; typ : vhdl_subtype_indication_t} [@name "SUBTYPE_DECLARATION"]
62
and vhdl_expr_t =
63
  | Call of vhdl_name_t [@name "CALL"]
64
  | Cst of vhdl_cst_val_t [@name "CONSTANT_VALUE"]
65
  | Op of { id: string [@default ""]; args: vhdl_expr_t list [@default []]} [@name "EXPRESSION"]
66
  | IsNull [@name "IsNull"]
67
  | Time of { value: int; phy_unit: string [@default ""]}
68
  | Sig of { name: vhdl_name_t; att: vhdl_signal_attributes_t option }
69
  | SuffixMod of { expr : vhdl_expr_t; selection : vhdl_suffix_selection_t }
70
  | Aggregate of { elems : vhdl_element_assoc_t list } [@name "AGGREGATE"]
71
  | Others [@name "OTHERS"]
72
and vhdl_name_t =
73
  | Simple of string [@name "SIMPLE_NAME"]
74
  | Identifier of string [@name "IDENTIFIER"]
75
  | Selected of vhdl_name_t list [@name "SELECTED_NAME"]
76
  | Index of { id: vhdl_name_t; exprs: vhdl_expr_t list } [@name "INDEXED_NAME"]
77
  | Slice of { id: vhdl_name_t; range: vhdl_discrete_range_t } [@name "SLICE_NAME"]
78
  | Attribute of { id: vhdl_name_t; designator: vhdl_name_t; expr: vhdl_expr_t [@default IsNull]} [@name "ATTRIBUTE_NAME"]
79
  | Function of { id: vhdl_name_t; assoc_list: vhdl_assoc_element_t list } [@name "FUNCTION_CALL"]
80
  | NoName
81
and vhdl_assoc_element_t =
82
  {
83
    formal_name: vhdl_name_t option [@default None];
84
    formal_arg: vhdl_name_t option [@default None];
85
    actual_name: vhdl_name_t option [@default None];
86
    actual_designator: vhdl_name_t option [@default None];
87
    actual_expr: vhdl_expr_t option [@default None];
88
  }
89
and vhdl_element_assoc_t =
90
  {
91
    choices: vhdl_expr_t list;
92
    expr: vhdl_expr_t;
93
  }
94
and vhdl_array_attributes_t = 
95
  | AAttInt of { id: string; arg: int; } 
96
  | AAttAscending
97
and vhdl_signal_attributes_t = SigAtt of string
98
and vhdl_string_attributes_t = StringAtt of string
99
and vhdl_suffix_selection_t = Idx of int | SuffixRange of int * int
100
[@@deriving show { with_path = false }, yojson {strict = false}];;
101

    
102
(*
103
let rec pp_vhdl_type fmt t =
104
  match t with
105
  | Base s -> Format.fprintf fmt "%s" s 
106
  | Range(base, n, m) -> Format.fprintf fmt "%trange %i to %i" (fun fmt -> match base with Some s -> Format.fprintf fmt "%s " s | None -> ()) n m
107
  | Bit_vector (n,m) -> Format.fprintf fmt "bit_vector(%i downto %i)" n m
108
  | Array (n, m, base) -> Format.fprintf fmt "array (%i to %i) of %a" n m pp_vhdl_type base
109
  | Enumerated sl -> Format.fprintf fmt "(%a)" (Utils.fprintf_list ~sep:", " Format.pp_print_string) sl
110
  | Void -> Format.fprintf fmt ""
111
*)
112

    
113
(************************************************************************************)		   
114
(*            Attributes for types, arrays, signals and strings                     *)
115
(************************************************************************************)		   
116

    
117
type 'basetype vhdl_type_attributes_t =
118
  | TAttNoArg of { id: string }
119
  | TAttIntArg of { id: string; arg: int }
120
  | TAttValArg of { id: string; arg: 'basetype }
121
  | TAttStringArg of { id: string; arg: string }
122
[@@deriving show { with_path = false }, yojson {strict = false}];;
123

    
124
let typ_att_noarg = ["base"; "left"; "right"; "high"; "low"]
125
let typ_att_intarg = ["pos"; "val"; "succ"; "pred"; "leftof"; "rightof"]
126
let typ_att_valarg = ["image"]
127
let typ_att_stringarg = ["value"]
128
  
129
let array_att_intarg = ["left"; "right"; "high"; "low"; "range"; "reverse_range"; "length"]  
130

    
131
type vhdl_parameter_t =
132
  {
133
    names: vhdl_name_t list;
134
    mode: string list [@default []];
135
    typ: vhdl_subtype_indication_t;
136
    init_val: vhdl_cst_val_t option [@default None];
137
  }
138
[@@deriving show { with_path = false }, yojson {strict = false}];;
139

    
140
type vhdl_subprogram_spec_t =
141
  {
142
    name: string [@default ""];
143
    typeMark: vhdl_name_t [@default NoName];
144
    parameters: vhdl_parameter_t list;
145
    isPure: bool [@default false];
146
  }
147
[@@deriving show { with_path = false }, yojson {strict = false}];;
148

    
149
(************************************************************************************)		   
150
(*                        Expressions  / Statements                                 *)
151
(************************************************************************************)		   
152

    
153
let arith_funs = ["+";"-";"*";"/";"mod"; "rem";"abs";"**";"&"]
154
let bool_funs  = ["and"; "or"; "nand"; "nor"; "xor"; "not"]
155
let rel_funs   = ["<";">";"<=";">=";"/=";"=";"?=";"?/=";"?<";"?<=";"?>";"?>=";"??"]
156
let shift_funs = ["sll";"srl";"sla";"sra";"rol";"ror"]
157

    
158
type vhdl_sequential_stmt_t = 
159
  | VarAssign of { label: vhdl_name_t [@default NoName]; lhs: vhdl_name_t; rhs: vhdl_expr_t } [@name "VARIABLE_ASSIGNMENT_STATEMENT"]
160
  | SigSeqAssign of { label: vhdl_name_t [@default NoName]; lhs: vhdl_name_t; rhs: vhdl_expr_t list} [@name "SIGNAL_ASSIGNMENT_STATEMENT"]
161
  | If of { label: vhdl_name_t [@default NoName]; if_cases: vhdl_if_case_t list;
162
    default: vhdl_sequential_stmt_t list [@default []]; } [@name "IF_STATEMENT"]
163
  | Case of { label: vhdl_name_t [@default NoName]; guard: vhdl_expr_t; branches: vhdl_case_item_t list } [@name "CASE_STATEMENT_TREE"]
164
  | Exit of { label: vhdl_name_t [@default NoName]; loop_label: string option [@default Some ""]; condition: vhdl_expr_t option [@default Some IsNull]} [@name "EXIT_STATEMENT"]
165
  | Assert of { label: vhdl_name_t [@default NoName]; cond: vhdl_expr_t; report: vhdl_expr_t [@default IsNull]; severity: vhdl_expr_t [@default IsNull]} [@name "ASSERTION_STATEMENT"]
166
  | ProcedureCall of { label: vhdl_name_t [@default NoName]; name: vhdl_name_t; assocs: vhdl_assoc_element_t list } [@name "PROCEDURE_CALL_STATEMENT"]
167
  | Wait [@name "WAIT_STATEMENT"]
168
  | Null of { label: vhdl_name_t [@default NoName]} [@name "NULL_STATEMENT"]
169
  | Return of { label: vhdl_name_t [@default NoName]} [@name "RETURN_STATEMENT"]
170
and vhdl_if_case_t = 
171
  {
172
    if_cond: vhdl_expr_t;
173
    if_block: vhdl_sequential_stmt_t list;
174
  }
175
and vhdl_case_item_t = 
176
  {
177
    when_cond: vhdl_expr_t list;
178
    when_stmt: vhdl_sequential_stmt_t list;
179
  }
180
[@@deriving show { with_path = false }, yojson {strict = false}];;
181

    
182
type vhdl_declaration_t =
183
  | VarDecl of {
184
      names : vhdl_name_t list; 
185
      typ : vhdl_subtype_indication_t; 
186
      init_val : vhdl_expr_t [@default IsNull] 
187
    } [@name "VARIABLE_DECLARATION"]
188
  | CstDecl of { 
189
      names : vhdl_name_t list; 
190
      typ : vhdl_subtype_indication_t; 
191
      init_val : vhdl_expr_t
192
    } [@name "CONSTANT_DECLARATION"]
193
  | SigDecl of { 
194
      names : vhdl_name_t list; 
195
      typ : vhdl_subtype_indication_t; 
196
      init_val : vhdl_expr_t [@default IsNull]
197
    } [@name "SIGNAL_DECLARATION"]
198
  | Subprogram of {
199
      name: vhdl_name_t [@default NoName]; 
200
      kind: string [@default ""]; 
201
      spec: vhdl_subprogram_spec_t [@default {name="";typeMark=NoName;parameters=[];isPure=false}]; 
202
      decl_part: vhdl_declaration_t list [@default []]; 
203
      stmts: vhdl_sequential_stmt_t list [@default []]
204
    } [@name "SUBPROGRAM_BODY"]
205
[@@deriving show { with_path = false }, yojson {strict = false}];;
206

    
207
type vhdl_signal_condition_t =
208
  {                            
209
    expr: vhdl_expr_t list;              (* when expression *)
210
    cond: vhdl_expr_t [@default IsNull];  (* optional else case expression. 
211
                                             If None, could be a latch  *)
212
  }
213
[@@deriving show { with_path = false }, yojson {strict = false}];;
214

    
215
type vhdl_signal_selection_t =
216
  {
217
    expr : vhdl_expr_t;
218
    when_sel: vhdl_expr_t list [@default []];
219
  }
220
[@@deriving show { with_path = false }, yojson {strict = false}];;
221

    
222
type vhdl_conditional_signal_t =
223
  {
224
    postponed: bool [@default false];
225
    label: vhdl_name_t [@default NoName];
226
    lhs: vhdl_name_t;        (* assigned signal = target*)
227
    rhs: vhdl_signal_condition_t list;                   (* expression *)
228
    cond: vhdl_expr_t [@default IsNull];
229
    delay: vhdl_expr_t [@default IsNull];
230
  }
231
[@@deriving show { with_path = false }, yojson {strict = false}];;
232

    
233
type vhdl_process_t =
234
  { 
235
    id: vhdl_name_t [@default NoName];
236
    declarations: vhdl_declaration_t list option [@key "PROCESS_DECLARATIVE_PART"] [@default Some []];
237
    active_sigs: vhdl_name_t list [@default []];
238
    body: vhdl_sequential_stmt_t list [@key "PROCESS_STATEMENT_PART"] [@default []]
239
  }
240
[@@deriving show { with_path = false }, yojson {strict = false}];;
241

    
242
type vhdl_selected_signal_t = 
243
  { 
244
    postponed: bool [@default false];
245
    label: vhdl_name_t [@default NoName];
246
    lhs: vhdl_name_t;      (* assigned signal = target *)
247
    sel: vhdl_expr_t;  
248
    branches: vhdl_signal_selection_t list [@default []];
249
    delay: vhdl_expr_t option;
250
  }
251
[@@deriving show { with_path = false }, yojson {strict = false}];;
252

    
253
type vhdl_component_instantiation_t =
254
  {
255
    name: vhdl_name_t;
256
    inst_unit: vhdl_name_t;
257
    archi_name: vhdl_name_t option [@default None];
258
    generic_map: vhdl_assoc_element_t option [@default None];
259
    port_map: vhdl_assoc_element_t option [@default None];
260
  }
261
[@@deriving show { with_path = false }, yojson {strict = false}];;
262

    
263
type vhdl_concurrent_stmt_t =
264
  | SigAssign of vhdl_conditional_signal_t [@name "CONDITIONAL_SIGNAL_ASSIGNMENT"]
265
  | Process of vhdl_process_t [@name "PROCESS_STATEMENT"]
266
  | SelectedSig of vhdl_selected_signal_t [@name "SELECTED_SIGNAL_ASSIGNMENT"]
267
  | ComponentInst of vhdl_component_instantiation_t [@name "COMPONENT_INSTANTIATION_STATEMENT"]
268
[@@deriving show { with_path = false }, yojson {strict = false}];;
269
  (*
270
type vhdl_statement_t =
271
  
272
  (* | DeclarationStmt of declaration_stmt_t *)
273
  | ConcurrentStmt of vhdl_concurrent_stmt_t
274
  | SequentialStmt of vhdl_sequential_stmt_t
275
   *)
276
		     
277
(************************************************************************************)		   
278
(*                     Entities                                                     *)
279
(************************************************************************************)		   
280
			     
281
type vhdl_port_mode_t = 
282
    InPort     [@name "in"]
283
  | OutPort    [@name "out"]
284
  | InoutPort  [@name "inout"]
285
  | BufferPort [@name "buffer"]
286
[@@deriving show { with_path = false }, yojson];;
287
	     
288
type vhdl_port_t =
289
  {
290
    names: vhdl_name_t list [@default []];
291
    mode: vhdl_port_mode_t [@default InPort];
292
    typ: vhdl_subtype_indication_t;
293
    expr: vhdl_expr_t [@default IsNull];
294
  }
295
[@@deriving show { with_path = false }, yojson {strict = false}];;
296

    
297
type vhdl_entity_t =
298
  {
299
    name: vhdl_name_t [@default NoName];
300
    generics: vhdl_port_t list [@default []];
301
    ports: vhdl_port_t list [@default []];
302
    declaration: vhdl_declaration_t list [@key "ENTITY_DECLARATIVE_PART"] [@default []];
303
    stmts: vhdl_concurrent_stmt_t list [@key "ENTITY_STATEMENT_PART"] [@default []]; 
304
  }
305
[@@deriving show { with_path = false }, yojson {strict = false}];;
306

    
307
(************************************************************************************)		   
308
(*                    Packages / Library loading                                    *)
309
(************************************************************************************)		   
310
				
311
(* Optional. Describes shared definitions *)
312
type vhdl_package_t =
313
  {
314
    name: vhdl_name_t [@default NoName];
315
    shared_defs: vhdl_definition_t list [@default []];
316
  }
317
[@@deriving show { with_path = false }, yojson {strict = false}];;
318

    
319
type vhdl_load_t = 
320
    Library of vhdl_name_t list [@name "LIBRARY_CLAUSE"] [@default []]
321
  | Use of vhdl_name_t list [@name "USE_CLAUSE"] [@default []]
322
[@@deriving show { with_path = false }, yojson];;
323

    
324
(************************************************************************************)		   
325
(*                        Architecture / VHDL Design                                *)
326
(************************************************************************************)		   
327
				       
328
type vhdl_architecture_t =
329
  {
330
    name: vhdl_name_t [@default NoName];
331
    entity: vhdl_name_t [@default NoName];
332
    declarations: vhdl_declaration_t list [@key "ARCHITECTURE_DECLARATIVE_PART"] [@default []];
333
    body: vhdl_concurrent_stmt_t list [@key "ARCHITECTURE_STATEMENT_PART"] [@default []]; 
334
  }
335
[@@deriving show { with_path = false }, yojson {strict = false}];;
336
    
337
(* TODO. Configuration is optional *)
338
type vhdl_configuration_t = unit
339
[@@deriving show { with_path = false }, yojson {strict = false}];;
340

    
341
type vhdl_library_unit_t = (* TODO: PACKAGE_BODY *)
342
    Package of vhdl_package_t [@name "PACKAGE_DECLARATION"]
343
  | Entities of vhdl_entity_t [@name "ENTITY_DECLARATION"]
344
  | Architecture of vhdl_architecture_t [@name "ARCHITECTURE_BODY"]
345
  | Configuration of vhdl_configuration_t [@name "CONFIGURATION_DECLARATION"]
346
[@@deriving show { with_path = false }, yojson {strict = false}];;
347

    
348
type vhdl_design_unit_t =
349
  {
350
    contexts: vhdl_load_t list [@default []];
351
    library: vhdl_library_unit_t;
352
  }
353
[@@deriving show { with_path = false }, yojson {strict = false}];;
354

    
355
type vhdl_design_file_t =
356
  {
357
    design_units: vhdl_design_unit_t list [@default []];
358
  }
359
[@@deriving show { with_path = false }, yojson {strict = false}];;
360

    
361
type vhdl_file_t = 
362
  {
363
    design_file: vhdl_design_file_t [@default {design_units=[]}] [@key "DESIGN_FILE"];
364
  }
365
[@@deriving show { with_path = false }, yojson];;
(1-1/6)