Skip to content

Commit

Permalink
Small improvements for DFConv and Axi4 related (#45)
Browse files Browse the repository at this point in the history
  • Loading branch information
samalws authored Aug 26, 2022
1 parent 06c581b commit 6026ee9
Show file tree
Hide file tree
Showing 12 changed files with 565 additions and 213 deletions.
4 changes: 3 additions & 1 deletion clash-protocols.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -189,7 +189,8 @@ test-suite unittests
Tests.Protocols
Tests.Protocols.Df
Tests.Protocols.DfConv
Tests.Protocols.AvalonMemMap
Tests.Protocols.Avalon
Tests.Protocols.Axi4
Tests.Protocols.Plugin
Tests.Protocols.Wishbone

Expand All @@ -203,6 +204,7 @@ test-suite unittests
extra,
hashable,
hedgehog,
strict-tuple,
tasty >= 1.2 && < 1.5,
tasty-hedgehog >= 1.2,
tasty-th,
Expand Down
42 changes: 39 additions & 3 deletions src/Protocols/Axi4/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,12 +4,14 @@ Types and utilities shared between AXI4, AXI4-Lite, and AXI3.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} -- NFDataX and ShowX for T3 and T4

module Protocols.Axi4.Common where

-- base
import GHC.Generics (Generic)
import GHC.TypeNats (Nat)
import Control.DeepSeq (NFData)

-- clash-prelude
import qualified Clash.Prelude as C
Expand All @@ -20,6 +22,32 @@ import Data.Tuple.Strict (T3, T4)

import Protocols.Internal

deriving instance
( C.NFDataX a
, C.NFDataX b
, C.NFDataX c
) => C.NFDataX (T3 a b c)

deriving instance
( C.NFDataX a
, C.NFDataX b
, C.NFDataX c
, C.NFDataX d
) => C.NFDataX (T4 a b c d)

deriving instance
( C.ShowX a
, C.ShowX b
, C.ShowX c
) => C.ShowX (T3 a b c)

deriving instance
( C.ShowX a
, C.ShowX b
, C.ShowX c
, C.ShowX d
) => C.ShowX (T4 a b c d)

-- | Enables or disables 'BurstMode'
type BurstType (keep :: Bool) = KeepType keep BurstMode

Expand Down Expand Up @@ -136,7 +164,7 @@ data BurstMode
-- This burst type is used for cache line accesses.
--
| BmWrap
deriving (Show, C.ShowX, Generic, C.NFDataX, Eq)
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | The maximum number of bytes to transfer in each data transfer, or beat,
-- in a burst.
Expand All @@ -149,7 +177,7 @@ data BurstSize
| Bs32
| Bs64
| Bs128
deriving (Show, C.ShowX, Generic, C.NFDataX)
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | Convert burst size to a numeric value
burstSizeToNum :: Num a => BurstSize -> a
Expand All @@ -165,14 +193,17 @@ burstSizeToNum = \case

-- | Whether a transaction is bufferable
data Bufferable = NonBufferable | Bufferable
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | When set to "LookupCache", it is recommended that this transaction is
-- allocated in the cache for performance reasons.
data Allocate = NoLookupCache | LookupCache
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | When set to "OtherLookupCache", it is recommended that this transaction is
-- allocated in the cache for performance reasons.
data OtherAllocate = OtherNoLookupCache | OtherLookupCache
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | See Table A4-3 AWCACHE bit allocations
type Cache = T4 Bufferable Modifiable OtherAllocate Allocate
Expand All @@ -191,29 +222,33 @@ data Resp
-- | Decode error. Generated, typically by an interconnect component, to
-- indicate that there is no slave at the transaction address.
| RDecodeError
deriving (Show, C.ShowX, Generic, C.NFDataX)
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | Whether a resource is accessed with exclusive access or not
data AtomicAccess
= NonExclusiveAccess
| ExclusiveAccess
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | Whether transaction can be modified
data Modifiable
= Modifiable
| NonModifiable
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | An AXI master might support Secure and Non-secure operating states, and
-- extend this concept of security to memory access.
data Secure
= Secure
| NonSecure
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | An AXI master might support more than one level of operating privilege,
-- and extend this concept of privilege to memory access.
data Privileged
= NotPrivileged
| Privileged
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

-- | Whether the transaction is an instruction access or a data access. The AXI
-- protocol defines this indication as a hint. It is not accurate in all cases,
Expand All @@ -224,3 +259,4 @@ data Privileged
data InstructionOrData
= Data
| Instruction
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)
87 changes: 49 additions & 38 deletions src/Protocols/Axi4/ReadAddress.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module Protocols.Axi4.ReadAddress

-- * configuration
, Axi4ReadAddressConfig(..)
, GoodAxi4ReadAddressConfig
, KnownAxi4ReadAddressConfig
, ARKeepBurst
, ARKeepSize
, ARIdWidth
Expand All @@ -37,6 +37,7 @@ module Protocols.Axi4.ReadAddress
) where

-- base
import Control.DeepSeq (NFData)
import Data.Coerce
import Data.Kind (Type)
import GHC.Generics (Generic)
Expand Down Expand Up @@ -187,7 +188,7 @@ newtype S2M_ReadAddress = S2M_ReadAddress
-- | Shorthand for a "well-behaved" read address config,
-- so that we don't need to write out a bunch of type constraints later.
-- Holds for every configuration; don't worry about implementing this class.
class
type KnownAxi4ReadAddressConfig conf =
( KeepTypeClass (ARKeepBurst conf)
, KeepTypeClass (ARKeepSize conf)
, KeepTypeClass (ARKeepRegion conf)
Expand All @@ -200,37 +201,14 @@ class
, C.KnownNat (ARIdWidth conf)
, C.KnownNat (ARAddrWidth conf)

, Show (RegionType (ARKeepRegion conf))
, Show (BurstLengthType (ARKeepBurstLength conf))
, Show (SizeType (ARKeepSize conf))
, Show (BurstType (ARKeepBurst conf))
, Show (LockType (ARKeepLock conf))
, Show (CacheType (ARKeepCache conf))
, Show (PermissionsType (ARKeepPermissions conf))
, Show (QosType (ARKeepQos conf))

, C.NFDataX (RegionType (ARKeepRegion conf))
, C.NFDataX (BurstLengthType (ARKeepBurstLength conf))
, C.NFDataX (SizeType (ARKeepSize conf))
, C.NFDataX (BurstType (ARKeepBurst conf))
, C.NFDataX (LockType (ARKeepLock conf))
, C.NFDataX (CacheType (ARKeepCache conf))
, C.NFDataX (PermissionsType (ARKeepPermissions conf))
, C.NFDataX (QosType (ARKeepQos conf))
) => GoodAxi4ReadAddressConfig conf

instance
( KeepTypeClass (ARKeepBurst conf)
, KeepTypeClass (ARKeepSize conf)
, KeepTypeClass (ARKeepRegion conf)
, KeepTypeClass (ARKeepBurstLength conf)
, KeepTypeClass (ARKeepLock conf)
, KeepTypeClass (ARKeepCache conf)
, KeepTypeClass (ARKeepPermissions conf)
, KeepTypeClass (ARKeepQos conf)

, C.KnownNat (ARIdWidth conf)
, C.KnownNat (ARAddrWidth conf)
, C.ShowX (RegionType (ARKeepRegion conf))
, C.ShowX (BurstLengthType (ARKeepBurstLength conf))
, C.ShowX (SizeType (ARKeepSize conf))
, C.ShowX (BurstType (ARKeepBurst conf))
, C.ShowX (LockType (ARKeepLock conf))
, C.ShowX (CacheType (ARKeepCache conf))
, C.ShowX (PermissionsType (ARKeepPermissions conf))
, C.ShowX (QosType (ARKeepQos conf))

, Show (RegionType (ARKeepRegion conf))
, Show (BurstLengthType (ARKeepBurstLength conf))
Expand All @@ -249,16 +227,34 @@ instance
, C.NFDataX (CacheType (ARKeepCache conf))
, C.NFDataX (PermissionsType (ARKeepPermissions conf))
, C.NFDataX (QosType (ARKeepQos conf))
) => GoodAxi4ReadAddressConfig conf

, NFData (RegionType (ARKeepRegion conf))
, NFData (BurstLengthType (ARKeepBurstLength conf))
, NFData (SizeType (ARKeepSize conf))
, NFData (BurstType (ARKeepBurst conf))
, NFData (LockType (ARKeepLock conf))
, NFData (CacheType (ARKeepCache conf))
, NFData (PermissionsType (ARKeepPermissions conf))
, NFData (QosType (ARKeepQos conf))

, Eq (RegionType (ARKeepRegion conf))
, Eq (BurstLengthType (ARKeepBurstLength conf))
, Eq (SizeType (ARKeepSize conf))
, Eq (BurstType (ARKeepBurst conf))
, Eq (LockType (ARKeepLock conf))
, Eq (CacheType (ARKeepCache conf))
, Eq (PermissionsType (ARKeepPermissions conf))
, Eq (QosType (ARKeepQos conf))
)

deriving instance
( GoodAxi4ReadAddressConfig conf
( KnownAxi4ReadAddressConfig conf
, Show userType
) =>
Show (M2S_ReadAddress conf userType)

deriving instance
( GoodAxi4ReadAddressConfig conf
( KnownAxi4ReadAddressConfig conf
, C.NFDataX userType
) =>
C.NFDataX (M2S_ReadAddress conf userType)
Expand Down Expand Up @@ -307,15 +303,30 @@ data Axi4ReadAddressInfo (conf :: Axi4ReadAddressConfig) (userType :: Type)
deriving (Generic)

deriving instance
( GoodAxi4ReadAddressConfig conf
( KnownAxi4ReadAddressConfig conf
, Show userType ) =>
Show (Axi4ReadAddressInfo conf userType)

deriving instance
( GoodAxi4ReadAddressConfig conf
( KnownAxi4ReadAddressConfig conf
, C.ShowX userType ) =>
C.ShowX (Axi4ReadAddressInfo conf userType)

deriving instance
( KnownAxi4ReadAddressConfig conf
, C.NFDataX userType ) =>
C.NFDataX (Axi4ReadAddressInfo conf userType)

deriving instance
( KnownAxi4ReadAddressConfig conf
, NFData userType ) =>
NFData (Axi4ReadAddressInfo conf userType)

deriving instance
( KnownAxi4ReadAddressConfig conf
, Eq userType ) =>
Eq (Axi4ReadAddressInfo conf userType)

-- | Convert 'M2S_ReadAddress' to 'Axi4ReadAddressInfo', dropping some info
axi4ReadAddrMsgToReadAddrInfo
:: M2S_ReadAddress conf userType
Expand Down
17 changes: 5 additions & 12 deletions src/Protocols/Axi4/ReadData.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ module Protocols.Axi4.ReadData

-- * configuration
, Axi4ReadDataConfig(..)
, GoodAxi4ReadDataConfig
, KnownAxi4ReadDataConfig
, RKeepResponse
, RIdWidth
) where
Expand Down Expand Up @@ -101,29 +101,22 @@ newtype M2S_ReadData = M2S_ReadData { _rready :: Bool }
-- | Shorthand for a "well-behaved" read data config,
-- so that we don't need to write out a bunch of type constraints later.
-- Holds for every configuration; don't worry about implementing this class.
class
type KnownAxi4ReadDataConfig conf =
( KeepTypeClass (RKeepResponse conf)
, C.KnownNat (RIdWidth conf)
, Show (ResponseType (RKeepResponse conf))
, C.NFDataX (ResponseType (RKeepResponse conf))
) => GoodAxi4ReadDataConfig conf

instance
( KeepTypeClass (RKeepResponse conf)
, C.KnownNat (RIdWidth conf)
, Show (ResponseType (RKeepResponse conf))
, C.NFDataX (ResponseType (RKeepResponse conf))
) => GoodAxi4ReadDataConfig conf
)

deriving instance
( GoodAxi4ReadDataConfig conf
( KnownAxi4ReadDataConfig conf
, Show userType
, Show dataType
) =>
Show (S2M_ReadData conf userType dataType)

deriving instance
( GoodAxi4ReadDataConfig conf
( KnownAxi4ReadDataConfig conf
, C.NFDataX userType
, C.NFDataX dataType
) =>
Expand Down
Loading

0 comments on commit 6026ee9

Please sign in to comment.