Skip to content

Commit

Permalink
Strongly separate clash-protocols-base and clash-protocols
Browse files Browse the repository at this point in the history
`clash-protocols-base` should only contain code and definitions related to the circuit plugin.
This includes the `Circuit` definition and `Protocol` typeclass. Furthermore we include instances
for types imported from underlying clash libraries such as tuples, `Vec` and `Signal`.
  • Loading branch information
lmbollen committed Sep 27, 2024
1 parent 8b80277 commit 5ddd411
Show file tree
Hide file tree
Showing 7 changed files with 70 additions and 42 deletions.
2 changes: 1 addition & 1 deletion clash-protocols-base/clash-protocols-base.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ library

exposed-modules:
Protocols.Cpp
Protocols.Internal
Protocols.Circuit
Protocols.Internal.Classes
Protocols.Internal.TaggedBundle
Protocols.Internal.TaggedBundle.TH
Expand Down
38 changes: 38 additions & 0 deletions clash-protocols-base/src/Protocols/Circuit.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
{-# OPTIONS_GHC -Wno-dodgy-exports #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Protocols.Circuit (
module Protocols.Internal.Classes,
) where

import Clash.Signal
import Clash.Sized.Vector
import GHC.TypeNats (KnownNat)
import Protocols.Cpp (maxTupleSize)
import Protocols.Internal.TH
import Protocols.Internal.Classes

instance Protocol () where
type Fwd () = ()
type Bwd () = ()

{- | __NB__: The documentation only shows instances up to /3/-tuples. By
default, instances up to and including /12/-tuples will exist. If the flag
@large-tuples@ is set instances up to the GHC imposed limit will exist. The
GHC imposed limit is either 62 or 64 depending on the GHC version.
-}
instance Protocol (a, b) where
type Fwd (a, b) = (Fwd a, Fwd b)
type Bwd (a, b) = (Bwd a, Bwd b)

-- Generate n-tuple instances, where n > 2
protocolTupleInstances 3 maxTupleSize

instance (KnownNat n) => Protocol (Vec n a) where
type Fwd (Vec n a) = Vec n (Fwd a)
type Bwd (Vec n a) = Vec n (Bwd a)

-- XXX: Type families with Signals on LHS are currently broken on Clash:
instance Protocol (CSignal dom a) where
type Fwd (CSignal dom a) = Signal dom a
type Bwd (CSignal dom a) = Signal dom ()
11 changes: 11 additions & 0 deletions clash-protocols-base/src/Protocols/Internal/Classes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ for instances. They are defined separately to avoid import loops.
This module is not exported; the classes and their (orphan) instances are
exported elsewhere.
-}
{-# LANGUAGE RoleAnnotations #-}
module Protocols.Internal.Classes where

import Clash.Signal
Expand Down Expand Up @@ -141,6 +142,16 @@ class (Protocol p) => IdleCircuit p where
idleFwd :: Proxy p -> Fwd (p :: Type)
idleBwd :: Proxy p -> Bwd (p :: Type)

{- | Circuit protocol with /Signal dom a/ in its forward direction, and
/()/ in its backward direction. Convenient for exposing protocol
internals, or simply for undirectional streams.
Note: 'CSignal' exists to work around [issue 760](https://github.com/clash-lang/clash-compiler/issues/760)
in Clash, where type families with 'Signal' on the LHS are broken.
-}
data CSignal (dom :: Domain) (a :: Type)

type role CSignal nominal representational

{- | Force a /nack/ on the backward channel and /no data/ on the forward
channel if reset is asserted.
-}
Expand Down
2 changes: 1 addition & 1 deletion clash-protocols-base/src/Protocols/Plugin.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ module Protocols.Plugin (
import Prelude

-- clash-protocols
import Protocols.Internal
import Protocols.Internal.Classes
import Protocols.Internal.TaggedBundle
import Protocols.Internal.Units
import Protocols.Plugin.Internal
Expand Down
17 changes: 16 additions & 1 deletion clash-protocols-base/src/Protocols/Plugin/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,22 @@ module Protocols.Plugin.Internal where
import Clash.Explicit.Prelude

import Data.Tagged
import Protocols.Internal
import GHC.Base (Any)
import Protocols.Internal.Classes

{- | Picked up by "Protocols.Plugin" to process protocol DSL. See
"Protocols.Plugin" for more information.
-}
circuit :: Any
circuit =
error "'protocol' called: did you forget to enable \"Protocols.Plugin\"?"

{- | Picked up by "Protocols.Plugin" to tie circuits together. See
"Protocols.Plugin" for more information.
-}
(-<) :: Any
(-<) =
error "(-<) called: did you forget to enable \"Protocols.Plugin\"?"

{- | Convenience type alias. A circuit where all parts are decorated with a
tag, referring to the @a@ and @b@ in its main signature. This is (indirectly)
Expand Down
1 change: 1 addition & 0 deletions clash-protocols/clash-protocols.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -145,6 +145,7 @@ library
Protocols.Axi4.WriteData
Protocols.Axi4.WriteResponse
Protocols.Df
Protocols.Internal
Protocols.DfConv
Protocols.Hedgehog
Protocols.Hedgehog.Internal
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -26,12 +26,11 @@ import GHC.Base (Any)
import Prelude hiding (const, map)

import qualified Clash.Explicit.Prelude as CE
import Clash.Prelude (Signal, type (*), type (+))
import Clash.Prelude (type (*), type (+))
import qualified Clash.Prelude as C

import Protocols.Cpp (maxTupleSize)
import Protocols.Circuit
import Protocols.Internal.Classes
import Protocols.Internal.TH (protocolTupleInstances)

import Control.Arrow ((***))
import Data.Coerce (coerce)
Expand All @@ -53,42 +52,6 @@ newtype Ack = Ack Bool
instance Default Ack where
def = Ack True

{- | Circuit protocol with /Signal dom a/ in its forward direction, and
/()/ in its backward direction. Convenient for exposing protocol
internals, or simply for undirectional streams.
Note: 'CSignal' exists to work around [issue 760](https://github.com/clash-lang/clash-compiler/issues/760)
in Clash, where type families with 'Signal' on the LHS are broken.
-}
data CSignal (dom :: CE.Domain) (a :: Type)

type role CSignal nominal representational

instance Protocol () where
type Fwd () = ()
type Bwd () = ()

{- | __NB__: The documentation only shows instances up to /3/-tuples. By
default, instances up to and including /12/-tuples will exist. If the flag
@large-tuples@ is set instances up to the GHC imposed limit will exist. The
GHC imposed limit is either 62 or 64 depending on the GHC version.
-}
instance Protocol (a, b) where
type Fwd (a, b) = (Fwd a, Fwd b)
type Bwd (a, b) = (Bwd a, Bwd b)

-- Generate n-tuple instances, where n > 2
protocolTupleInstances 3 maxTupleSize

instance (C.KnownNat n) => Protocol (C.Vec n a) where
type Fwd (C.Vec n a) = C.Vec n (Fwd a)
type Bwd (C.Vec n a) = C.Vec n (Bwd a)

-- XXX: Type families with Signals on LHS are currently broken on Clash:
instance Protocol (CSignal dom a) where
type Fwd (CSignal dom a) = Signal dom a
type Bwd (CSignal dom a) = Signal dom ()

{- | Left-to-right circuit composition.
@
Expand Down

0 comments on commit 5ddd411

Please sign in to comment.