Skip to content

Commit 6026ee9

Browse files
authored
Small improvements for DFConv and Axi4 related (#45)
1 parent 06c581b commit 6026ee9

File tree

12 files changed

+565
-213
lines changed

12 files changed

+565
-213
lines changed

clash-protocols.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -189,7 +189,8 @@ test-suite unittests
189189
Tests.Protocols
190190
Tests.Protocols.Df
191191
Tests.Protocols.DfConv
192-
Tests.Protocols.AvalonMemMap
192+
Tests.Protocols.Avalon
193+
Tests.Protocols.Axi4
193194
Tests.Protocols.Plugin
194195
Tests.Protocols.Wishbone
195196

@@ -203,6 +204,7 @@ test-suite unittests
203204
extra,
204205
hashable,
205206
hedgehog,
207+
strict-tuple,
206208
tasty >= 1.2 && < 1.5,
207209
tasty-hedgehog >= 1.2,
208210
tasty-th,

src/Protocols/Axi4/Common.hs

Lines changed: 39 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,14 @@ Types and utilities shared between AXI4, AXI4-Lite, and AXI3.
44
{-# LANGUAGE GADTs #-}
55
{-# LANGUAGE TypeFamilyDependencies #-}
66
{-# LANGUAGE UndecidableInstances #-}
7+
{-# OPTIONS_GHC -fno-warn-orphans #-} -- NFDataX and ShowX for T3 and T4
78

89
module Protocols.Axi4.Common where
910

1011
-- base
1112
import GHC.Generics (Generic)
1213
import GHC.TypeNats (Nat)
14+
import Control.DeepSeq (NFData)
1315

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

2123
import Protocols.Internal
2224

25+
deriving instance
26+
( C.NFDataX a
27+
, C.NFDataX b
28+
, C.NFDataX c
29+
) => C.NFDataX (T3 a b c)
30+
31+
deriving instance
32+
( C.NFDataX a
33+
, C.NFDataX b
34+
, C.NFDataX c
35+
, C.NFDataX d
36+
) => C.NFDataX (T4 a b c d)
37+
38+
deriving instance
39+
( C.ShowX a
40+
, C.ShowX b
41+
, C.ShowX c
42+
) => C.ShowX (T3 a b c)
43+
44+
deriving instance
45+
( C.ShowX a
46+
, C.ShowX b
47+
, C.ShowX c
48+
, C.ShowX d
49+
) => C.ShowX (T4 a b c d)
50+
2351
-- | Enables or disables 'BurstMode'
2452
type BurstType (keep :: Bool) = KeepType keep BurstMode
2553

@@ -136,7 +164,7 @@ data BurstMode
136164
-- This burst type is used for cache line accesses.
137165
--
138166
| BmWrap
139-
deriving (Show, C.ShowX, Generic, C.NFDataX, Eq)
167+
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)
140168

141169
-- | The maximum number of bytes to transfer in each data transfer, or beat,
142170
-- in a burst.
@@ -149,7 +177,7 @@ data BurstSize
149177
| Bs32
150178
| Bs64
151179
| Bs128
152-
deriving (Show, C.ShowX, Generic, C.NFDataX)
180+
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)
153181

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

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

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

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

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

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

201233
-- | Whether transaction can be modified
202234
data Modifiable
203235
= Modifiable
204236
| NonModifiable
237+
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)
205238

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

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

218253
-- | Whether the transaction is an instruction access or a data access. The AXI
219254
-- protocol defines this indication as a hint. It is not accurate in all cases,
@@ -224,3 +259,4 @@ data Privileged
224259
data InstructionOrData
225260
= Data
226261
| Instruction
262+
deriving (Show, C.ShowX, Generic, C.NFDataX, NFData, Eq)

src/Protocols/Axi4/ReadAddress.hs

Lines changed: 49 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module Protocols.Axi4.ReadAddress
1818

1919
-- * configuration
2020
, Axi4ReadAddressConfig(..)
21-
, GoodAxi4ReadAddressConfig
21+
, KnownAxi4ReadAddressConfig
2222
, ARKeepBurst
2323
, ARKeepSize
2424
, ARIdWidth
@@ -37,6 +37,7 @@ module Protocols.Axi4.ReadAddress
3737
) where
3838

3939
-- base
40+
import Control.DeepSeq (NFData)
4041
import Data.Coerce
4142
import Data.Kind (Type)
4243
import GHC.Generics (Generic)
@@ -187,7 +188,7 @@ newtype S2M_ReadAddress = S2M_ReadAddress
187188
-- | Shorthand for a "well-behaved" read address config,
188189
-- so that we don't need to write out a bunch of type constraints later.
189190
-- Holds for every configuration; don't worry about implementing this class.
190-
class
191+
type KnownAxi4ReadAddressConfig conf =
191192
( KeepTypeClass (ARKeepBurst conf)
192193
, KeepTypeClass (ARKeepSize conf)
193194
, KeepTypeClass (ARKeepRegion conf)
@@ -200,37 +201,14 @@ class
200201
, C.KnownNat (ARIdWidth conf)
201202
, C.KnownNat (ARAddrWidth conf)
202203

203-
, Show (RegionType (ARKeepRegion conf))
204-
, Show (BurstLengthType (ARKeepBurstLength conf))
205-
, Show (SizeType (ARKeepSize conf))
206-
, Show (BurstType (ARKeepBurst conf))
207-
, Show (LockType (ARKeepLock conf))
208-
, Show (CacheType (ARKeepCache conf))
209-
, Show (PermissionsType (ARKeepPermissions conf))
210-
, Show (QosType (ARKeepQos conf))
211-
212-
, C.NFDataX (RegionType (ARKeepRegion conf))
213-
, C.NFDataX (BurstLengthType (ARKeepBurstLength conf))
214-
, C.NFDataX (SizeType (ARKeepSize conf))
215-
, C.NFDataX (BurstType (ARKeepBurst conf))
216-
, C.NFDataX (LockType (ARKeepLock conf))
217-
, C.NFDataX (CacheType (ARKeepCache conf))
218-
, C.NFDataX (PermissionsType (ARKeepPermissions conf))
219-
, C.NFDataX (QosType (ARKeepQos conf))
220-
) => GoodAxi4ReadAddressConfig conf
221-
222-
instance
223-
( KeepTypeClass (ARKeepBurst conf)
224-
, KeepTypeClass (ARKeepSize conf)
225-
, KeepTypeClass (ARKeepRegion conf)
226-
, KeepTypeClass (ARKeepBurstLength conf)
227-
, KeepTypeClass (ARKeepLock conf)
228-
, KeepTypeClass (ARKeepCache conf)
229-
, KeepTypeClass (ARKeepPermissions conf)
230-
, KeepTypeClass (ARKeepQos conf)
231-
232-
, C.KnownNat (ARIdWidth conf)
233-
, C.KnownNat (ARAddrWidth conf)
204+
, C.ShowX (RegionType (ARKeepRegion conf))
205+
, C.ShowX (BurstLengthType (ARKeepBurstLength conf))
206+
, C.ShowX (SizeType (ARKeepSize conf))
207+
, C.ShowX (BurstType (ARKeepBurst conf))
208+
, C.ShowX (LockType (ARKeepLock conf))
209+
, C.ShowX (CacheType (ARKeepCache conf))
210+
, C.ShowX (PermissionsType (ARKeepPermissions conf))
211+
, C.ShowX (QosType (ARKeepQos conf))
234212

235213
, Show (RegionType (ARKeepRegion conf))
236214
, Show (BurstLengthType (ARKeepBurstLength conf))
@@ -249,16 +227,34 @@ instance
249227
, C.NFDataX (CacheType (ARKeepCache conf))
250228
, C.NFDataX (PermissionsType (ARKeepPermissions conf))
251229
, C.NFDataX (QosType (ARKeepQos conf))
252-
) => GoodAxi4ReadAddressConfig conf
230+
231+
, NFData (RegionType (ARKeepRegion conf))
232+
, NFData (BurstLengthType (ARKeepBurstLength conf))
233+
, NFData (SizeType (ARKeepSize conf))
234+
, NFData (BurstType (ARKeepBurst conf))
235+
, NFData (LockType (ARKeepLock conf))
236+
, NFData (CacheType (ARKeepCache conf))
237+
, NFData (PermissionsType (ARKeepPermissions conf))
238+
, NFData (QosType (ARKeepQos conf))
239+
240+
, Eq (RegionType (ARKeepRegion conf))
241+
, Eq (BurstLengthType (ARKeepBurstLength conf))
242+
, Eq (SizeType (ARKeepSize conf))
243+
, Eq (BurstType (ARKeepBurst conf))
244+
, Eq (LockType (ARKeepLock conf))
245+
, Eq (CacheType (ARKeepCache conf))
246+
, Eq (PermissionsType (ARKeepPermissions conf))
247+
, Eq (QosType (ARKeepQos conf))
248+
)
253249

254250
deriving instance
255-
( GoodAxi4ReadAddressConfig conf
251+
( KnownAxi4ReadAddressConfig conf
256252
, Show userType
257253
) =>
258254
Show (M2S_ReadAddress conf userType)
259255

260256
deriving instance
261-
( GoodAxi4ReadAddressConfig conf
257+
( KnownAxi4ReadAddressConfig conf
262258
, C.NFDataX userType
263259
) =>
264260
C.NFDataX (M2S_ReadAddress conf userType)
@@ -307,15 +303,30 @@ data Axi4ReadAddressInfo (conf :: Axi4ReadAddressConfig) (userType :: Type)
307303
deriving (Generic)
308304

309305
deriving instance
310-
( GoodAxi4ReadAddressConfig conf
306+
( KnownAxi4ReadAddressConfig conf
311307
, Show userType ) =>
312308
Show (Axi4ReadAddressInfo conf userType)
313309

314310
deriving instance
315-
( GoodAxi4ReadAddressConfig conf
311+
( KnownAxi4ReadAddressConfig conf
312+
, C.ShowX userType ) =>
313+
C.ShowX (Axi4ReadAddressInfo conf userType)
314+
315+
deriving instance
316+
( KnownAxi4ReadAddressConfig conf
316317
, C.NFDataX userType ) =>
317318
C.NFDataX (Axi4ReadAddressInfo conf userType)
318319

320+
deriving instance
321+
( KnownAxi4ReadAddressConfig conf
322+
, NFData userType ) =>
323+
NFData (Axi4ReadAddressInfo conf userType)
324+
325+
deriving instance
326+
( KnownAxi4ReadAddressConfig conf
327+
, Eq userType ) =>
328+
Eq (Axi4ReadAddressInfo conf userType)
329+
319330
-- | Convert 'M2S_ReadAddress' to 'Axi4ReadAddressInfo', dropping some info
320331
axi4ReadAddrMsgToReadAddrInfo
321332
:: M2S_ReadAddress conf userType

src/Protocols/Axi4/ReadData.hs

Lines changed: 5 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ module Protocols.Axi4.ReadData
1717

1818
-- * configuration
1919
, Axi4ReadDataConfig(..)
20-
, GoodAxi4ReadDataConfig
20+
, KnownAxi4ReadDataConfig
2121
, RKeepResponse
2222
, RIdWidth
2323
) where
@@ -101,29 +101,22 @@ newtype M2S_ReadData = M2S_ReadData { _rready :: Bool }
101101
-- | Shorthand for a "well-behaved" read data config,
102102
-- so that we don't need to write out a bunch of type constraints later.
103103
-- Holds for every configuration; don't worry about implementing this class.
104-
class
104+
type KnownAxi4ReadDataConfig conf =
105105
( KeepTypeClass (RKeepResponse conf)
106106
, C.KnownNat (RIdWidth conf)
107107
, Show (ResponseType (RKeepResponse conf))
108108
, C.NFDataX (ResponseType (RKeepResponse conf))
109-
) => GoodAxi4ReadDataConfig conf
110-
111-
instance
112-
( KeepTypeClass (RKeepResponse conf)
113-
, C.KnownNat (RIdWidth conf)
114-
, Show (ResponseType (RKeepResponse conf))
115-
, C.NFDataX (ResponseType (RKeepResponse conf))
116-
) => GoodAxi4ReadDataConfig conf
109+
)
117110

118111
deriving instance
119-
( GoodAxi4ReadDataConfig conf
112+
( KnownAxi4ReadDataConfig conf
120113
, Show userType
121114
, Show dataType
122115
) =>
123116
Show (S2M_ReadData conf userType dataType)
124117

125118
deriving instance
126-
( GoodAxi4ReadDataConfig conf
119+
( KnownAxi4ReadDataConfig conf
127120
, C.NFDataX userType
128121
, C.NFDataX dataType
129122
) =>

0 commit comments

Comments
 (0)