Skip to content

Commit

Permalink
Merge pull request #75 from clash-lang/reset-sanity
Browse files Browse the repository at this point in the history
Add `forceResetSanity` for all protocols
  • Loading branch information
lmbollen authored May 29, 2024
2 parents 517793c + 45b8aec commit fad7495
Show file tree
Hide file tree
Showing 9 changed files with 89 additions and 11 deletions.
8 changes: 8 additions & 0 deletions src/Protocols/Avalon/MemMap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ module Protocols.Avalon.MemMap
, subordinateOutRemoveNonDf
, subordinateInAddNonDf
, subordinateInRemoveNonDf
, forceResetSanity

-- * Protocols
, AvalonMmManager(..)
Expand Down Expand Up @@ -1272,3 +1273,10 @@ instance (KnownSubordinateConfig config) =>
IdleCircuit (AvalonMmSubordinate dom fixedWaitTime config) where
idleFwd _ = pure mmSubordinateInNoData
idleBwd _ = pure $ boolToMmSubordinateAck False

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity ::
(KnownDomain dom, HiddenReset dom, KnownManagerConfig config) =>
Circuit (AvalonMmManager dom config) (AvalonMmManager dom config)
forceResetSanity = forceResetSanityGeneric
7 changes: 7 additions & 0 deletions src/Protocols/Avalon/Stream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -237,3 +237,10 @@ instance IdleCircuit (AvalonStream dom conf dataType) where
idleFwd _ = pure Nothing
idleBwd _ = pure AvalonStreamS2M { _ready = False }

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity ::
forall dom conf dataType.
( C.HiddenClockResetEnable dom) =>
Circuit (AvalonStream dom conf dataType) (AvalonStream dom conf dataType)
forceResetSanity = forceResetSanityGeneric
11 changes: 11 additions & 0 deletions src/Protocols/Axi4/ReadAddress.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ module Protocols.Axi4.ReadAddress
, Axi4ReadAddressInfo(..)
, axi4ReadAddrMsgToReadAddrInfo
, axi4ReadAddrMsgFromReadAddrInfo

-- * helpers
, forceResetSanity
) where

-- base
Expand Down Expand Up @@ -368,3 +371,11 @@ axi4ReadAddrMsgFromReadAddrInfo Axi4ReadAddressInfo{..}
instance IdleCircuit (Axi4ReadAddress dom conf userType) where
idleFwd _ = pure M2S_NoReadAddress
idleBwd _ = pure S2M_ReadAddress { _arready = False }

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity ::
forall dom conf userType.
( C.HiddenClockResetEnable dom) =>
Circuit (Axi4ReadAddress dom conf userType) (Axi4ReadAddress dom conf userType)
forceResetSanity = forceResetSanityGeneric
11 changes: 11 additions & 0 deletions src/Protocols/Axi4/ReadData.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,9 @@ module Protocols.Axi4.ReadData
, KnownAxi4ReadDataConfig
, RKeepResponse
, RIdWidth

-- * helpers
, forceResetSanity
) where

-- base
Expand Down Expand Up @@ -126,3 +129,11 @@ deriving instance
instance IdleCircuit (Axi4ReadData dom conf userType dataType) where
idleFwd _ = C.pure S2M_NoReadData
idleBwd _ = C.pure $ M2S_ReadData False

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity ::
forall dom conf userType dataType.
( C.HiddenClockResetEnable dom) =>
Circuit (Axi4ReadData dom conf userType dataType) (Axi4ReadData dom conf userType dataType)
forceResetSanity = forceResetSanityGeneric
7 changes: 7 additions & 0 deletions src/Protocols/Axi4/Stream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -177,3 +177,10 @@ instance
instance IdleCircuit (Axi4Stream dom conf userType) where
idleFwd Proxy = C.pure Nothing
idleBwd Proxy = C.pure $ Axi4StreamS2M False

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity ::
(KnownDomain dom, HiddenReset dom) =>
Circuit (Axi4Stream dom conf userType) (Axi4Stream dom conf userType)
forceResetSanity = forceResetSanityGeneric
8 changes: 8 additions & 0 deletions src/Protocols/Axi4/WriteAddress.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ module Protocols.Axi4.WriteAddress
, Axi4WriteAddressInfo(..)
, axi4WriteAddrMsgToWriteAddrInfo
, axi4WriteAddrMsgFromWriteAddrInfo
, forceResetSanity
) where

-- base
Expand Down Expand Up @@ -361,3 +362,10 @@ axi4WriteAddrMsgFromWriteAddrInfo _awlen _awburst Axi4WriteAddressInfo{..}
instance IdleCircuit (Axi4WriteAddress dom conf userType) where
idleFwd _ = C.pure M2S_NoWriteAddress
idleBwd _ = C.pure $ S2M_WriteAddress False

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity ::
(C.KnownDomain dom, C.HiddenReset dom) =>
Circuit (Axi4WriteAddress dom conf userType) (Axi4WriteAddress dom conf userType)
forceResetSanity = forceResetSanityGeneric
14 changes: 3 additions & 11 deletions src/Protocols/Df.hs
Original file line number Diff line number Diff line change
Expand Up @@ -209,17 +209,9 @@ instance (C.KnownDomain dom, C.NFDataX a, C.ShowX a, Show a) => Drivable (Df dom

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity :: forall dom a. C.HiddenClockResetEnable dom => Circuit (Df dom a) (Df dom a)
forceResetSanity
= Circuit (\(fwd, bwd) -> C.unbundle . fmap f . C.bundle $ (rstLow, fwd, bwd))
where
f (True, _, _ ) = (Ack False, NoData)
f (False, fwd, bwd) = (bwd, fwd)
#if MIN_VERSION_clash_prelude(1,8,0)
rstLow = C.unsafeToActiveHigh C.hasReset
#else
rstLow = C.unsafeToHighPolarity C.hasReset
#endif
forceResetSanity :: forall dom a. C.HiddenClockResetEnable dom =>
Circuit (Df dom a) (Df dom a)
forceResetSanity = forceResetSanityGeneric

-- | Coerce the payload of a Df stream.
coerce :: (Coerce.Coercible a b) => Circuit (Df dom a) (Df dom b)
Expand Down
23 changes: 23 additions & 0 deletions src/Protocols/Internal/Classes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module Protocols.Internal.Classes where

import Data.Kind (Type)
import Data.Proxy
import Clash.Signal

-- | A protocol describes the in- and outputs of one side of a 'Circuit'.
class Protocol a where
Expand Down Expand Up @@ -140,3 +141,25 @@ class (Protocol p) => IdleCircuit p where
idleFwd :: Proxy p -> Fwd (p :: Type)
idleBwd :: Proxy p -> Bwd (p :: Type)

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanityGeneric ::
forall dom a fwd bwd.
( KnownDomain dom
, HiddenReset dom
, IdleCircuit a
, Fwd a ~ Signal dom fwd
, Bwd a ~ Signal dom bwd
) => Circuit a a
forceResetSanityGeneric = Circuit go
where
go (fwd, bwd) = unbundle $
mux rstAsserted
(bundle (idleBwd $ Proxy @a, idleFwd $ Proxy @a))
(bundle (bwd, fwd))

#if MIN_VERSION_clash_prelude(1,8,0)
rstAsserted = unsafeToActiveHigh hasReset
#else
rstAsserted = unsafeToHighPolarity hasReset
#endif
11 changes: 11 additions & 0 deletions src/Protocols/Wishbone.hs
Original file line number Diff line number Diff line change
Expand Up @@ -245,3 +245,14 @@ emptyWishboneS2M =
-- | Helper function to determine whether a Slave signals the termination of a cycle.
hasTerminateFlag :: WishboneS2M dat -> Bool
hasTerminateFlag s2m = acknowledge s2m || err s2m || retry s2m

-- | Force a /nack/ on the backward channel and /no data/ on the forward
-- channel if reset is asserted.
forceResetSanity ::
forall dom mode aw a .
( C.HiddenClockResetEnable dom
, C.KnownNat aw
, C.KnownNat (C.BitSize a)
, C.NFDataX a) =>
Circuit (Wishbone dom mode aw a) (Wishbone dom mode aw a)
forceResetSanity = forceResetSanityGeneric

0 comments on commit fad7495

Please sign in to comment.