Skip to content

Commit 6d38f85

Browse files
committed
Add Clash.Tutorial content on primitives
1 parent e31f1cc commit 6d38f85

File tree

2 files changed

+391
-0
lines changed

2 files changed

+391
-0
lines changed

compiler-user-guide/src/SUMMARY.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,4 +12,5 @@
1212
- [Language](./developing-hardware/language.md)
1313
- [Prelude](./developing-hardware/prelude.md)
1414
- [Flags](./developing-hardware/flags.md)
15+
- [User-defined primitives](./developing-hardware/primitives.md)
1516
- [Hacking on Clash](./hacking-on-clash/index.md)
Lines changed: 390 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,390 @@
1+
# User-defined primitives
2+
There are times when you already have an existing piece of IP, or there are times where you need the HDL to have a specific shape so that the HDL synthesis tool can infer a specific component.
3+
In these specific cases you can resort to defining your own HDL primitives. Actually, most of the primitives in Clash are specified in the same way as you will read about in this section.
4+
There are perhaps 10 (at most) functions which are truly hard-coded into the Clash compiler.
5+
You can take a look at the files in <https://github.com/clash-lang/clash-compiler/tree/master/clash-lib/prims/vhdl> (or <https://github.com/clash-lang/clash-compiler/tree/master/clash-lib/prims/verilog> for the Verilog primitives or <https://github.com/clash-lang/clash-compiler/tree/master/clash-lib/prims/systemverilog> for the SystemVerilog primitives) if you want to know which functions are defined as "regular" primitives.
6+
The compiler looks for primitives in four locations:
7+
8+
* The official install location: e.g.
9+
10+
* `$HOME/.stack/snapshots/x86_64-linux/<HASH>/share/<GHC_VERSION>/clash-lib-<VERSION>/prims/common`
11+
* `$HOME/.stack/snapshots/x86_64-linux/<HASH>/share/<GHC_VERSION>/clash-lib-<VERSION>/prims/commonverilog`
12+
* `$HOME/.stack/snapshots/x86_64-linux/<HASH>/share/<GHC_VERSION>/clash-lib-<VERSION>/prims/systemverilog`
13+
* `$HOME/.stack/snapshots/x86_64-linux/<HASH>/share/<GHC_VERSION>/clash-lib-<VERSION>/prims/verilog`
14+
* `$HOME/.stack/snapshots/x86_64-linux/<HASH>/share/<GHC_VERSION>/clash-lib-<VERSION>/prims/vhdl`
15+
16+
* Directories indicated by a `Clash.Annotations.Primitive.Primitive` annotation
17+
* The current directory (the location given by `pwd`)
18+
* The include directories specified on the command-line: `-i<DIR>`
19+
20+
Where redefined primitives in the current directory or include directories will overwrite those in the official install location.
21+
For now, files containing primitive definitions must have a `.primitives.yaml` file-extension.
22+
23+
Clash differentiates between two types of primitives, _expression_ primitives and _declaration_ primitives, corresponding to whether the primitive is an HDL _expression_ or an HDL _declaration_.
24+
We will first explore _expression_ primitives, using `Signed` multiplication (`*`) as an example.
25+
The `Clash.Sized.Internal.Signed` module specifies multiplication as follows:
26+
27+
``` haskell
28+
(*#) :: KnownNat n => Signed n -> Signed n -> Signed n
29+
(S a) *# (S b) = fromInteger_INLINE (a * b)
30+
{-# OPAQUE (*#) #-}
31+
```
32+
33+
For which the VHDL _expression_ primitive is:
34+
35+
``` yaml
36+
BlackBox:
37+
name: Clash.Sized.Internal.Signed.*#
38+
kind: Expression
39+
type: '(*#) :: KnownNat n => Signed n -> Signed n -> Signed n'
40+
template: resize(~ARG[1] * ~ARG[2], ~LIT[0])
41+
```
42+
43+
The `name` of the primitive is the _fully qualified_ name of the function you are creating the primitive for.
44+
Because we are creating an _expression_ primitive the kind must be set to `Expression`.
45+
As the name suggest, it is a VHDL _template_, meaning that the compiler must fill in the holes heralded by the tilde (~).
46+
Here:
47+
48+
* `~ARG[1]` denotes the second argument given to the `(*#)` function, which corresponds to the LHS of the (`*`) operator.
49+
* `~ARG[2]` denotes the third argument given to the `(*#)` function, which corresponds to the RHS of the (`*`) operator.
50+
* `~LIT[0]` denotes the first argument given to the `(*#)` function, with the extra condition that it must be a `LIT`eral.
51+
If for some reason this first argument does not turn out to be a literal then the compiler will raise an error.
52+
This first arguments corresponds to the `KnownNat n` class constraint.
53+
54+
55+
An extensive list with all of the template holes will be given the end of this section. What we immediately notice is that class constraints are counted as normal arguments in the primitive definition.
56+
This is because these class constraints are actually represented by ordinary record types, with fields corresponding to the methods of the type class.
57+
In the above case, `KnownNat` is actually just like a `newtype` wrapper for `Natural`.
58+
59+
The second kind of primitive that we will explore is the _declaration_ primitive.
60+
We will use `blockRam#` as an example, for which the Haskell/Clash code is:
61+
62+
``` haskell
63+
{-# LANGUAGE BangPatterns #-}
64+
65+
module BlockRam where
66+
67+
import Clash.Explicit.Prelude
68+
import Clash.Annotations.Primitive (hasBlackBox)
69+
import Clash.Signal.Internal (Clock, Signal (..), (.&&.))
70+
import Clash.Sized.Vector (Vec, toList)
71+
import Clash.XException (defaultSeqX)
72+
73+
import qualified Data.Vector as V
74+
import GHC.Stack (HasCallStack, withFrozenCallStack)
75+
76+
blockRam#
77+
:: ( KnownDomain dom
78+
, HasCallStack
79+
, NFDataX a )
80+
=> Clock dom -- ^ Clock to synchronize to
81+
-> Enable dom -- ^ Global enable
82+
-> Vec n a -- ^ Initial content of the BRAM, also
83+
-- determines the size, @n@, of the BRAM.
84+
--
85+
-- __NB__: __MUST__ be a constant.
86+
-> Signal dom Int -- ^ Read address @r@
87+
-> Signal dom Bool -- ^ Write enable
88+
-> Signal dom Int -- ^ Write address @w@
89+
-> Signal dom a -- ^ Value to write (at address @w@)
90+
-> Signal dom a -- ^ Value of the BRAM at address @r@ from
91+
-- the previous clock cycle
92+
blockRam# (Clock _) gen content rd wen =
93+
go
94+
(V.fromList (toList content))
95+
(withFrozenCallStack (deepErrorX "blockRam: intial value undefined"))
96+
(fromEnable gen)
97+
rd
98+
(fromEnable gen .&&. wen)
99+
where
100+
go !ram o ret@(~(re :- res)) rt@(~(r :- rs)) et@(~(e :- en)) wt@(~(w :- wr)) dt@(~(d :- din)) =
101+
let ram' = d `defaultSeqX` upd ram e (fromEnum w) d
102+
o' = if re then ram V.! r else o
103+
in o `seqX` o :- (ret `seq` rt `seq` et `seq` wt `seq` dt `seq` go ram' o' res rs en wr din)
104+
105+
upd ram we waddr d = case maybeIsX we of
106+
Nothing -> case maybeIsX waddr of
107+
Nothing -> V.map (const (seq waddr d)) ram
108+
Just wa -> ram V.// [(wa,d)]
109+
Just True -> case maybeIsX waddr of
110+
Nothing -> V.map (const (seq waddr d)) ram
111+
Just wa -> ram V.// [(wa,d)]
112+
_ -> ram
113+
{-# OPAQUE blockRam# #-}
114+
{-# ANN blockRam# hasBlackBox #-}
115+
```
116+
117+
And for which the _declaration_ primitive is:
118+
119+
``` yaml
120+
BlackBox:
121+
name: Clash.Explicit.BlockRam.blockRam#
122+
kind: Declaration
123+
type: |-
124+
blockRam#
125+
:: ( KnownDomain dom ARG[0]
126+
, HasCallStack -- ARG[1]
127+
, NFDataX a ) -- ARG[2]
128+
=> Clock dom -- clk, ARG[3]
129+
-> Enable dom -- en, ARG[4]
130+
-> Vec n a -- init, ARG[5]
131+
-> Signal dom Int -- rd, ARG[6]
132+
-> Signal dom Bool -- wren, ARG[7]
133+
-> Signal dom Int -- wr, ARG[8]
134+
-> Signal dom a -- din, ARG[9]
135+
-> Signal dom a
136+
template: |-
137+
-- blockRam begin
138+
~GENSYM[~RESULT_blockRam][1] : block
139+
signal ~GENSYM[~RESULT_RAM][2] : ~TYP[5] := ~CONST[5];
140+
signal ~GENSYM[rd][4] : integer range 0 to ~LENGTH[~TYP[5]] - 1;
141+
signal ~GENSYM[wr][5] : integer range 0 to ~LENGTH[~TYP[5]] - 1;
142+
begin
143+
~SYM[4] <= to_integer(~ARG[6])
144+
-- pragma translate_off
145+
mod ~LENGTH[~TYP[5]]
146+
-- pragma translate_on
147+
;
148+
~SYM[5] <= to_integer(~ARG[8])
149+
-- pragma translate_off
150+
mod ~LENGTH[~TYP[5]]
151+
-- pragma translate_on
152+
;
153+
~IF ~VIVADO ~THEN
154+
~SYM[6] : process(~ARG[3])
155+
begin
156+
if ~IF~ACTIVEEDGE[Rising][0]~THENrising_edge~ELSEfalling_edge~FI(~ARG[3]) then
157+
if ~ARG[7] ~IF ~ISACTIVEENABLE[4] ~THEN and ~ARG[4] ~ELSE ~FI then
158+
~SYM[2](~SYM[5]) <= ~TOBV[~ARG[9]][~TYP[9]];
159+
end if;
160+
~RESULT <= fromSLV(~SYM[2](~SYM[4]))
161+
-- pragma translate_off
162+
after 1 ps
163+
-- pragma translate_on
164+
;
165+
end if;
166+
end process; ~ELSE
167+
~SYM[6] : process(~ARG[3])
168+
begin
169+
if ~IF~ACTIVEEDGE[Rising][0]~THENrising_edge~ELSEfalling_edge~FI(~ARG[3]) then
170+
if ~ARG[7] ~IF ~ISACTIVEENABLE[4] ~THEN and ~ARG[4] ~ELSE ~FI then
171+
~SYM[2](~SYM[5]) <= ~ARG[9];
172+
end if;
173+
~RESULT <= ~SYM[2](~SYM[4])
174+
-- pragma translate_off
175+
after 1 ps
176+
-- pragma translate_on
177+
;
178+
end if;
179+
end process; ~FI
180+
end block;
181+
--end blockRam
182+
```
183+
184+
Again, the `name` of the primitive is the fully qualified name of the function you are creating the primitive for.
185+
Because we are creating a _declaration_ primitive the _kind_ must be set to `Declaration`.
186+
Instead of discussing what the individual template holes mean in the above context, we will instead just give a general listing of the available template holes:
187+
188+
* `~RESULT`: Signal to which the result of a primitive must be assigned to.
189+
NB: Only used in a _declaration_ primitive.
190+
* `~ARG[N]`: `(N+1)`'th argument to the function.
191+
* `~CONST[N]`: `(N+1)`'th argument to the function.
192+
Like `~ARG`, but Clash will try to reduce this to a literal, even if it would otherwise consider it too expensive.
193+
And if Clash fails to reduce this argument to a literal it will produce an error.
194+
* `~LIT[N]`: `(N+1)`'th argument to the function.
195+
Like `~CONST` but values are rendered as a bare literals, without any size or type annotations.
196+
This only works for numeric types, and not for BitVector.
197+
* `~TYP[N]`: VHDL type of the `(N+1)`'th argument.
198+
* `~TYPO`: VHDL type of the result.
199+
* `~TYPM[N]`: VHDL type*name* of the `(N+1)`'th argument; used in _type qualification_.
200+
* `~TYPMO`: VHDL type*name* of the result; used in _type qualification_.
201+
* `~ERROR[N]`: Error value for the VHDL type of the `(N+1)`'th argument.
202+
* `~ERRORO`: Error value for the VHDL type of the result.
203+
* `~GENSYM[<NAME>][N]`: Create a unique name, trying to stay as close to the given `<NAME>` as possible.
204+
This unique symbol can be referred to in other places using `~SYM[N]`.
205+
* `~SYM[N]`: a reference to the unique symbol created by `~GENSYM[<NAME>][N]`.
206+
* `~SIGD[<HOLE>][N]`: Create a signal declaration, using `<HOLE>` as the name of the signal, and the type of the `(N+1)`'th argument.
207+
* `~SIGDO[<HOLE>]`: Create a signal declaration, using `<HOLE>` as the name of the signal, and the type of the result.
208+
* `~TYPEL[<HOLE>]`: The element type of the vector type represented by `<HOLE>`.
209+
The content of `<HOLE>` must either be: `~TYP[N]`, `~TYPO`, or `~TYPEL[<HOLE>]`.
210+
* `~COMPNAME`: The name of the component in which the primitive is instantiated.
211+
* `~LENGTH[<HOLE>]`: The vector length of the type represented by `<HOLE>`.
212+
* `~DEPTH[<HOLE>]`: The tree depth of the type represented by `<HOLE>`.
213+
The content of `<HOLE>` must either be: `~TYP[N]`, `~TYPO`, or `~TYPEL[<HOLE>]`.
214+
* `~SIZE[<HOLE>]`: The number of bits needed to encode the type represented by `<HOLE>`.
215+
The content of `<HOLE>` must either be: `~TYP[N]`, `~TYPO`, or `~TYPEL[<HOLE>]`.
216+
* `~IF <CONDITION> ~THEN <THEN> ~ELSE <ELSE> ~FI`: renders the `<ELSE>` part when `<CONDITION>` evaluates to _0_, and renders the `<THEN>` in all other cases.
217+
Valid `<CONDITION>`s are `~LENGTH[<HOLE>]`, `~SIZE[<HOLE>]`, `~CMPLE[<HOLE1>][<HOLE2>]`, `~DEPTH[<HOLE>]`, `~VIVADO`, `~IW64`, `~ISLIT[N]`, `~ISVAR[N]`, `~ISACTIVEENABLE[N]`, `~ISSYNC[N]`, and `~AND[<HOLE1>,<HOLE2>,..]`.
218+
* `~VIVADO`: _1_ when Clash compiler is invoked with the `-fclash-hdlsyn Vivado` (or `Xilinx` or `ISE`) flag.
219+
To be used with in an `~IF .. ~THEN .. ~ELSE .. ~FI` statement.
220+
* `~CMPLE[<HOLE1>][<HOLE2>]`: _1_ when `<HOLE1> <= <HOLE2>`, otherwise _0_
221+
* `~IW64`: _1_ when `Int`/`Word`/`Integer` types are represented with 64 bits in HDL.
222+
_0_ when they're represented by 32 bits.
223+
* `~TOBV[<HOLE>][<TYPE>]`: create conversion code that so that the expression in `<HOLE>` is converted to a bit vector (`std_logic_vector`).
224+
The `<TYPE>` hole indicates the type of the expression and must be either `~TYP[N]`, `~TYPO`, or `~TYPEL[<HOLE>]`.
225+
* `~FROMBV[<HOLE>][<TYPE>]`: create conversion code that so that the expression in `<HOLE>`, which has a bit vector (`std_logic_vector`) type, is converted to type indicated by `<TYPE>`.
226+
The `<TYPE>` hole must be either `~TYP[N]`, `~TYPO`, or `~TYPEL[<HOLE>]`.
227+
* `~INCLUDENAME[N]`: the generated name of the `N`'th included component.
228+
* `~FILE[<HOLE>]`: The argument mentioned in `<HOLE>` is a file which must be copied to the location of the generated HDL.
229+
* `~GENERATE`: Verilog: create a _generate_ statement, except when already in a _generate_ context.
230+
* `~ENDGENERATE`: Verilog: create an _endgenerate_ statement, except when already in a _generate_ context.
231+
* `~ISLIT[N]`: Is the `(N+1)`'th argument to the function a literal.
232+
* `~ISVAR[N]`: Is the `(N+1)`'th argument to the function explicitly not a literal.
233+
* `~ISSCALAR[N]`: Is the `(N+1)`'th argument to the function a scalar.
234+
Note that this means different things for different HDLs.
235+
In (System)Verilog only `Bit` and `Bool` are considered scalar.
236+
In VHDL, in addition to those two, enumeration types and integers are considered scalar.
237+
* `~TAG[N]`: Name of given domain.
238+
Errors when called on an argument which is not a `KnownDomain`, `Reset`, or `Clock`.
239+
* `~PERIOD[N]`: Clock period of given domain.
240+
Errors when called on an argument which is not a `Clock`, `Reset`, `KnownDomain` or `KnownConf`.
241+
* `~ISACTIVEENABLE[N]`: Is the `(N+1)`'th argument an Enable line __not__ set to a constant True.
242+
* `~ISSYNC[N]`: Does synthesis domain at the `(N+1)`'th argument have synchronous resets.
243+
Errors when called on an argument which is not a `Reset`, `Clock`, `Enable`, `KnownDomain` or `KnownConf`.
244+
* `~ISINITDEFINED[N]`: Does synthesis domain at the `(N+1)`'th argument have defined initial values.
245+
Errors when called on an argument which is not a `Clock`, `Reset`, `Enable`, `KnownDomain` or `KnownConf`.
246+
* `~ACTIVEEDGE[edge][N]`: Does synthesis domain at the `(N+1)`'th argument respond to _edge_.
247+
_edge_ must be one of `Falling` or `Rising`.
248+
Errors when called on an argument which is not a `Clock`, `Reset`, `Enable`, `KnownDomain` or `KnownConf`.
249+
* `~AND[<HOLE1>,<HOLE2>,..]`: Logically _and_ the conditions in the `<HOLE>`'s
250+
* `~VAR[<NAME>][N]`: Like `~ARG[N]` but binds the argument to a variable named NAME.
251+
The `<NAME>` can be left blank, then Clash will come up with a (unique) name.
252+
* `~VARS[N]`: VHDL: Return the variables at the `(N+1)`'th argument.
253+
* `~NAME[N]`: Render the `(N+1)`'th string literal argument as an identifier instead of a string literal.
254+
Fails when the `(N+1)`'th argument is not a string literal.
255+
* `~DEVNULL[<HOLE>]`: Render all dependencies of `<HOLE>`, but disregard direct output.
256+
* `~REPEAT[<HOLE>][N]`: Repeat literal value of `<HOLE>` a total of `N` times.
257+
* `~TEMPLATE[<HOLE1>][<HOLE2>]`: Render a file `<HOLE1>` with contents `<HOLE2>`.
258+
259+
Some final remarks to end this section: HDL primitives are there to instruct the Clash compiler to use the given HDL template, instead of trying to do normal synthesis.
260+
As a consequence you can use constructs inside the Haskell definitions that are normally not synthesizable by the Clash compiler.
261+
However, VHDL primitives do not give us _co-simulation_: where you would be able to simulate VHDL and Haskell in a _single_ environment.
262+
If you still want to simulate your design in Haskell, you will have to describe, in a cycle- and bit-accurate way, the behavior of that (potentially complex) IP you are trying to include in your design.
263+
264+
## Verilog examples
265+
266+
For those who are interested, the equivalent Verilog primitives are:
267+
268+
``` yaml
269+
BlackBox:
270+
name: Clash.Sized.Internal.Signed.*#
271+
kind: Expression
272+
type: '(*#) :: KnownNat n => Signed n -> Signed n -> Signed n'
273+
template: ~ARG[1] * ~ARG[2]
274+
```
275+
276+
and
277+
278+
``` yaml
279+
BlackBox:
280+
name: Clash.Explicit.BlockRam.blockRam#
281+
kind: Declaration
282+
outputUsage: NonBlocking
283+
type: |-
284+
blockRam#
285+
:: ( KnownDomain dom ARG[0]
286+
, HasCallStack -- ARG[1]
287+
, NFDataX a ) -- ARG[2]
288+
=> Clock dom -- clk, ARG[3]
289+
=> Enable dom -- en, ARG[4]
290+
-> Vec n a -- init, ARG[5]
291+
-> Signal dom Int -- rd, ARG[6]
292+
-> Signal dom Bool -- wren, ARG[7]
293+
-> Signal dom Int -- wr, ARG[8]
294+
-> Signal dom a -- din, ARG[9]
295+
-> Signal dom a
296+
template: |-
297+
// blockRam begin
298+
reg ~TYPO ~GENSYM[~RESULT_RAM][1] [0:~LENGTH[~TYP[5]]-1];
299+
reg ~TYP[5] ~GENSYM[ram_init][3];
300+
integer ~GENSYM[i][4];
301+
initial begin
302+
~SYM[3] = ~CONST[5];
303+
for (~SYM[4]=0; ~SYM[4] < ~LENGTH[~TYP[5]]; ~SYM[4] = ~SYM[4] + 1) begin
304+
~SYM[1][~LENGTH[~TYP[5]]-1-~SYM[4]] = ~SYM[3][~SYM[4]*~SIZE[~TYPO]+:~SIZE[~TYPO]];
305+
end
306+
end
307+
~IF ~ISACTIVEENABLE[4] ~THEN
308+
always @(~IF~ACTIVEEDGE[Rising][0]~THENposedge~ELSEnegedge~FI ~ARG[3]) begin : ~GENSYM[~RESULT_blockRam][5]~IF ~VIVADO ~THEN
309+
if (~ARG[4]) begin
310+
if (~ARG[7]) begin
311+
~SYM[1][~ARG[8]] <= ~ARG[9];
312+
end
313+
~RESULT <= ~SYM[1][~ARG[6]];
314+
end~ELSE
315+
if (~ARG[7] & ~ARG[4]) begin
316+
~SYM[1][~ARG[8]] <= ~ARG[9];
317+
end
318+
if (~ARG[4]) begin
319+
~RESULT <= ~SYM[1][~ARG[6]];
320+
end~FI
321+
end~ELSE
322+
always @(~IF~ACTIVEEDGE[Rising][0]~THENposedge~ELSEnegedge~FI ~ARG[3]) begin : ~SYM[5]
323+
if (~ARG[7]) begin
324+
~SYM[1][~ARG[8]] <= ~ARG[9];
325+
end
326+
~RESULT <= ~SYM[1][~ARG[6]];
327+
end~FI
328+
// blockRam end
329+
```
330+
331+
## SystemVerilog examples
332+
And the equivalent SystemVerilog primitives are:
333+
334+
``` yaml
335+
BlackBox:
336+
name: Clash.Sized.Internal.Signed.*#
337+
kind: Expression
338+
type: '(*#) :: KnownNat n => Signed n -> Signed n -> Signed n'
339+
template: ~ARG[1] * ~ARG[2]
340+
```
341+
342+
and
343+
344+
``` yaml
345+
BlackBox:
346+
name: Clash.Explicit.BlockRam.blockRam#
347+
kind: Declaration
348+
type: |-
349+
blockRam#
350+
:: ( KnownDomain dom ARG[0]
351+
, HasCallStack -- ARG[1]
352+
, NFDataX a ) -- ARG[2]
353+
=> Clock dom -- clk, ARG[3]
354+
-> Enable dom -- en, ARG[4]
355+
-> Vec n a -- init, ARG[5]
356+
-> Signal dom Int -- rd, ARG[6]
357+
-> Signal dom Bool -- wren, ARG[7]
358+
-> Signal dom Int -- wr, ARG[8]
359+
-> Signal dom a -- din, ARG[9]
360+
-> Signal dom a
361+
template: |-
362+
// blockRam begin
363+
~SIGD[~GENSYM[RAM][1]][5];
364+
logic [~SIZE[~TYP[9]]-1:0] ~GENSYM[~RESULT_q][2];
365+
initial begin
366+
~SYM[1] = ~CONST[5];
367+
end~IF ~ISACTIVEENABLE[4] ~THEN
368+
always @(~IF~ACTIVEEDGE[Rising][0]~THENposedge~ELSEnegedge~FI ~ARG[3]) begin : ~GENSYM[~COMPNAME_blockRam][3]~IF ~VIVADO ~THEN
369+
if (~ARG[4]) begin
370+
if (~ARG[7]) begin
371+
~SYM[1][~ARG[8]] <= ~TOBV[~ARG[9]][~TYP[9]];
372+
end
373+
~SYM[2] <= ~SYM[1][~ARG[6]];
374+
end~ELSE
375+
if (~ARG[7] & ~ARG[4]) begin
376+
~SYM[1][~ARG[8]] <= ~TOBV[~ARG[9]][~TYP[9]];
377+
end
378+
if (~ARG[4]) begin
379+
~SYM[2] <= ~SYM[1][~ARG[6]];
380+
end~FI
381+
end~ELSE
382+
always @(~IF~ACTIVEEDGE[Rising][0]~THENposedge~ELSEnegedge~FI ~ARG[3]) begin : ~SYM[3]
383+
if (~ARG[7]) begin
384+
~SYM[1][~ARG[8]] <= ~TOBV[~ARG[9]][~TYP[9]];
385+
end
386+
~SYM[2] <= ~SYM[1][~ARG[6]];
387+
end~FI
388+
assign ~RESULT = ~FROMBV[~SYM[2]][~TYP[9]];
389+
// blockRam end
390+
```

0 commit comments

Comments
 (0)