Skip to content

Commit

Permalink
Add AXI conversion functions
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Jan 5, 2021
1 parent de46d3a commit da0c3c6
Show file tree
Hide file tree
Showing 8 changed files with 308 additions and 9 deletions.
10 changes: 8 additions & 2 deletions src/Protocols/Axi4/Common.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-|
Types and utilities shared between AXI4, AXI4-Lite, and AXI3.
-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE UndecidableInstances #-}

module Protocols.Axi4.Common where
Expand All @@ -15,7 +16,7 @@ import qualified Clash.Prelude as C
import Clash.Prelude (type (^), type (-), type (*))

-- strict-tuple
import Data.Tuple.Strict
import Data.Tuple.Strict (T3, T4)

-- | Simple wrapper to achieve "named arguments" when instantiating an AXI protocol
data IdWidth = IdWidth Nat deriving (Show)
Expand Down Expand Up @@ -63,6 +64,11 @@ data KeepSize = KeepSize | NoSize deriving (Show)
-- | Keep or remove strobe field. See 'Strobe'
data KeepStrobe = KeepStrobe | NoStrobe deriving (Show)

-- | Type used to introduce strobe information on the term level
data SKeepStrobe (strobeType :: KeepStrobe) where
SKeepStrobe :: SKeepStrobe 'KeepStrobe
SNoStrobe :: SKeepStrobe 'NoStrobe

-- | Extracts Nat from 'IdWidth', 'AddrWidth', and 'LengthWidth'
type family Width (a :: k) :: Nat where
Width ('IdWidth n) = n
Expand Down Expand Up @@ -126,7 +132,7 @@ type family StrobeType (byteSize :: Nat) (keepStrobe :: KeepStrobe) where

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

-- | Indicates valid bytes on data field.
Expand Down
15 changes: 10 additions & 5 deletions src/Protocols/Axi4/Partial/Full.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,13 @@ module Protocols.Axi4.Partial.Full
, module WriteResponse
) where

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
import Protocols.Axi4.Partial.Full.ReadAddress
as ReadAddress hiding (toStrict, toStrictDf, fromStrict, fromStrictDf)
import Protocols.Axi4.Partial.Full.ReadData
as ReadData hiding (toStrict, toStrictDf, fromStrict, fromStrictDf)
import Protocols.Axi4.Partial.Full.WriteAddress
as WriteAddress hiding (toStrict, toStrictDf, fromStrict, fromStrictDf)
import Protocols.Axi4.Partial.Full.WriteData
as WriteData hiding (toStrict, toStrictDf, fromStrict, fromStrictDf)
import Protocols.Axi4.Partial.Full.WriteResponse
as WriteResponse hiding (toStrict, toStrictDf, fromStrict, fromStrictDf)
52 changes: 52 additions & 0 deletions src/Protocols/Axi4/Partial/Full/ReadAddress.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ to the AXI4 specification.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-missing-fields #-}
Expand All @@ -14,6 +15,8 @@ module Protocols.Axi4.Partial.Full.ReadAddress
( M2S_ReadAddress(..)
, S2M_ReadAddress(..)
, Axi4ReadAddress
, toStrict, toStrictDf
, fromStrict, fromStrictDf
) where

-- base
Expand All @@ -31,6 +34,9 @@ import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
import qualified Protocols.Axi4.Strict.Full.ReadAddress as Strict
import qualified Protocols.Df as Df
import Protocols.Df (Df)

-- | AXI4 Read Address channel protocol
data Axi4ReadAddress
Expand Down Expand Up @@ -187,3 +193,49 @@ deriving instance
, C.NFDataX (PermissionsType kp)
, C.NFDataX (QosType kq) ) =>
C.NFDataX (M2S_ReadAddress kb ksz lw iw aw kr kbl kl kc kp kq userType)

-- | Convert an 'Axi4ReadAddress' into its strict version
-- 'Strict.Axi4ReadAddress'. The latter is usually preferred in Clash designs
-- as its definitions don't contain partial fields. Note that the functions
-- defined over these circuits operate on @userType@. If you need functions to
-- map over all fields, consider using 'toStrictDf'.
toStrict ::
Circuit
(Axi4ReadAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
(Strict.Axi4ReadAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
toStrict = Circuit (C.unbundle . fmap go . C.bundle)
where
go (M2S_ReadAddress{..}, ack)
| _arvalid = (coerce ack, Strict.M2S_ReadAddress{..})
| otherwise = (coerce ack, Strict.M2S_NoReadAddress)

-- | Convert a 'Strict.Axi4ReadAddress' into 'Axi4ReadAddress'
fromStrict ::
Circuit
(Strict.Axi4ReadAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
(Axi4ReadAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
fromStrict = Circuit (C.unbundle . fmap go . C.bundle)
where
go (Strict.M2S_ReadAddress{..}, ack) = (coerce ack, M2S_ReadAddress{_arvalid=True,..})
go (Strict.M2S_NoReadAddress, ack) = (coerce ack, M2S_ReadAddress{_arvalid=False})

-- | Convert an 'Axi4ReadAddress' into its strict 'Df' equivalent.
toStrictDf ::
Circuit
(Axi4ReadAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
(Df dom (Strict.M2S_ReadAddress kb ksz lw iw aw kr kbl kl kc kp kq userType))
toStrictDf = Circuit (C.unbundle . fmap go . C.bundle)
where
go (M2S_ReadAddress{..}, ack)
| _arvalid = (coerce ack, Df.Data (Strict.M2S_ReadAddress{..}))
| otherwise = (coerce ack, Df.NoData)

-- | Convert a into 'Axi4ReadAddress' from its Df equivalent
fromStrictDf ::
Circuit
(Df dom (Strict.M2S_ReadAddress kb ksz lw iw aw kr kbl kl kc kp kq userType))
(Axi4ReadAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
fromStrictDf = Circuit (C.unbundle . fmap go . C.bundle)
where
go (Df.Data (Strict.M2S_ReadAddress{..}), ack) = (coerce ack, M2S_ReadAddress{_arvalid=True,..})
go (_, ack) = (coerce ack, M2S_ReadAddress{_arvalid=False})
52 changes: 52 additions & 0 deletions src/Protocols/Axi4/Partial/Full/ReadData.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ to the AXI4 specification.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-missing-fields #-}
Expand All @@ -14,6 +15,8 @@ module Protocols.Axi4.Partial.Full.ReadData
( M2S_ReadData(..)
, S2M_ReadData(..)
, Axi4ReadData
, toStrict, toStrictDf
, fromStrict, fromStrictDf
) where

-- base
Expand All @@ -31,6 +34,9 @@ import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
import qualified Protocols.Axi4.Strict.Full.ReadData as Strict
import qualified Protocols.Df as Df
import Protocols.Df (Df)

-- | AXI4 Read Data channel protocol
data Axi4ReadData
Expand Down Expand Up @@ -138,3 +144,49 @@ deriving instance
, Show dataType
, Show (ResponseType kr) ) =>
Show (S2M_ReadData kr iw dataType userType)

-- | Convert an 'Axi4ReadData' into its strict version
-- 'Strict.Axi4ReadData'. The latter is usually preferred in Clash designs
-- as its definitions don't contain partial fields. Note that the functions
-- defined over these circuits operate on @userType@. If you need functions to
-- map over all fields, consider using 'toStrictDf'.
toStrict ::
Circuit
(Axi4ReadData dom kr iw dataType userType)
(Strict.Axi4ReadData dom kr iw dataType userType)
toStrict = Circuit (C.unbundle . fmap go . C.bundle)
where
go (S2M_ReadData{..}, ack)
| _rvalid = (coerce ack, Strict.S2M_ReadData{..})
| otherwise = (coerce ack, Strict.S2M_NoReadData)

-- | Convert a 'Strict.Axi4ReadData' into 'Axi4ReadData'
fromStrict ::
Circuit
(Strict.Axi4ReadData dom kr iw dataType userType)
(Axi4ReadData dom kr iw dataType userType)
fromStrict = Circuit (C.unbundle . fmap go . C.bundle)
where
go (Strict.S2M_ReadData{..}, ack) = (coerce ack, S2M_ReadData{_rvalid=True,..})
go (Strict.S2M_NoReadData, ack) = (coerce ack, S2M_ReadData{_rvalid=False})

-- | Convert an 'Axi4ReadData' into its strict 'Df' equivalent.
toStrictDf ::
Circuit
(Axi4ReadData dom kr iw dataType userType)
(Df dom (Strict.S2M_ReadData kr iw dataType userType))
toStrictDf = Circuit (C.unbundle . fmap go . C.bundle)
where
go (S2M_ReadData{..}, ack)
| _rvalid = (coerce ack, Df.Data (Strict.S2M_ReadData{..}))
| otherwise = (coerce ack, Df.NoData)

-- | Convert a into 'Axi4ReadData' from its Df equivalent
fromStrictDf ::
Circuit
(Df dom (Strict.S2M_ReadData kr iw dataType userType))
(Axi4ReadData dom kr iw dataType userType)
fromStrictDf = Circuit (C.unbundle . fmap go . C.bundle)
where
go (Df.Data (Strict.S2M_ReadData{..}), ack) = (coerce ack, S2M_ReadData{_rvalid=True,..})
go (_, ack) = (coerce ack, S2M_ReadData{_rvalid=False})
52 changes: 52 additions & 0 deletions src/Protocols/Axi4/Partial/Full/WriteAddress.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ to the AXI4 specification.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-missing-fields #-}
Expand All @@ -14,6 +15,8 @@ module Protocols.Axi4.Partial.Full.WriteAddress
( M2S_WriteAddress(..)
, S2M_WriteAddress(..)
, Axi4WriteAddress
, toStrict, toStrictDf
, fromStrict, fromStrictDf
) where

-- base
Expand All @@ -31,6 +34,9 @@ import Protocols.Axi4.Common
import Protocols.Internal
import Protocols.DfLike (DfLike)
import qualified Protocols.DfLike as DfLike
import qualified Protocols.Axi4.Strict.Full.WriteAddress as Strict
import qualified Protocols.Df as Df
import Protocols.Df (Df)

-- | AXI4 Write Address channel protocol
data Axi4WriteAddress
Expand Down Expand Up @@ -187,3 +193,49 @@ deriving instance
, C.NFDataX (PermissionsType kp)
, C.NFDataX (QosType kq) ) =>
C.NFDataX (M2S_WriteAddress kb ksz lw iw aw kr kbl kl kc kp kq userType)

-- | Convert an 'Axi4WriteAddress' into its strict version
-- 'Strict.Axi4WriteAddress'. The latter is usually preferred in Clash designs
-- as its definitions don't contain partial fields. Note that the functions
-- defined over these circuits operate on @userType@. If you need functions to
-- map over all fields, consider using 'toStrictDf'.
toStrict ::
Circuit
(Axi4WriteAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
(Strict.Axi4WriteAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
toStrict = Circuit (C.unbundle . fmap go . C.bundle)
where
go (M2S_WriteAddress{..}, ack)
| _awvalid = (coerce ack, Strict.M2S_WriteAddress{..})
| otherwise = (coerce ack, Strict.M2S_NoWriteAddress)

-- | Convert a 'Strict.Axi4WriteAddress' into 'Axi4WriteAddress'
fromStrict ::
Circuit
(Strict.Axi4WriteAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
(Axi4WriteAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
fromStrict = Circuit (C.unbundle . fmap go . C.bundle)
where
go (Strict.M2S_WriteAddress{..}, ack) = (coerce ack, M2S_WriteAddress{_awvalid=True,..})
go (Strict.M2S_NoWriteAddress, ack) = (coerce ack, M2S_WriteAddress{_awvalid=False})

-- | Convert an 'Axi4WriteAddress' into its strict 'Df' equivalent.
toStrictDf ::
Circuit
(Axi4WriteAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
(Df dom (Strict.M2S_WriteAddress kb ksz lw iw aw kr kbl kl kc kp kq userType))
toStrictDf = Circuit (C.unbundle . fmap go . C.bundle)
where
go (M2S_WriteAddress{..}, ack)
| _awvalid = (coerce ack, Df.Data (Strict.M2S_WriteAddress{..}))
| otherwise = (coerce ack, Df.NoData)

-- | Convert a into 'Axi4WriteAddress' from its Df equivalent
fromStrictDf ::
Circuit
(Df dom (Strict.M2S_WriteAddress kb ksz lw iw aw kr kbl kl kc kp kq userType))
(Axi4WriteAddress dom kb ksz lw iw aw kr kbl kl kc kp kq userType)
fromStrictDf = Circuit (C.unbundle . fmap go . C.bundle)
where
go (Df.Data (Strict.M2S_WriteAddress{..}), ack) = (coerce ack, M2S_WriteAddress{_awvalid=True,..})
go (_, ack) = (coerce ack, M2S_WriteAddress{_awvalid=False})
Loading

0 comments on commit da0c3c6

Please sign in to comment.