Skip to content

Commit

Permalink
Use XilinxSystem domain
Browse files Browse the repository at this point in the history
fix output type

tidy up tcl generation &c.
  • Loading branch information
vmchale committed May 10, 2022
1 parent 92c22da commit 7821d91
Show file tree
Hide file tree
Showing 3 changed files with 36 additions and 21 deletions.
33 changes: 24 additions & 9 deletions clash-cores/src/Clash/Cores/Xilinx/DcFifo/BlackBoxes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,9 @@ module Clash.Cores.Xilinx.DcFifo.BlackBoxes where

import Prelude

import Clash.Core.Literal (Literal(NaturalLiteral))
import Clash.Core.TermLiteral (termToDataError, TermLiteralSNat(..))
import Clash.Core.Term (Term(Literal))
import qualified Clash.Primitives.DSL as DSL
import Clash.Netlist.BlackBox.Types (BlackBoxFunction, emptyBlackBoxMeta)
import Clash.Netlist.Types (TemplateFunction(..), BlackBox(BBFunction))
Expand Down Expand Up @@ -47,7 +49,7 @@ import Clash.Cores.Xilinx.Common (toTclBool, renderTcl, defIpConfig, IpConfig (p
dcFifoBBF :: HasCallStack => BlackBoxFunction
dcFifoBBF _isD _primName args _resTys = do
let
[ _knownNatN, _knownDomainWrite, _knownDomainRead, _knownNatDepth
[ knownNatN, _knownDomainWrite, _knownDomainRead, _knownNatDepth
, _constraint1, _constraint2
, either error id . termToDataError -> dcConfig
, _wClk, _rClk, _rst, _wData
Expand All @@ -60,13 +62,18 @@ dcFifoBBF _isD _primName args _resTys = do

dcFifoName <- Id.makeBasic "dcfifo"

pure (Right (bbMeta dcFifoName dcConfig, bb dcFifoName dcConfig))
let depth =
case knownNatN of
Literal (NaturalLiteral n) -> fromInteger n
_ -> error "Unexpected type of knownNatN!"

pure (Right (bbMeta depth dcFifoName dcConfig, bb dcFifoName dcConfig))
where
bbMeta dcFifoName dcConfig = emptyBlackBoxMeta
bbMeta width dcFifoName dcConfig = emptyBlackBoxMeta
{ N.bbKind = N.TDecl
, N.bbIncludes =
[ ( ("dcfifo", "tcl")
, BBFunction (show 'dcFifoTclTF) 0 (dcFifoTclTF dcFifoName dcConfig))
, BBFunction (show 'dcFifoTclTF) 0 (dcFifoTclTF width dcFifoName dcConfig))
]
-- TODO: Make this blackbox return multiple results, instead of a tuple. See:
-- https://github.com/clash-lang/clash-compiler/pull/1560
Expand Down Expand Up @@ -98,6 +105,8 @@ dcFifoTF dcFifoName DcConfig{..} = TemplateFunction [] (const True) $ \bbCtx ->
, wEnable, rEnable
] = map fst (DSL.tInputs bbCtx)

[tResult] = map DSL.ety (DSL.tResults bbCtx)

dcFifoInstName <- Id.makeBasic "dcfifo_inst"

DSL.declarationReturn bbCtx "dcfifo_inst_block" $ do
Expand All @@ -115,6 +124,9 @@ dcFifoTF dcFifoName DcConfig{..} = TemplateFunction [] (const True) $ \bbCtx ->
wEnableBit <- DSL.boolToBit "wr_enable" wEnable
rEnableBit <- DSL.boolToBit "rd_enable" rEnable

wrDataCountUnsigned <- DSL.unsignedFromBitVector wrDataCount
rdDataCountUnsigned <- DSL.unsignedFromBitVector rdDataCount

let
inps =
[ ("rst", rst)
Expand Down Expand Up @@ -146,15 +158,16 @@ dcFifoTF dcFifoName DcConfig{..} = TemplateFunction [] (const True) $ \bbCtx ->

DSL.instDecl N.Entity dcFifoName dcFifoInstName [] inps outs

pure [DSL.tuple
[ wrResetBusy, wrFullBool, wrDataCount
, rdResetBusy, rdEmptyBool, rdDataCount, rdDout
pure [DSL.constructProduct
tResult
[ wrResetBusy, wrFullBool, wrDataCountUnsigned
, rdResetBusy, rdEmptyBool, rdDataCountUnsigned, rdDout
]]

-- | Generate TCL file that calls Xilinx's `create_ip` with the options supplied
-- in the second argument.
dcFifoTclTF :: Identifier -> DcConfig TermLiteralSNat -> TemplateFunction
dcFifoTclTF dcFifoName DcConfig{..} =
dcFifoTclTF :: Int -> Identifier -> DcConfig TermLiteralSNat -> TemplateFunction
dcFifoTclTF width dcFifoName DcConfig{..} =
TemplateFunction [] (const True) (const (pure (renderTcl ipConfig)))
where
ipConfig = (defIpConfig "fifo_generator" "13.2" dcFifoName){properties = props}
Expand All @@ -165,6 +178,8 @@ dcFifoTclTF dcFifoName DcConfig{..} =
, ("Performance_Options", show dcReadMode)
, ("Reset_Type", "Asynchronous_Reset")
, ("Full_Flags_Reset_Value", "1")
, ("Input_Data_Width", show width)
, ("Output_Data_Width", show width)
, ("Write_Data_Count", toTclBool dcWriteDataCount)
, ("Write_Data_Count_Width", show depth)
, ("Read_Data_Count", toTclBool dcReadDataCount)
Expand Down
7 changes: 4 additions & 3 deletions clash-cores/test/Test/Cores/Xilinx/DcFifo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -121,10 +121,11 @@ throughFifo
-> [BitVector 32]
throughFifo wrDataList rdStalls = rdDataList
where
clk = clockGen @System
rst = resetGen @System
ena = enableGen @System
clk = clockGen @XilinxSystem
rst = resetGen @XilinxSystem
ena = enableGen @XilinxSystem
(wrData, wrEna) =
-- The reset to the mealy machine must be the same reset fed to the FIFO
mealyB clk rst ena feedState wrDataList (wrRstBusy, wrFull, wrCnt)
(rdDataMaybe, rdEna) =
mealyB clk rst ena takeState (False, rdStalls) (rdRstBusy, rdEmpty, rdCnt, rdData)
Expand Down
17 changes: 8 additions & 9 deletions clash-lib/src/Clash/Primitives/DSL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ instantiations.

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE QuasiQuotes #-}
Expand Down Expand Up @@ -434,16 +435,14 @@ boolFromBitVector n =

-- | Used to create an output `Unsigned` from a `BitVector` of given
-- size. Works in a similar way to `boolFromBit` above.
--
-- TODO: Implement for (System)Verilog
unsignedFromBitVector
:: Size
-> Text
-- ^ Name hint for intermediate signal
-> TExpr
-> State (BlockState VHDLState) TExpr
unsignedFromBitVector n =
outputCoerce (BitVector n) (Unsigned n) (\i -> "unsigned(" <> i <> ")")
:: Backend backend
=> TExpr
-> State (BlockState backend) TExpr
unsignedFromBitVector TExpr { ety, eex } =
case ety of
BitVector n -> pure $ TExpr { ety = Unsigned n, eex = FromBv Nothing (Unsigned n) eex }
tExpr -> error $ "unsignedFromBitVector: Got \"" <> show tExpr <> "\" expected BitVector"

-- | Used to create an output `Bool` from a number of `Bit`s, using
-- conjunction. Similarly to `untuple`, it returns a list of
Expand Down

0 comments on commit 7821d91

Please sign in to comment.