Skip to content

Commit b48575b

Browse files
leonschoorlchristiaanb
authored andcommitted
Fix index_int verilog prim
... for non-var vecs
1 parent de7c7f0 commit b48575b

File tree

2 files changed

+22
-15
lines changed

2 files changed

+22
-15
lines changed

clash-lib/src/Clash/Primitives/Sized/Vector.hs

Lines changed: 17 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ import GHC.Stack (HasCallStack)
3232

3333
import Clash.Backend
3434
(Backend, hdlTypeErrValue, expr, blockDecl)
35+
import Clash.Core.TermInfo (isVar)
3536
import Clash.Core.Type
3637
(Type(LitTy), LitTy(NumTy), coreView)
3738
import Clash.Netlist.BlackBox (isLiteral)
@@ -241,21 +242,21 @@ foldTF' args =
241242
error $ "Unexpected number of arguments: " ++ show (length (bbInputs args))
242243

243244
indexIntVerilog :: BlackBoxFunction
244-
indexIntVerilog _isD _primName args _ty = return ((meta,) <$> bb)
245+
indexIntVerilog _isD _primName args _ty = return bb
245246
where
246-
meta = emptyBlackBoxMeta{bbKind=bbKi}
247-
248-
bbKi = case args of
249-
[_nTy,_aTy,_kn,_v,Left ix]
250-
| isLiteral ix -> TExpr
251-
_ -> TDecl
247+
meta bbKi = emptyBlackBoxMeta{bbKind=bbKi}
252248

253249
bb = case args of
250+
[_nTy,_aTy,_kn,Left v,Left ix] | isLiteral ix && isVar v ->
251+
Right (meta TExpr, BBFunction "Clash.Primitives.Sized.Vector.indexIntVerilogTF" 0 indexIntVerilogTF)
254252
[_nTy,_aTy,_kn,_v,Left ix] | isLiteral ix ->
255-
Right (BBFunction "Clash.Primitives.Sized.Vector.indexIntVerilogTF" 0 indexIntVerilogTF)
253+
case runParse (pack (I.unindent bbTextLitIx)) of
254+
Success t -> Right (meta TDecl, BBTemplate t)
255+
_ -> Left "internal error: parse fail"
256+
256257
_ ->
257-
BBTemplate <$> case runParse (pack (I.unindent bbText)) of
258-
Success t -> Right t
258+
case runParse (pack (I.unindent bbText)) of
259+
Success t -> Right (meta TDecl, BBTemplate t)
259260
_ -> Left "internal error: parse fail"
260261

261262
bbText = [I.i|
@@ -270,6 +271,12 @@ indexIntVerilog _isD _primName args _ty = return ((meta,) <$> bb)
270271
assign ~RESULT = ~SYM[0][~ARG[2]];~ELSEassign ~RESULT = ~ERRORO;~FI
271272
// index end|]
272273

274+
bbTextLitIx = [I.i|
275+
// index lit begin
276+
~IF~SIZE[~TYP[1]]~THENassign ~RESULT = ~VAR[vec][1][~SIZE[~TYP[1]]-1-~LIT[2]*~SIZE[~TYPO] -: ~SIZE[~TYPO]];~ELSEassign ~RESULT = ~ERRORO;~FI
277+
// index lit end|]
278+
279+
273280
indexIntVerilogTF :: TemplateFunction
274281
indexIntVerilogTF = TemplateFunction used valid indexIntVerilogTemplate
275282
where

tests/shouldwork/Vector/IndexInt2.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,11 @@ import Clash.Explicit.Testbench
1313

1414
import Clash.Netlist.Types
1515

16-
topEntity :: Vec 4 Bool -> Signed 8 -> (Bool,Bool,Bool)
16+
topEntity :: Vec 4 (Unsigned 4) -> Signed 8 -> (Unsigned 4,Unsigned 4,Unsigned 4)
1717
topEntity xs ix0 =
1818
( xs !! ix0 -- non-constant index
19-
, xs !! ix1 -- constant index, vec is a var
20-
, (tail xs :< False) !! ix1 -- constant index, vec is not a var
19+
, xs !! ix1 -- constant index, vec is a Var
20+
, (tail xs :< 0xe) !! ix1 -- constant index, vec is an expression
2121
)
2222
where
2323
ix1 :: Signed 8
@@ -27,9 +27,9 @@ topEntity xs ix0 =
2727
testBench :: Signal System Bool
2828
testBench = done
2929
where
30-
testVecs = stimuliGenerator clk rst (map unpack $ 0b0010 :> 0b0100 :> 0b1000 :> Nil)
30+
testVecs = stimuliGenerator clk rst (map unpack $ 0x0010 :> 0x0100 :> 0x1000 :> Nil)
3131
testIxs = stimuliGenerator clk rst (2 :> 1 :> 0 :> Nil)
32-
output = map unpack $ 0b101 :> 0b110 :> 0b100 :> Nil
32+
output = map unpack $ 0x101 :> 0x110 :> 0x100 :> Nil
3333
expectedOutput = outputVerifier' clk rst output
3434
done = expectedOutput (topEntity <$> testVecs <*> testIxs)
3535
clk = tbSystemClockGen (not <$> done)

0 commit comments

Comments
 (0)