Skip to content

Commit

Permalink
Add sctrict AXI
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Jan 5, 2021
1 parent 9919236 commit ea5c5aa
Show file tree
Hide file tree
Showing 15 changed files with 830 additions and 29 deletions.
26 changes: 17 additions & 9 deletions clash-protocols.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -124,12 +124,13 @@ library
build-depends:
-- inline-circuit-notation
circuit-notation
, extra
, data-default
, deepseq
, hedgehog >= 1.0.2
, extra
, ghc >= 8.6
, hedgehog >= 1.0.2
, pretty-show
, strict-tuple

-- To be removed; we need 'Test.Tasty.Hedgehog.Extra' to fix upstream issues
, tasty >= 1.2 && < 1.5
Expand All @@ -138,13 +139,20 @@ library
exposed-modules:
Protocols

Protocols.Axi4.Raw.Common
Protocols.Axi4.Raw.Full
Protocols.Axi4.Raw.Full.ReadAddress
Protocols.Axi4.Raw.Full.ReadData
Protocols.Axi4.Raw.Full.WriteAddress
Protocols.Axi4.Raw.Full.WriteData
Protocols.Axi4.Raw.Full.WriteResponse
Protocols.Axi4.Common

Protocols.Axi4.Partial.Full
Protocols.Axi4.Partial.Full.ReadAddress
Protocols.Axi4.Partial.Full.ReadData
Protocols.Axi4.Partial.Full.WriteAddress
Protocols.Axi4.Partial.Full.WriteData
Protocols.Axi4.Partial.Full.WriteResponse

Protocols.Axi4.Strict.Full.ReadAddress
Protocols.Axi4.Strict.Full.ReadData
Protocols.Axi4.Strict.Full.WriteAddress
Protocols.Axi4.Strict.Full.WriteData
Protocols.Axi4.Strict.Full.WriteResponse

Protocols.Df
Protocols.DfLike
Expand Down
16 changes: 12 additions & 4 deletions src/Protocols/Axi4/Raw/Common.hs → src/Protocols/Axi4/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ Types and utilities shared between AXI4, AXI4-Lite, and AXI3.
-}
{-# LANGUAGE UndecidableInstances #-}

module Protocols.Axi4.Raw.Common where
module Protocols.Axi4.Common where

-- base
import Data.Kind (Type)
Expand All @@ -12,7 +12,10 @@ import GHC.TypeNats (Nat)

-- clash-prelude
import qualified Clash.Prelude as C
import Clash.Prelude (type (^), type (-))
import Clash.Prelude (type (^), type (-), type (*))

-- strict-tuple
import Data.Tuple.Strict

-- | Simple wrapper to achieve "named arguments" when instantiating an AXI protocol
data IdWidth = IdWidth Nat deriving (Show)
Expand Down Expand Up @@ -93,7 +96,7 @@ type family LockType (keepLockType :: KeepLock) where

-- | Enables or disables 'Privileged', 'Secure', and 'InstructionOrData'
type family PermissionsType (keepPermissions :: KeepPermissions) where
PermissionsType 'KeepPermissions = (Privileged, Secure, InstructionOrData)
PermissionsType 'KeepPermissions = T3 Privileged Secure InstructionOrData
PermissionsType 'NoPermissions = ()

-- | Enables or disables 'Qos'
Expand Down Expand Up @@ -121,6 +124,11 @@ type family StrobeType (byteSize :: Nat) (keepStrobe :: KeepStrobe) where
StrobeType byteSize 'KeepStrobe = Strobe byteSize
StrobeType byteSize 'NoStrobe = ()

-- | Enable or disable 'Strobe'
type family StrictStrobeType (byteSize :: Nat) (keepStrobe :: KeepStrobe) where
StrictStrobeType byteSize 'KeepStrobe = C.Vec byteSize (C.BitVector 8)
StrictStrobeType byteSize 'NoStrobe = C.BitVector (byteSize * 8)

-- | Indicates valid bytes on data field.
type Strobe (byteSize :: Nat) = C.BitVector byteSize

Expand Down Expand Up @@ -213,7 +221,7 @@ data Allocate = NoLookupCache | LookupCache
data OtherAllocate = OtherNoLookupCache | OtherLookupCache

-- | See Table A4-3 AWCACHE bit allocations
type Cache = (Bufferable, Modifiable, OtherAllocate, Allocate)
type Cache = T4 Bufferable Modifiable OtherAllocate Allocate

-- | Status of the write transaction.
data Resp
Expand Down
Empty file removed src/Protocols/Axi4/Full.hs
Empty file.
Original file line number Diff line number Diff line change
Expand Up @@ -10,16 +10,16 @@ is not.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}

module Protocols.Axi4.Raw.Full
module Protocols.Axi4.Partial.Full
( module ReadAddress
, module ReadData
, module WriteAddress
, module WriteData
, module WriteResponse
) where

import Protocols.Axi4.Raw.Full.ReadAddress as ReadAddress
import Protocols.Axi4.Raw.Full.ReadData as ReadData
import Protocols.Axi4.Raw.Full.WriteAddress as WriteAddress
import Protocols.Axi4.Raw.Full.WriteData as WriteData
import Protocols.Axi4.Raw.Full.WriteResponse as WriteResponse
import Protocols.Axi4.Partial.Full.ReadAddress as ReadAddress
import Protocols.Axi4.Partial.Full.ReadData as ReadData
import Protocols.Axi4.Partial.Full.WriteAddress as WriteAddress
import Protocols.Axi4.Partial.Full.WriteData as WriteData
import Protocols.Axi4.Partial.Full.WriteResponse as WriteResponse
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ to the AXI4 specification.

{-# OPTIONS_GHC -Wno-missing-fields #-}

module Protocols.Axi4.Raw.Full.ReadAddress
module Protocols.Axi4.Partial.Full.ReadAddress
( M2S_ReadAddress(..)
, S2M_ReadAddress(..)
, Axi4ReadAddress
Expand All @@ -27,7 +27,7 @@ import qualified Clash.Prelude as C
import Clash.Prelude ((:::))

-- me
import Protocols.Axi4.Raw.Common
import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ to the AXI4 specification.

{-# OPTIONS_GHC -Wno-missing-fields #-}

module Protocols.Axi4.Raw.Full.ReadData
module Protocols.Axi4.Partial.Full.ReadData
( M2S_ReadData(..)
, S2M_ReadData(..)
, Axi4ReadData
Expand All @@ -27,7 +27,7 @@ import qualified Clash.Prelude as C
import Clash.Prelude ((:::))

-- me
import Protocols.Axi4.Raw.Common
import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ to the AXI4 specification.

{-# OPTIONS_GHC -Wno-missing-fields #-}

module Protocols.Axi4.Raw.Full.WriteAddress
module Protocols.Axi4.Partial.Full.WriteAddress
( M2S_WriteAddress(..)
, S2M_WriteAddress(..)
, Axi4WriteAddress
Expand All @@ -27,7 +27,7 @@ import qualified Clash.Prelude as C
import Clash.Prelude ((:::))

-- me
import Protocols.Axi4.Raw.Common
import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ to the AXI4 specification.

{-# OPTIONS_GHC -Wno-missing-fields #-}

module Protocols.Axi4.Raw.Full.WriteData
module Protocols.Axi4.Partial.Full.WriteData
( M2S_WriteData(..)
, S2M_WriteData(..)
, Axi4WriteData
Expand All @@ -28,7 +28,7 @@ import qualified Clash.Prelude as C
import Clash.Prelude ((:::), type (*))

-- me
import Protocols.Axi4.Raw.Common
import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ to the AXI4 specification.

{-# OPTIONS_GHC -Wno-missing-fields #-}

module Protocols.Axi4.Raw.Full.WriteResponse
module Protocols.Axi4.Partial.Full.WriteResponse
( M2S_WriteResponse(..)
, S2M_WriteResponse(..)
, Axi4WriteResponse
Expand All @@ -27,7 +27,7 @@ import qualified Clash.Prelude as C
import Clash.Prelude ((:::))

-- me
import Protocols.Axi4.Raw.Common
import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
Expand Down
23 changes: 23 additions & 0 deletions src/Protocols/Axi4/Strict/Full.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
{-|
Defines the full AXI4 protocol with port names corresponding to the AXI4
specification.
Note that every individual channel is a DfLike-protocol, but the bundled version
is not.
-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}

module Protocols.Axi4.Strict.Full
( module ReadAddress
, module ReadData
, module WriteAddress
, module WriteData
, module WriteResponse
) where

import Protocols.Axi4.Strict.Full.ReadAddress as ReadAddress
import Protocols.Axi4.Strict.Full.ReadData as ReadData
import Protocols.Axi4.Strict.Full.WriteAddress as WriteAddress
import Protocols.Axi4.Strict.Full.WriteData as WriteData
import Protocols.Axi4.Strict.Full.WriteResponse as WriteResponse
Loading

0 comments on commit ea5c5aa

Please sign in to comment.