Skip to content

Commit

Permalink
Add Simulate instance for AXI4Lite
Browse files Browse the repository at this point in the history
  • Loading branch information
PietPtr committed Mar 7, 2022
1 parent 6eaaa8e commit d8e80f9
Show file tree
Hide file tree
Showing 3 changed files with 64 additions and 28 deletions.
67 changes: 64 additions & 3 deletions src/Protocols/Axi4/Lite/Axi4Lite.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RecordWildCards #-}
{-|
Defines datatypes for all five channels of the AXI4 Lite protocol. For more
information on AXI4 Lite, see chapter B of the AMBA AXI specification.
Expand All @@ -9,13 +10,16 @@ information on AXI4 Lite, see chapter B of the AMBA AXI specification.
module Protocols.Axi4.Lite.Axi4Lite where

import Protocols
import Protocols.Internal
import Protocols.Axi4.Common
import Clash.Prelude as C
import qualified Prelude as P
import qualified Clash.Explicit.Prelude as CE

import Control.DeepSeq

-- | AXI4 Lite busses are always either 32 bit or 64 bit.
data BusWidth = Width32 | Width64 deriving (Show, Eq)
data BusWidth = Width32 | Width64 deriving (Show, Eq, Generic, NFDataX)

type instance Width 'Width32 = 32
type instance Width 'Width64 = 64
Expand All @@ -32,7 +36,6 @@ type family ReadBusWidthType (bw :: BusWidth) where
ReadBusWidthType 'Width32 = C.Vec 4 (C.BitVector 8)
ReadBusWidthType 'Width64 = C.Vec 8 (C.BitVector 8)


---------------------------
--- Write address types ---
---------------------------
Expand Down Expand Up @@ -130,6 +133,8 @@ data M2S_ReadAddress
_arprot :: PermissionsType 'KeepPermissions
} deriving (Generic)

deriving instance (KnownNat (Width aw)) => NFDataX (M2S_ReadAddress aw)

deriving instance
(C.KnownNat (Width aw))
=> Show (M2S_ReadAddress aw)
Expand All @@ -138,7 +143,7 @@ deriving instance
data S2M_ReadAddress
= S2M_ReadAddress {
_arready :: Bool
} deriving (Show, Generic)
} deriving (Show, Generic, NFDataX)


-----------------------
Expand Down Expand Up @@ -180,6 +185,11 @@ data M2S_Axi4Lite
m2s_ra :: M2S_ReadAddress aw,
m2s_rd :: M2S_ReadData bw
}
deriving (Generic)

deriving instance
(NFDataX (ReadBusWidthType bw), NFDataX (WriteBusWidthType bw), KnownNat (Width aw))
=> NFDataX (M2S_Axi4Lite aw bw)

deriving instance
( Show (ReadBusWidthType bw)
Expand All @@ -199,6 +209,10 @@ data S2M_Axi4Lite
s2m_ra :: S2M_ReadAddress,
s2m_rd :: S2M_ReadData bw
}
deriving (Generic)

-- this breaks when e.g. fromList is used on an unconstrained value :: S2MAxi4Lite aw bw.
deriving instance (NFDataX (ReadBusWidthType bw)) => NFDataX (S2M_Axi4Lite aw bw)

deriving instance
( Show (ReadBusWidthType bw)
Expand All @@ -219,3 +233,50 @@ instance Protocol (Axi4Lite dom aw bw) where
type Fwd (Axi4Lite dom aw bw) = C.Signal dom (M2S_Axi4Lite aw bw)
type Bwd (Axi4Lite dom aw bw) = C.Signal dom (S2M_Axi4Lite aw bw)


instance Backpressure (Axi4Lite dom aw bw) where
boolsToBwd = error "Cannot construct arbitrary S2M AXI type from boolean."

instance Simulate (Axi4Lite dom aw bw) where
type SimulateFwdType (Axi4Lite dom aw bw) = [M2S_Axi4Lite aw bw]
type SimulateBwdType (Axi4Lite dom aw bw) = [S2M_Axi4Lite aw bw]
type SimulateChannels (Axi4Lite dom aw bw) = 1

simulateRight :: SimulationConfig
-> [S2M_Axi4Lite aw bw]
-> Circuit () (Axi4Lite dom aw bw)
-> [M2S_Axi4Lite aw bw]
simulateRight SimulationConfig{..} bwds circ =
P.take timeoutAfter $
CE.sample_lazy $
P.snd $
toSignals circ ((), resetAndBwds)
where
resetAndBwds = C.fromList_lazy $ P.replicate resetCycles idleS2MChannels <> bwds
idleS2MChannels = S2M_Axi4Lite {
s2m_wa = S2M_WriteAddress False,
s2m_wd = S2M_WriteData False,
s2m_wr = S2M_NoWriteResponse,
s2m_ra = S2M_ReadAddress False,
s2m_rd = S2M_NoReadData
}

simulateLeft :: SimulationConfig
-> [M2S_Axi4Lite aw bw]
-> Circuit (Axi4Lite dom aw bw) ()
-> [S2M_Axi4Lite aw bw]
simulateLeft SimulationConfig{..} fwds circ =
P.take timeoutAfter $
CE.sample_lazy $
P.fst $
toSignals circ (resetAndFwds, ())
where
resetAndFwds = C.fromList_lazy $ P.replicate resetCycles idleM2SChannels <> fwds
idleM2SChannels = M2S_Axi4Lite {
m2s_wa = M2S_NoWriteAddress,
m2s_wd = M2S_NoWriteData,
m2s_wr = M2S_WriteResponse False,
m2s_ra = M2S_NoReadAddress,
m2s_rd = M2S_ReadData False
}

22 changes: 0 additions & 22 deletions src/Protocols/Df.hs
Original file line number Diff line number Diff line change
Expand Up @@ -177,28 +177,6 @@ instance (C.KnownDomain dom, C.NFDataX a, C.ShowX a, Show a) => Simulate (Df dom



simulateManager SimulationConfig{..} acks circ =
P.take timeoutAfter $
CE.sample_lazy $
P.snd $
toSignals circ ((), resetAndAcks)
where
resetAndAcks = C.fromList $ (P.map Ack (replicate resetCycles False) <> acks)

-- TODO: apply simulation config
simulateSubordinate SimulationConfig{..} fwds circ = CE.sample_lazy ackSig
where
(ackSig, ()) = toSignals circ (dataSig, ())
dataSig = C.fromList_lazy (ackedData resetCycles fwds (C.sample ackSig))

ackedData resetN _ (_:acks) | resetN > 0 =
NoData : ackedData (resetN - 1) fwds acks
ackedData _ [] (_:acks) = NoData : ackedData 0 [] acks
ackedData _ (dat:datas) (ack:acks) = case ack of
Ack True -> dat : ackedData 0 (datas) acks
Ack False -> dat : ackedData 0 (dat:datas) acks



instance DfLike dom (Df dom) a where
type Data (Df dom) a = Data a
Expand Down
3 changes: 0 additions & 3 deletions src/Protocols/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -491,9 +491,6 @@ instance Simulate () where
simulateRight _ _ _ = ()
simulateLeft _ _ _ = ()

simulateManager _ _ _ = ()
simulateSubordinate _ _ _ = ()


instance (Simulate a, Simulate b) => Simulate (a, b) where
type SimulateType (a, b) = (SimulateType a, SimulateType b)
Expand Down

0 comments on commit d8e80f9

Please sign in to comment.