Revision 40364f53
Added by Arnaud Dieumegard about 5 years ago
src/backends/VHDL/vhdl_ast.ml | ||
---|---|---|
1 |
(* source: Synario VHDL Reference Manual - March 1997 *) |
|
2 |
|
|
3 |
(************************************************************************************) |
|
4 |
(* Types *) |
|
5 |
(************************************************************************************) |
|
6 | 1 |
let base_types = ["integer"; "character"; "bit"; "real"; "natural"; "positive"; "std_logic"; "std_logic_vector" ] |
7 |
|
|
8 |
type vhdl_type_t = |
|
9 |
| Base of string |
|
10 |
| Range of string option * int * int |
|
11 |
| Bit_vector of int * int |
|
12 |
| Array of int * int * vhdl_type_t |
|
13 |
| Enumerated of string list |
|
14 |
|
|
15 |
let rec pp_vhdl_type fmt t = |
|
16 |
match t with |
|
17 |
| Base s -> Format.fprintf fmt "%s" s |
|
18 |
| Bit_vector (n,m) -> Format.fprintf fmt "bit_vector(%i downto %i)" n m |
|
19 |
| 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 |
|
20 |
| Array (n, m, base) -> Format.fprintf fmt "array (%i to %i) of %a" n m pp_vhdl_type base |
|
21 |
| Enumerated sl -> Format.fprintf fmt "(%a)" (Utils.fprintf_list ~sep:", " Format.pp_print_string) sl |
|
22 |
|
|
23 |
|
|
24 |
|
|
2 |
|
|
25 | 3 |
(************************************************************************************) |
26 | 4 |
(* Constants *) |
27 | 5 |
(************************************************************************************) |
... | ... | |
37 | 15 |
'H': Weak signal that should probably go to 1 |
38 | 16 |
'-': Don't care. *) |
39 | 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 *) |
|
40 | 19 |
|
41 | 20 |
(* TODO: do we need more constructors ? *) |
42 |
type cst_val_t = CstInt of int | CstStdLogic of string | CstBV of string * string |
|
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}];; |
|
43 | 26 |
|
27 |
(* |
|
44 | 28 |
let pp_cst_val fmt c = |
45 | 29 |
match c with |
46 | 30 |
| CstInt i -> Format.fprintf fmt "%i" i |
47 | 31 |
| CstStdLogic s -> if List.mem s std_logic_cst then Format.fprintf fmt "%s" s else assert false |
48 |
| CstBV (pref,suff) -> Format.fprintf fmt "%s\"%s\"" pref suff |
|
49 |
|
|
50 |
(************************************************************************************) |
|
51 |
(* Declarations *) |
|
52 |
(************************************************************************************) |
|
53 |
|
|
54 |
|
|
55 |
(* TODO ? Shall we merge definition / declaration ? Do they appear at the same |
|
56 |
place or at different ones ? *) |
|
57 |
type vhdl_definition_t = |
|
58 |
| Type of {name : string ; definition: vhdl_type_t} |
|
59 |
| Subtype of {name : string ; definition: vhdl_type_t} |
|
60 |
|
|
61 |
let pp_vhdl_definition fmt def = |
|
62 |
match def with |
|
63 |
| Type s -> Format.fprintf fmt "type %s is %a;" s.name pp_vhdl_type s.definition |
|
64 |
| Subtype s -> Format.fprintf fmt "subtype %s is %a;" s.name pp_vhdl_type s.definition |
|
65 |
|
|
66 |
type vhdl_declaration_t = |
|
67 |
| VarDecl of { name : string; typ : vhdl_type_t; init_val : cst_val_t option } |
|
68 |
| CstDecl of { name : string; typ : vhdl_type_t; init_val : cst_val_t } |
|
69 |
| SigDecl of { name : string; typ : vhdl_type_t; init_val : cst_val_t option } |
|
70 |
|
|
71 |
let pp_vhdl_declaration fmt decl = |
|
72 |
match decl with |
|
73 |
| VarDecl v -> Format.fprintf |
|
74 |
fmt |
|
75 |
"variable %s : %a%t;" |
|
76 |
v.name |
|
77 |
pp_vhdl_type v.typ |
|
78 |
(fun fmt -> match v.init_val with Some initv -> Format.fprintf fmt " := %a" pp_cst_val initv | _ -> ()) |
|
79 |
| CstDecl v -> Format.fprintf |
|
80 |
fmt |
|
81 |
"constant %s : %a := %a;" |
|
82 |
v.name |
|
83 |
pp_vhdl_type v.typ |
|
84 |
pp_cst_val v.init_val |
|
85 |
| SigDecl v -> Format.fprintf |
|
86 |
fmt |
|
87 |
"signal %s : %a%t;" |
|
88 |
v.name |
|
89 |
pp_vhdl_type v.typ |
|
90 |
(fun fmt -> match v.init_val with Some initv -> Format.fprintf fmt " := %a" pp_cst_val initv | _ -> ()) |
|
32 |
| CstLiteral s -> Format.fprintf fmt "%s" s |
|
33 |
*) |
|
91 | 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 Some NoName]; |
|
84 |
formal_arg: vhdl_name_t option [@default Some NoName]; |
|
85 |
actual_name: vhdl_name_t option [@default Some NoName]; |
|
86 |
actual_designator: vhdl_name_t option [@default Some NoName]; |
|
87 |
actual_expr: vhdl_expr_t option [@default Some IsNull]; |
|
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 |
*) |
|
92 | 112 |
|
93 | 113 |
(************************************************************************************) |
94 | 114 |
(* Attributes for types, arrays, signals and strings *) |
... | ... | |
99 | 119 |
| TAttIntArg of { id: string; arg: int } |
100 | 120 |
| TAttValArg of { id: string; arg: 'basetype } |
101 | 121 |
| TAttStringArg of { id: string; arg: string } |
122 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
102 | 123 |
|
103 | 124 |
let typ_att_noarg = ["base"; "left"; "right"; "high"; "low"] |
104 | 125 |
let typ_att_intarg = ["pos"; "val"; "succ"; "pred"; "leftof"; "rightof"] |
105 | 126 |
let typ_att_valarg = ["image"] |
106 | 127 |
let typ_att_stringarg = ["value"] |
107 | 128 |
|
108 |
let pp_type_attribute pp_val fmt tatt = |
|
109 |
match tatt with |
|
110 |
| TAttNoArg a -> Format.fprintf fmt "'%s" a.id |
|
111 |
| TAttIntArg a -> Format.fprintf fmt "'%s(%i)" a.id a.arg |
|
112 |
| TAttValArg a -> Format.fprintf fmt "'%s(%a)" a.id pp_val a.arg |
|
113 |
| TAttStringArg a -> Format.fprintf fmt "'%s(%s)" a.id a.arg |
|
114 |
|
|
115 |
type vhdl_array_attributes_t = AAttInt of { id: string; arg: int; } | AAttAscending |
|
116 |
let pp_array_attribute fmt aatt = |
|
117 |
match aatt with |
|
118 |
| AAttInt a -> Format.fprintf fmt "'%s(%i)" a.id a.arg |
|
119 |
| AAttAscending -> Format.fprintf fmt "'ascending" |
|
120 | 129 |
let array_att_intarg = ["left"; "right"; "high"; "low"; "range"; "reverse_range"; "length"] |
121 | 130 |
|
122 |
type vhdl_signal_attributes_t = SigAtt of string |
|
123 |
let pp_signal_attribute fmt sa = match sa with |
|
124 |
| SigAtt s -> Format.fprintf fmt "'%s" s |
|
125 |
let signal_att = [ "event"; "stable"; "last_value" ] |
|
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 Some (CstInt (0))]; |
|
137 |
} |
|
138 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
126 | 139 |
|
127 |
type vhdl_string_attributes_t = StringAtt of string |
|
128 |
let pp_string_attribute fmt sa = match sa with |
|
129 |
| StringAtt s -> Format.fprintf fmt "'%s" s |
|
130 |
let signal_att = [ "simple_name"; "path_name"; "instance_name" ] |
|
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}];; |
|
131 | 148 |
|
132 | 149 |
(************************************************************************************) |
133 | 150 |
(* Expressions / Statements *) |
134 | 151 |
(************************************************************************************) |
135 | 152 |
|
136 |
|
|
137 |
(* TODO: call to functions? procedures? component instanciations ? *) |
|
138 |
|
|
139 |
type suffix_selection_t = Idx of int | Range of int * int |
|
140 |
let pp_suffix_selection fmt sel = |
|
141 |
match sel with |
|
142 |
| Idx n -> Format.fprintf fmt "(%i)" n |
|
143 |
| Range(n,m) -> Format.fprintf fmt "(%i downto %i)" n m |
|
144 |
|
|
145 |
type vhdl_expr_t = |
|
146 |
| Cst of cst_val_t |
|
147 |
| Var of string (* a signal or a variable *) |
|
148 |
| Sig of { name: string; att: vhdl_signal_attributes_t option } |
|
149 |
| SuffixMod of { expr : vhdl_expr_t; selection : suffix_selection_t } |
|
150 |
| Op of { id: string; args: vhdl_expr_t list } |
|
151 |
|
|
152 |
let rec pp_vhdl_expr fmt e = |
|
153 |
match e with |
|
154 |
| Cst c -> pp_cst_val fmt c |
|
155 |
| Var s -> Format.fprintf fmt "%s" s |
|
156 |
| Sig s -> Format.fprintf |
|
157 |
fmt |
|
158 |
"%s%t" |
|
159 |
s.name |
|
160 |
(fun fmt -> match s.att with None -> () | Some att -> pp_signal_attribute fmt att) |
|
161 |
| SuffixMod s -> |
|
162 |
Format.fprintf fmt "%a %a" |
|
163 |
pp_vhdl_expr s.expr |
|
164 |
pp_suffix_selection s.selection |
|
165 |
| Op op -> ( |
|
166 |
match op.args with |
|
167 |
| [] -> assert false |
|
168 |
| [ e1; e2] -> Format.fprintf fmt "@[<hov 3>%a %s %a@]" pp_vhdl_expr e1 op.id pp_vhdl_expr e2 |
|
169 |
| _ -> assert false (* all ops are binary up to now *) |
|
170 |
(* | _ -> Format.fprintf fmt "@[<hov 3>%s (%a)@]" op.id (Utils.fprintf_list ~sep:",@ " pp_vhdl_expr) op.args *) |
|
171 |
) |
|
172 |
|
|
173 |
(* Available operators in the standard library. There are some restrictions on |
|
174 |
types. See reference doc. *) |
|
175 |
let arith_funs = ["+";"-";"*";"/";"mod"; "rem";"abs";"**"] |
|
153 |
let arith_funs = ["+";"-";"*";"/";"mod"; "rem";"abs";"**";"&"] |
|
176 | 154 |
let bool_funs = ["and"; "or"; "nand"; "nor"; "xor"; "not"] |
177 |
let rel_funs = ["<";">";"<=";">=";"/=";"="] |
|
178 |
|
|
179 |
|
|
180 |
type vhdl_if_case_t = { |
|
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 |
| Wait [@name "WAIT_STATEMENT"] |
|
167 |
| Null of { label: vhdl_name_t [@default NoName]} [@name "NULL_STATEMENT"] |
|
168 |
| Return of { label: vhdl_name_t [@default NoName]} [@name "RETURN_STATEMENT"] |
|
169 |
and vhdl_if_case_t = |
|
170 |
{ |
|
181 | 171 |
if_cond: vhdl_expr_t; |
182 | 172 |
if_block: vhdl_sequential_stmt_t list; |
183 |
} |
|
184 |
and vhdl_sequential_stmt_t = |
|
185 |
| VarAssign of { lhs: string; rhs: vhdl_expr_t } |
|
186 |
| SigSeqAssign of { lhs: string; rhs: vhdl_expr_t } |
|
187 |
| If of { if_cases: vhdl_if_case_t list; |
|
188 |
default: (vhdl_sequential_stmt_t list) option; } |
|
189 |
| Case of { guard: vhdl_expr_t; branches: vhdl_case_item_t list } |
|
190 |
and vhdl_case_item_t = { |
|
191 |
when_cond: vhdl_expr_t; |
|
192 |
when_stmt: vhdl_sequential_stmt_t; |
|
193 | 173 |
} |
174 |
and vhdl_case_item_t = |
|
175 |
{ |
|
176 |
when_cond: vhdl_expr_t list; |
|
177 |
when_stmt: vhdl_sequential_stmt_t list; |
|
178 |
} |
|
179 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
194 | 180 |
|
195 |
|
|
196 |
|
|
197 |
let rec pp_vhdl_sequential_stmt fmt stmt = |
|
198 |
match stmt with |
|
199 |
| VarAssign va -> Format.fprintf fmt "%s := %a;" va.lhs pp_vhdl_expr va.rhs |
|
200 |
| SigSeqAssign va -> Format.fprintf fmt "%s <= %a;" va.lhs pp_vhdl_expr va.rhs |
|
201 |
| If ifva -> ( |
|
202 |
List.iteri (fun idx ifcase -> |
|
203 |
if idx = 0 then |
|
204 |
Format.fprintf fmt "@[<v 3>if" |
|
205 |
else |
|
206 |
Format.fprintf fmt "@ @[<v 3>elsif"; |
|
207 |
Format.fprintf fmt " %a then@ %a@]" |
|
208 |
pp_vhdl_expr ifcase.if_cond |
|
209 |
pp_vhdl_sequential_stmts ifcase.if_block |
|
210 |
) ifva.if_cases; |
|
211 |
let _ = |
|
212 |
match ifva.default with |
|
213 |
| None -> () |
|
214 |
| Some bl -> Format.fprintf fmt "@ @[<v 3>else@ %a@]" pp_vhdl_sequential_stmts bl |
|
215 |
in |
|
216 |
Format.fprintf fmt "@ end if;" |
|
217 |
) |
|
218 |
| Case caseva -> ( |
|
219 |
Format.fprintf fmt "@[<v 3>case %a is@ %a@]@ end case;" |
|
220 |
pp_vhdl_expr caseva.guard |
|
221 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_case) caseva.branches |
|
222 |
) |
|
223 |
|
|
224 |
|
|
225 |
and pp_vhdl_sequential_stmts fmt l = Utils.fprintf_list ~sep:"@ " pp_vhdl_sequential_stmt fmt l |
|
226 |
and pp_vhdl_case fmt case = |
|
227 |
Format.fprintf fmt "when %a => %a" |
|
228 |
pp_vhdl_expr case.when_cond |
|
229 |
pp_vhdl_sequential_stmt case.when_stmt |
|
230 |
|
|
231 |
type signal_condition_t = |
|
181 |
type vhdl_declaration_t = |
|
182 |
| VarDecl of { |
|
183 |
names : vhdl_name_t list; |
|
184 |
typ : vhdl_subtype_indication_t; |
|
185 |
init_val : vhdl_cst_val_t option [@default Some (CstInt (0))] |
|
186 |
} [@name "VARIABLE_DECLARATION"] |
|
187 |
| CstDecl of { |
|
188 |
names : vhdl_name_t list; |
|
189 |
typ : vhdl_subtype_indication_t; |
|
190 |
init_val : vhdl_cst_val_t |
|
191 |
} [@name "CONSTANT_DECLARATION"] |
|
192 |
| SigDecl of { |
|
193 |
names : vhdl_name_t list; |
|
194 |
typ : vhdl_subtype_indication_t; |
|
195 |
init_val : vhdl_cst_val_t option [@default Some (CstInt (0))] |
|
196 |
} [@name "SIGNAL_DECLARATION"] |
|
197 |
| Subprogram of { |
|
198 |
name: vhdl_name_t [@default NoName]; |
|
199 |
kind: string [@default ""]; |
|
200 |
spec: vhdl_subprogram_spec_t [@default {name="";typeMark=NoName;parameters=[];isPure=false}]; |
|
201 |
decl_part: vhdl_declaration_t list [@default []]; |
|
202 |
stmts: vhdl_sequential_stmt_t list [@default []] |
|
203 |
} [@name "SUBPROGRAM_BODY"] |
|
204 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
205 |
|
|
206 |
type vhdl_signal_condition_t = |
|
232 | 207 |
{ |
233 |
expr: vhdl_expr_t; (* when expression *) |
|
234 |
else_case: vhdl_expr_t option; (* optional else case expression.
|
|
208 |
expr: vhdl_expr_t list; (* when expression *)
|
|
209 |
cond: vhdl_expr_t [@default IsNull]; (* optional else case expression.
|
|
235 | 210 |
If None, could be a latch *) |
236 | 211 |
} |
212 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
237 | 213 |
|
238 |
type signal_selection_t = |
|
214 |
type vhdl_signal_selection_t =
|
|
239 | 215 |
{ |
240 |
sel_lhs: string; |
|
241 | 216 |
expr : vhdl_expr_t; |
242 |
when_sel: vhdl_expr_t option;
|
|
217 |
when_sel: vhdl_expr_t list [@default []];
|
|
243 | 218 |
} |
219 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
244 | 220 |
|
245 |
type conditional_signal_t = |
|
221 |
type vhdl_conditional_signal_t =
|
|
246 | 222 |
{ |
247 |
lhs: string; (* assigned signal *) |
|
248 |
rhs: vhdl_expr_t; (* expression *) |
|
249 |
cond: signal_condition_t option (* conditional signal statement *) |
|
223 |
postponed: bool [@default false]; |
|
224 |
label: vhdl_name_t [@default NoName]; |
|
225 |
lhs: vhdl_name_t; (* assigned signal = target*) |
|
226 |
rhs: vhdl_signal_condition_t list; (* expression *) |
|
227 |
cond: vhdl_expr_t [@default IsNull]; |
|
228 |
delay: vhdl_expr_t [@default IsNull]; |
|
250 | 229 |
} |
251 |
|
|
252 |
type process_t = |
|
253 |
{ id: string option; active_sigs: string list; body: vhdl_sequential_stmt_t list } |
|
254 |
|
|
255 |
type selected_signal_t = { sel: vhdl_expr_t; branches: signal_selection_t list } |
|
230 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
231 |
|
|
232 |
type vhdl_process_t = |
|
233 |
{ |
|
234 |
id: vhdl_name_t [@default NoName]; |
|
235 |
declarations: vhdl_declaration_t list option [@key "PROCESS_DECLARATIVE_PART"] [@default Some []]; |
|
236 |
active_sigs: vhdl_name_t list [@default []]; |
|
237 |
body: vhdl_sequential_stmt_t list [@key "PROCESS_STATEMENT_PART"] [@default []] |
|
238 |
} |
|
239 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
240 |
|
|
241 |
type vhdl_selected_signal_t = |
|
242 |
{ |
|
243 |
postponed: bool [@default false]; |
|
244 |
label: vhdl_name_t [@default NoName]; |
|
245 |
lhs: vhdl_name_t; (* assigned signal = target *) |
|
246 |
sel: vhdl_expr_t; |
|
247 |
branches: vhdl_signal_selection_t list [@default []]; |
|
248 |
delay: vhdl_expr_t option; |
|
249 |
} |
|
250 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
256 | 251 |
|
257 | 252 |
type vhdl_concurrent_stmt_t = |
258 |
| SigAssign of conditional_signal_t |
|
259 |
| Process of process_t |
|
260 |
| SelectedSig of selected_signal_t |
|
253 |
| SigAssign of vhdl_conditional_signal_t [@name "CONDITIONAL_SIGNAL_ASSIGNMENT"] |
|
254 |
| Process of vhdl_process_t [@name "PROCESS_STATEMENT"] |
|
255 |
| SelectedSig of vhdl_selected_signal_t [@name "SELECTED_SIGNAL_ASSIGNMENT"] |
|
256 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
261 | 257 |
(* |
262 | 258 |
type vhdl_statement_t = |
263 | 259 |
|
... | ... | |
266 | 262 |
| SequentialStmt of vhdl_sequential_stmt_t |
267 | 263 |
*) |
268 | 264 |
|
269 |
let pp_vhdl_concurrent_stmt fmt stmt = |
|
270 |
let pp_sig_cond fmt va = |
|
271 |
Format.fprintf |
|
272 |
fmt |
|
273 |
"%s <= %a%t;" |
|
274 |
va.lhs |
|
275 |
pp_vhdl_expr va.rhs |
|
276 |
(fun fmt -> match va.cond with |
|
277 |
| None -> () |
|
278 |
| Some cond -> |
|
279 |
Format.fprintf |
|
280 |
fmt |
|
281 |
" when %a%t" |
|
282 |
pp_vhdl_expr cond.expr |
|
283 |
(fun fmt -> match cond.else_case with |
|
284 |
| None -> () |
|
285 |
| Some else_case -> |
|
286 |
Format.fprintf |
|
287 |
fmt |
|
288 |
" else %a" |
|
289 |
pp_vhdl_expr else_case |
|
290 |
) |
|
291 |
) |
|
292 |
in |
|
293 |
let pp_process fmt p = |
|
294 |
Format.fprintf |
|
295 |
fmt |
|
296 |
"@[<v 0>%tprocess %a@ @[<v 3>begin@ %a@]@ end process;@]" |
|
297 |
(fun fmt -> match p.id with Some id -> Format.fprintf fmt "%s: " id| None -> ()) |
|
298 |
(fun fmt asigs -> |
|
299 |
if asigs <> [] then |
|
300 |
Format.fprintf |
|
301 |
fmt |
|
302 |
"(@[<hov 0>%a)@]" |
|
303 |
(Utils.fprintf_list ~sep:",@ " Format.pp_print_string) asigs) |
|
304 |
p.active_sigs |
|
305 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_sequential_stmt) p.body |
|
306 |
in |
|
307 |
let pp_sig_sel fmt va = |
|
308 |
Format.fprintf fmt "@[<v 3>with %a select@ %a;@]" |
|
309 |
pp_vhdl_expr va.sel |
|
310 |
(Utils.fprintf_list |
|
311 |
~sep:"@ " |
|
312 |
(fun fmt b -> |
|
313 |
Format.fprintf |
|
314 |
fmt |
|
315 |
"%s <= %a when %t" |
|
316 |
b.sel_lhs |
|
317 |
pp_vhdl_expr b.expr |
|
318 |
(fun fmt -> match b.when_sel with |
|
319 |
| None -> Format.fprintf fmt "others" |
|
320 |
| Some w -> pp_vhdl_expr fmt w |
|
321 |
)) |
|
322 |
) va.branches in |
|
323 |
match stmt with |
|
324 |
| SigAssign va -> pp_sig_cond fmt va |
|
325 |
| Process p -> pp_process fmt p |
|
326 |
| SelectedSig va -> pp_sig_sel fmt va |
|
327 |
|
|
328 |
|
|
329 |
|
|
330 |
|
|
331 |
|
|
332 |
|
|
333 |
|
|
334 | 265 |
(************************************************************************************) |
335 | 266 |
(* Entities *) |
336 | 267 |
(************************************************************************************) |
337 | 268 |
|
338 |
(* TODO? Seems to appear optionally in entities *) |
|
339 |
type vhdl_generic_t = unit |
|
340 |
let pp_vhdl_generic fmt g = () |
|
341 |
|
|
342 |
|
|
343 |
type vhdl_port_kind_t = InPort | OutPort | InoutPort | BufferPort |
|
344 |
let pp_vhdl_port_kind fmt p = |
|
345 |
match p with |
|
346 |
| InPort -> Format.fprintf fmt "in" |
|
347 |
| OutPort -> Format.fprintf fmt "in" |
|
348 |
| InoutPort -> Format.fprintf fmt "inout" |
|
349 |
| BufferPort -> Format.fprintf fmt "buffer" |
|
350 |
|
|
351 |
|
|
269 |
type vhdl_port_mode_t = |
|
270 |
InPort [@name "in"] |
|
271 |
| OutPort [@name "out"] |
|
272 |
| InoutPort [@name "inout"] |
|
273 |
| BufferPort [@name "buffer"] |
|
274 |
[@@deriving show { with_path = false }, yojson];; |
|
275 |
|
|
352 | 276 |
type vhdl_port_t = |
353 | 277 |
{ |
354 |
name: string; |
|
355 |
kind: vhdl_port_kind_t; |
|
356 |
typ: vhdl_type_t; |
|
278 |
names: vhdl_name_t list [@default []]; |
|
279 |
mode: vhdl_port_mode_t [@default InPort]; |
|
280 |
typ: vhdl_subtype_indication_t; |
|
281 |
expr: vhdl_expr_t [@default IsNull]; |
|
357 | 282 |
} |
283 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
358 | 284 |
|
359 |
let pp_vhdl_port fmt p = |
|
360 |
Format.fprintf fmt "%s : %a %a" |
|
361 |
p.name |
|
362 |
pp_vhdl_port_kind p.kind |
|
363 |
pp_vhdl_type p.typ |
|
364 |
|
|
365 |
|
|
366 | 285 |
type vhdl_entity_t = |
367 | 286 |
{ |
368 |
name: string; |
|
369 |
generics: vhdl_generic_t list; |
|
370 |
ports: vhdl_port_t list; |
|
287 |
name: vhdl_name_t [@default NoName]; |
|
288 |
generics: vhdl_port_t list [@default []]; |
|
289 |
ports: vhdl_port_t list [@default []]; |
|
290 |
declaration: vhdl_declaration_t list [@key "ENTITY_DECLARATIVE_PART"] [@default []]; |
|
291 |
stmts: vhdl_concurrent_stmt_t list [@key "ENTITY_STATEMENT_PART"] [@default []]; |
|
371 | 292 |
} |
372 |
let pp_vhdl_entity fmt e = |
|
373 |
Format.fprintf |
|
374 |
fmt |
|
375 |
"@[<v 3>entity %s is@ %t%t@]@ end %s;@ " |
|
376 |
e.name |
|
377 |
(fun fmt -> List.iter (fun g -> Format.fprintf fmt "generic %a;@ " pp_vhdl_generic g) e.generics) |
|
378 |
(fun fmt -> |
|
379 |
if e.ports = [] then () else |
|
380 |
Format.fprintf fmt "port (@[<hov 0>%a@]);" (Utils.fprintf_list ~sep:",@ " pp_vhdl_port) e.ports) |
|
381 |
e.name |
|
382 |
|
|
383 |
|
|
384 |
|
|
293 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
385 | 294 |
|
386 | 295 |
(************************************************************************************) |
387 | 296 |
(* Packages / Library loading *) |
388 | 297 |
(************************************************************************************) |
389 |
|
|
390 |
|
|
391 | 298 |
|
392 | 299 |
(* Optional. Describes shared definitions *) |
393 | 300 |
type vhdl_package_t = |
394 | 301 |
{ |
395 |
name: string;
|
|
396 |
shared_defs: vhdl_definition_t list; |
|
302 |
name: vhdl_name_t [@default NoName];
|
|
303 |
shared_defs: vhdl_definition_t list [@default []];
|
|
397 | 304 |
} |
305 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
398 | 306 |
|
399 |
let pp_vhdl_package fmt p = |
|
400 |
Format.fprintf |
|
401 |
fmt |
|
402 |
"@[<v 3>package %s is@ %a@]@ end %s;@ " |
|
403 |
p.name |
|
404 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_definition) p.shared_defs |
|
405 |
p.name |
|
406 |
|
|
407 |
type vhdl_load_t = Library of string | Use of string list |
|
408 |
let pp_vhdl_load fmt l = |
|
409 |
match l with |
|
410 |
| Library s -> Format.fprintf fmt "library %s;@ " s |
|
411 |
| Use sl -> Format.fprintf fmt "use %a;@ " (Utils.fprintf_list ~sep:"." Format.pp_print_string) sl |
|
412 |
|
|
307 |
type vhdl_load_t = |
|
308 |
Library of vhdl_name_t list [@name "LIBRARY_CLAUSE"] [@default []] |
|
309 |
| Use of vhdl_name_t list [@name "USE_CLAUSE"] [@default []] |
|
310 |
[@@deriving show { with_path = false }, yojson];; |
|
413 | 311 |
|
414 | 312 |
(************************************************************************************) |
415 | 313 |
(* Architecture / VHDL Design *) |
416 | 314 |
(************************************************************************************) |
417 | 315 |
|
418 |
|
|
419 | 316 |
type vhdl_architecture_t = |
420 | 317 |
{ |
421 |
name: string;
|
|
422 |
entity: string;
|
|
423 |
declarations: vhdl_declaration_t list; |
|
424 |
body: vhdl_concurrent_stmt_t list;
|
|
318 |
name: vhdl_name_t [@default NoName];
|
|
319 |
entity: vhdl_name_t [@default NoName];
|
|
320 |
declarations: vhdl_declaration_t list [@key "ARCHITECTURE_DECLARATIVE_PART"] [@default []];
|
|
321 |
body: vhdl_concurrent_stmt_t list [@key "ARCHITECTURE_STATEMENT_PART"] [@default []];
|
|
425 | 322 |
} |
323 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
426 | 324 |
|
427 |
let pp_vhdl_architecture fmt a = |
|
428 |
Format.fprintf |
|
429 |
fmt |
|
430 |
"@[<v 3>architecture %s of %s is@ %a@]@ @[<v 3>begin@ %a@]@ end %s;" |
|
431 |
a.name |
|
432 |
a.entity |
|
433 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_declaration) a.declarations |
|
434 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_concurrent_stmt) a.body |
|
435 |
a.name |
|
436 |
|
|
437 |
|
|
438 |
(* TODO. Configuraiton is optional *) |
|
325 |
(* TODO. Configuration is optional *) |
|
439 | 326 |
type vhdl_configuration_t = unit |
440 |
let pp_vhdl_configuration fmt c = ()
|
|
327 |
[@@deriving show { with_path = false }, yojson {strict = false}];;
|
|
441 | 328 |
|
329 |
type vhdl_library_unit_t = (* TODO: PACKAGE_BODY *) |
|
330 |
Package of vhdl_package_t [@name "PACKAGE_DECLARATION"] |
|
331 |
| Entities of vhdl_entity_t [@name "ENTITY_DECLARATION"] |
|
332 |
| Architecture of vhdl_architecture_t [@name "ARCHITECTURE_BODY"] |
|
333 |
| Configuration of vhdl_configuration_t [@name "CONFIGURATION_DECLARATION"] |
|
334 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
442 | 335 |
|
336 |
type vhdl_design_unit_t = |
|
337 |
{ |
|
338 |
contexts: vhdl_load_t list [@default []]; |
|
339 |
library: vhdl_library_unit_t; |
|
340 |
} |
|
341 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
443 | 342 |
|
444 |
type vhdl_design_t = |
|
343 |
type vhdl_design_file_t =
|
|
445 | 344 |
{ |
446 |
packages: vhdl_package_t list; |
|
447 |
libraries: vhdl_load_t list; |
|
448 |
entities: vhdl_entity_t list; |
|
449 |
architectures: vhdl_architecture_t list; |
|
450 |
configuration: vhdl_configuration_t option; |
|
345 |
design_units: vhdl_design_unit_t list [@default []]; |
|
451 | 346 |
} |
347 |
[@@deriving show { with_path = false }, yojson {strict = false}];; |
|
452 | 348 |
|
453 |
let pp_vhdl_design fmt d = |
|
454 |
Format.fprintf |
|
455 |
fmt |
|
456 |
"@[<v 0>%a%t%a%t%a%t%a%t@]" |
|
457 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_package) d.packages |
|
458 |
(fun fmt -> if d.packages <> [] then Format.fprintf fmt "@ ") |
|
459 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_load) d.libraries |
|
460 |
(fun fmt -> if d.libraries <> [] then Format.fprintf fmt "@ ") |
|
461 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_entity) d.entities |
|
462 |
(fun fmt -> if d.entities <> [] then Format.fprintf fmt "@ ") |
|
463 |
(Utils.fprintf_list ~sep:"@ " pp_vhdl_architecture) d.architectures |
|
464 |
(fun fmt -> if d.architectures <> [] then Format.fprintf fmt "@ ") |
|
349 |
type vhdl_file_t = |
|
350 |
{ |
|
351 |
design_file: vhdl_design_file_t [@default {design_units=[]}] [@key "DESIGN_FILE"]; |
|
352 |
} |
|
353 |
[@@deriving show { with_path = false }, yojson];; |
Also available in: Unified diff
New version of the vhdl import + compilation