{-| Copyright : (C) 2013-2016, University of Twente, 2017-2019, Myrtle Software Ltd, Google Inc. 2019, QBayLogic B.V. License : BSD2 (see the file LICENSE) Maintainer : Christiaan Baaij <christiaan.baaij@gmail.com> The Product/Signal isomorphism -} {-# LANGUAGE CPP #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilyDependencies #-} #if __GLASGOW_HASKELL__ < 806 {-# LANGUAGE TypeInType #-} #endif {-# LANGUAGE Trustworthy #-} --{-# OPTIONS_GHC -ddump-splices #-} {-# OPTIONS_HADDOCK show-extensions #-} module Clash.Signal.Bundle ( Bundle (..) -- ** Tools to emulate pre Clash 1.0 @Bundle ()@ instance , EmptyTuple(..) , TaggedEmptyTuple(..) -- ** Internal , vecBundle# ) where import Data.Functor.Compose import GHC.Generics import GHC.TypeLits (KnownNat) import Prelude hiding (head, map, tail) import Clash.Signal.Bundle.Internal (deriveBundleTuples) import Clash.Signal.Internal (Signal (..), Domain) import Clash.Sized.BitVector (Bit, BitVector) import Clash.Sized.Fixed (Fixed) import Clash.Sized.Index (Index) import Clash.Sized.Signed (Signed) import Clash.Sized.Unsigned (Unsigned) import Clash.Sized.Vector (Vec, traverse#, lazyV) import Clash.Sized.RTree (RTree, lazyT) -- | Isomorphism between a 'Clash.Signal.Signal' of a product type (e.g. a tuple) and a -- product type of 'Clash.Signal.Signal's. -- -- Instances of 'Bundle' must satisfy the following laws: -- -- @ -- 'bundle' . 'unbundle' = 'id' -- 'unbundle' . 'bundle' = 'id' -- @ -- -- By default, 'bundle' and 'unbundle', are defined as the identity, that is, -- writing: -- -- @ -- data D = A | B -- -- instance Bundle D -- @ -- -- is the same as: -- -- @ -- data D = A | B -- -- instance Bundle D where -- type 'Unbundled' clk D = 'Signal' clk D -- 'bundle' s = s -- 'unbundle' s = s -- @ -- -- For custom product types you'll have to write the instance manually: -- -- @ -- data Pair a b = MkPair { getA :: a, getB :: b } -- -- instance Bundle (Pair a b) where -- type Unbundled dom (Pair a b) = Pair (Signal dom a) (Signal dom b) -- -- -- bundle :: Pair (Signal dom a) (Signal dom b) -> Signal dom (Pair a b) -- bundle (MkPair as bs) = MkPair <$> as <*> bs -- -- -- unbundle :: Signal dom (Pair a b) -> Pair (Signal dom a) (Signal dom b) -- unbundle pairs = MkPair (getA <$> pairs) (getB <$> pairs) -- @ class Bundle a where type Unbundled (dom :: Domain) a = res | res -> dom a type Unbundled dom a = Signal dom a -- | Example: -- -- @ -- __bundle__ :: ('Signal' dom a, 'Signal' dom b) -> 'Signal' dom (a,b) -- @ -- -- However: -- -- @ -- __bundle__ :: 'Signal' dom 'Clash.Sized.BitVector.Bit' -> 'Signal' dom 'Clash.Sized.BitVector.Bit' -- @ bundle :: Unbundled dom a -> Signal dom a {-# INLINE bundle #-} default bundle :: (Signal dom a ~ Unbundled dom a) => Unbundled dom a -> Signal dom a bundle Unbundled dom a s = Signal dom a Unbundled dom a s -- | Example: -- -- @ -- __unbundle__ :: 'Signal' dom (a,b) -> ('Signal' dom a, 'Signal' dom b) -- @ -- -- However: -- -- @ -- __unbundle__ :: 'Signal' dom 'Clash.Sized.BitVector.Bit' -> 'Signal' dom 'Clash.Sized.BitVector.Bit' -- @ unbundle :: Signal dom a -> Unbundled dom a {-# INLINE unbundle #-} default unbundle :: (Unbundled dom a ~ Signal dom a) => Signal dom a -> Unbundled dom a unbundle Signal dom a s = Signal dom a Unbundled dom a s instance Bundle () instance Bundle Bool instance Bundle Integer instance Bundle Int instance Bundle Float instance Bundle Double instance Bundle (Maybe a) instance Bundle (Either a b) instance Bundle Bit instance Bundle (BitVector n) instance Bundle (Index n) instance Bundle (Fixed rep int frac) instance Bundle (Signed n) instance Bundle (Unsigned n)