Skip to content

Commit

Permalink
add file for dcfifo
Browse files Browse the repository at this point in the history
  • Loading branch information
vmchale committed May 11, 2022
1 parent efa8695 commit 6d50a4a
Show file tree
Hide file tree
Showing 3 changed files with 64 additions and 11 deletions.
23 changes: 12 additions & 11 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -428,17 +428,18 @@ runClashTest = defaultMain $ clashTestRoot
-- The Cores.Xilinx.Floating tests require Vivado (and take much time to
-- run).
--
-- , clashTestGroup "Cores"
-- [ clashTestGroup "Xilinx"
-- [ runTest "Floating" def{ clashFlags=["-fclash-float-support"]
-- , buildTargets=[ "addBasicTB"
-- , "addEnableTB"
-- , "addShortPLTB"
-- , "subBasicTB"
-- , "mulBasicTB"
-- , "divBasicTB"]}
-- ]
-- ]
, clashTestGroup "Cores"
[ clashTestGroup "Xilinx"
-- [ runTest "Floating" def{ clashFlags=["-fclash-float-support"]
-- , buildTargets=[ "addBasicTB"
-- , "addEnableTB"
-- , "addShortPLTB"
-- , "subBasicTB"
-- , "mulBasicTB"
-- , "divBasicTB"]}
[ runTest "DcFifoTop" def
]
]
, clashTestGroup "CSignal"
[ runTest "MAC" def{hdlSim=False}
, runTest "CBlockRamTest" def{hdlSim=False}
Expand Down
32 changes: 32 additions & 0 deletions tests/shouldwork/Cores/Xilinx/DcFifo.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
module DcFifo where

import Clash.Explicit.Prelude
import Clash.Explicit.Testbench

import Data.Word (Word32)

import Clash.Cores.Xilinx.DcFifo.Explicit

createDomain vSystem{vName="P30", vPeriod=30000}
createDomain vSystem{vName="P50", vPeriod=50000}

tbOutput
:: Clock P50
-> Clock P30
-> Signal P30 (BitVector 32)
tbOutput wClk rClk = ignoreFor rClk resetGen enableGen d2 0 fifoOut
where
(XilinxFifo _ _ _ rdRstBusy isEmpty _ fifoOut) = dcFifo @4 defConfig wClk rClk resetGen inpSignal wrEna rdEna
inpSignal = pure (pack (0xFFFF :: Word32))
wrEna = pure True
rdEna = pure True

tb
:: (KnownNat n, 1 <= n)
=> Vec n (BitVector 32)
-> Signal P30 Bool
tb expected = done
where
output = tbOutput wClk rClk
(rClk, wClk) = (clockGen, clockGen) -- biTbClockGen (not <$> done) :: (Clock P30, Clock P50)
done = outputVerifier' rClk resetGen expected output
20 changes: 20 additions & 0 deletions tests/shouldwork/Cores/Xilinx/DcFifoTop.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module DcFifoTop where

import Clash.Explicit.Prelude

import Clash.Cores.Xilinx.DcFifo.Explicit

import DcFifo

topEntity
:: Clock P50
-> Clock P30
-> Signal P50 (BitVector 32)
-> Signal P50 Bool
-> Signal P30 Bool
-> XilinxFifo P30 P50 7 32
topEntity wClk rdClk = dcFifo defConfig wClk rdClk resetGen
{-# NOINLINE topEntity #-}

testBench :: Signal P30 Bool
testBench = tb $(listToVecTH $ sampleN 20 $ tbOutput clockGen clockGen)

0 comments on commit 6d50a4a

Please sign in to comment.