clash-prelude-1.2.5: CAES Language for Synchronous Hardware - Prelude library
Copyright(C) 2013-2016 University of Twente
2016-2019 Myrtle Software
2017 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • ScopedTypeVariables
  • BangPatterns
  • ViewPatterns
  • GADTs
  • GADTSyntax
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveLift
  • DerivingStrategies
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • MagicHash
  • KindSignatures
  • TupleSections
  • RankNTypes
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Explicit.Signal

Description

Clash has synchronous Signals in the form of:

Signal (dom :: Symbol) a

Where a is the type of the value of the Signal, for example Int or Bool, and dom is the clock- (and reset-) domain to which the memory elements manipulating these Signals belong.

The type-parameter, dom, is of the kind Domain - a simple string. That string refers to a single synthesis domain. A synthesis domain describes the behavior of certain aspects of memory elements in it. More specifically, a domain looks like:

DomainConfiguration
  { _name:: Symbol
  -- ^ Domain name
  , _period :: Nat
  -- ^ Clock period in ps
  , _edge :: ActiveEdge
  -- ^ Active edge of the clock
  , _reset :: ResetKind
  -- ^ Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive)
  , _init :: InitBehavior
  -- ^ Whether the initial (or "power up") value of memory elements is
  -- unknown/undefined, or configurable to a specific value
  , _polarity :: ResetPolarity
  -- ^ Whether resets are active high or active low
  }

Check the documentation of each of the types to see the various options Clash provides. In order to specify a domain, an instance of KnownDomain should be made. Clash provides a standard implementation, called System, that is configured as follows:

instance KnownDomain System where
  type KnownConf System = 'DomainConfiguration System 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh
  knownDomain = SDomainConfiguration SSymbol SNat SRising SAsynchronous SDefined SActiveHigh

In words, "System" is a synthesis domain with a clock running with a period of 10000 ps (100 MHz). Memory elements update their state on the rising edge of the clock, can be reset asynchronously with regards to the clock, and have defined power up values if applicable.

In order to create a new domain, you don't have to instantiate it explicitly. Instead, you can have createDomain create a domain for you. You can also use the same function to subclass existing domains.

  • NB: "Bad things"™ happen when you actually use a clock period of 0, so do not do that!
  • NB: You should be judicious using a clock with period of 1 as you can never create a clock that goes any faster!
  • NB: For the best compatibility make sure your period is divisible by 2, because some VHDL simulators don't support fractions of picoseconds.
  • NB: Whether System has good defaults depends on your target platform. Check out IntelSystem and XilinxSystem too!

Explicit clocks and resets, and meta-stability

When using multiple clocks and/or reset lines there are ways to accidentally introduce situations that are prone to metastability. These bugs are incredibly hard to debug as they often cannot be simulated, so it's best to prevent them in the first place. This section outlines the situations in which metastability arises and how to prevent it.

Two types of resets exist: synchronous and asynchronous resets. These reset types are encoded in a synthesis domain. For the following examples we assume the following exist:

DomainConfiguration "SyncExample" _period _edge Synchronous _init
DomainConfiguration "AsyncExample" _period _edge Asynchronous _init

See the previous section on how to use domains.

We now go over the clock and reset line combinations and explain when they can potentially introduce situations prone to meta-stability:

  • Reset situation 1:

    f :: Reset "SyncExample" -> Reset "SyncExample" -> ..
    f x y = ..
    

    There are no problems here, because although x and y can have different values, components to these reset lines are reset synchronously, and there is no metastability situation.

  • Reset situation 2:

    g :: Reset "AsyncExample" -> Reset "AsyncExample" -> ..
    g x y = ..
    

    This situation can be prone to metastability, because although x and y belong to the same domain according to their domain, there is no guarantee that they actually originate from the same source. This means that one component can enter its reset state asynchronously to another component, inducing metastability in the other component.

  • Clock situation:

    k :: Clock dom -> Clock dom -> ..
    k x y = ..
    

    The situation above is potentially prone to metastability, because even though x and y belong to the same domain according to their domain, there is no guarantee that they actually originate from the same source. They could hence be connected to completely unrelated clock sources, and components can then induce metastable states in others.

Synopsis

Synchronous signal

data Signal (dom :: Domain) a Source #

Clash has synchronous Signals in the form of:

Signal (dom :: Domain) a

Where a is the type of the value of the Signal, for example Int or Bool, and dom is the clock- (and reset-) domain to which the memory elements manipulating these Signals belong.

The type-parameter, dom, is of the kind Domain - a simple string. That string refers to a single synthesis domain. A synthesis domain describes the behavior of certain aspects of memory elements in it.

  • NB: "Bad things"™ happen when you actually use a clock period of 0, so do not do that!
  • NB: You should be judicious using a clock with period of 1 as you can never create a clock that goes any faster!
  • NB: For the best compatibility make sure your period is divisible by 2, because some VHDL simulators don't support fractions of picoseconds.
  • NB: Whether System has good defaults depends on your target platform. Check out IntelSystem and XilinxSystem too!

See the module documentation of Clash.Signal for more information about domains.

Instances

Instances details
Lift a => Lift (Signal dom a :: Type) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

lift :: Signal dom a -> Q Exp #

liftTyped :: Signal dom a -> Q (TExp (Signal dom a)) #

Functor (Signal dom) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

fmap :: (a -> b) -> Signal dom a -> Signal dom b #

(<$) :: a -> Signal dom b -> Signal dom a #

Applicative (Signal dom) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

pure :: a -> Signal dom a #

(<*>) :: Signal dom (a -> b) -> Signal dom a -> Signal dom b #

liftA2 :: (a -> b -> c) -> Signal dom a -> Signal dom b -> Signal dom c #

(*>) :: Signal dom a -> Signal dom b -> Signal dom b #

(<*) :: Signal dom a -> Signal dom b -> Signal dom a #

Foldable (Signal dom) Source #

NB: Not synthesizable

NB: In "foldr f z s":

  • The function f should be lazy in its second argument.
  • The z element will never be used.
Instance details

Defined in Clash.Signal.Internal

Methods

fold :: Monoid m => Signal dom m -> m #

foldMap :: Monoid m => (a -> m) -> Signal dom a -> m #

foldMap' :: Monoid m => (a -> m) -> Signal dom a -> m #

foldr :: (a -> b -> b) -> b -> Signal dom a -> b #

foldr' :: (a -> b -> b) -> b -> Signal dom a -> b #

foldl :: (b -> a -> b) -> b -> Signal dom a -> b #

foldl' :: (b -> a -> b) -> b -> Signal dom a -> b #

foldr1 :: (a -> a -> a) -> Signal dom a -> a #

foldl1 :: (a -> a -> a) -> Signal dom a -> a #

toList :: Signal dom a -> [a] #

null :: Signal dom a -> Bool #

length :: Signal dom a -> Int #

elem :: Eq a => a -> Signal dom a -> Bool #

maximum :: Ord a => Signal dom a -> a #

minimum :: Ord a => Signal dom a -> a #

sum :: Num a => Signal dom a -> a #

product :: Num a => Signal dom a -> a #

Traversable (Signal dom) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Signal dom a -> f (Signal dom b) #

sequenceA :: Applicative f => Signal dom (f a) -> f (Signal dom a) #

mapM :: Monad m => (a -> m b) -> Signal dom a -> m (Signal dom b) #

sequence :: Monad m => Signal dom (m a) -> m (Signal dom a) #

Fractional a => Fractional (Signal dom a) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

(/) :: Signal dom a -> Signal dom a -> Signal dom a #

recip :: Signal dom a -> Signal dom a #

fromRational :: Rational -> Signal dom a #

Num a => Num (Signal dom a) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

(+) :: Signal dom a -> Signal dom a -> Signal dom a #

(-) :: Signal dom a -> Signal dom a -> Signal dom a #

(*) :: Signal dom a -> Signal dom a -> Signal dom a #

negate :: Signal dom a -> Signal dom a #

abs :: Signal dom a -> Signal dom a #

signum :: Signal dom a -> Signal dom a #

fromInteger :: Integer -> Signal dom a #

Show a => Show (Signal dom a) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

showsPrec :: Int -> Signal dom a -> ShowS #

show :: Signal dom a -> String #

showList :: [Signal dom a] -> ShowS #

Arbitrary a => Arbitrary (Signal dom a) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

arbitrary :: Gen (Signal dom a) #

shrink :: Signal dom a -> [Signal dom a] #

CoArbitrary a => CoArbitrary (Signal dom a) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

coarbitrary :: Signal dom a -> Gen b -> Gen b #

Default a => Default (Signal dom a) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

def :: Signal dom a #

NFDataX a => NFDataX (Signal domain a) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

deepErrorX :: String -> Signal domain a Source #

hasUndefined :: Signal domain a -> Bool Source #

ensureSpine :: Signal domain a -> Signal domain a Source #

rnfX :: Signal domain a -> () Source #

Clocks (Clock c1, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source #

type HasDomain dom1 (Signal dom2 a) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSpecificDomain

type HasDomain dom1 (Signal dom2 a) = DomEq dom1 dom2
type TryDomain t (Signal dom a) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type TryDomain t (Signal dom a) = 'Found dom
type ClocksCxt (Clock c1, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Signal pllLock Bool) = KnownDomain c1
type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13, KnownDomain c14)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13, KnownDomain c14, KnownDomain c15)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13, KnownDomain c14, KnownDomain c15, KnownDomain c16)

data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #

The in part of an inout port

data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #

The out part of an inout port

Wraps (multiple) writing signals. The semantics are such that only one of the signals may write at a single time step.

Instances

Instances details
Semigroup (BiSignalOut defaultState dom n) Source # 
Instance details

Defined in Clash.Signal.BiSignal

Methods

(<>) :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n #

sconcat :: NonEmpty (BiSignalOut defaultState dom n) -> BiSignalOut defaultState dom n #

stimes :: Integral b => b -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n #

Monoid (BiSignalOut defaultState dom n) Source #

Monoid instance to support concatenating

NB Not synthesizable

Instance details

Defined in Clash.Signal.BiSignal

Methods

mempty :: BiSignalOut defaultState dom n #

mappend :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n #

mconcat :: [BiSignalOut defaultState dom n] -> BiSignalOut defaultState dom n #

type HasDomain dom1 (BiSignalOut ds dom2 n) Source # 
Instance details

Defined in Clash.Signal.BiSignal

type HasDomain dom1 (BiSignalOut ds dom2 n) = DomEq dom1 dom2
type TryDomain t (BiSignalOut ds dom n) Source # 
Instance details

Defined in Clash.Signal.BiSignal

type TryDomain t (BiSignalOut ds dom n) = 'Found dom

data BiSignalDefault Source #

Used to specify the default behavior of a BiSignal, i.e. what value is read when no value is being written to it.

Constructors

PullUp

inout port behaves as if connected to a pull-up resistor

PullDown

inout port behaves as if connected to a pull-down resistor

Floating

inout port behaves as if is floating. Reading a floating BiSignal value in simulation will yield an errorX (undefined value).

Instances

Instances details
Show BiSignalDefault Source # 
Instance details

Defined in Clash.Signal.BiSignal

Domain

class KnownSymbol dom => KnownDomain (dom :: Domain) where Source #

A KnownDomain constraint indicates that a circuit's behavior depends on some properties of a domain. See DomainConfiguration for more information.

Associated Types

type KnownConf dom :: DomainConfiguration Source #

Methods

knownDomain :: SDomainConfiguration dom (KnownConf dom) Source #

Returns SDomainConfiguration corresponding to an instance's DomainConfiguration.

Example usage: > knownDomain @System

Instances

Instances details
KnownDomain XilinxSystem Source #

System instance with defaults set for Xilinx FPGAs

Instance details

Defined in Clash.Signal.Internal

KnownDomain IntelSystem Source #

System instance with defaults set for Intel FPGAs

Instance details

Defined in Clash.Signal.Internal

KnownDomain System Source #

A clock (and reset) dom with clocks running at 100 MHz

Instance details

Defined in Clash.Signal.Internal

Associated Types

type KnownConf System :: DomainConfiguration Source #

type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf) Source #

data ActiveEdge Source #

Determines clock edge memory elements are sensitive to. Not yet implemented.

Constructors

Rising

Elements are sensitive to the rising edge (low-to-high) of the clock.

Falling

Elements are sensitive to the falling edge (high-to-low) of the clock.

Instances

Instances details
Eq ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

Data ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ActiveEdge -> c ActiveEdge #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ActiveEdge #

toConstr :: ActiveEdge -> Constr #

dataTypeOf :: ActiveEdge -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ActiveEdge) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActiveEdge) #

gmapT :: (forall b. Data b => b -> b) -> ActiveEdge -> ActiveEdge #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r #

gmapQ :: (forall d. Data d => d -> u) -> ActiveEdge -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ActiveEdge -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge #

Ord ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

Show ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

Generic ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

Associated Types

type Rep ActiveEdge :: Type -> Type #

Binary ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

NFData ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

rnf :: ActiveEdge -> () #

Hashable ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep ActiveEdge Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep ActiveEdge = D1 ('MetaData "ActiveEdge" "Clash.Signal.Internal" "clash-prelude-1.2.5-inplace" 'False) (C1 ('MetaCons "Rising" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Falling" 'PrefixI 'False) (U1 :: Type -> Type))

data SActiveEdge (edge :: ActiveEdge) where Source #

Singleton version of ActiveEdge

Instances

Instances details
Show (SActiveEdge edge) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

showsPrec :: Int -> SActiveEdge edge -> ShowS #

show :: SActiveEdge edge -> String #

showList :: [SActiveEdge edge] -> ShowS #

data InitBehavior Source #

Constructors

Unknown

Power up value of memory elements is unknown.

Defined

If applicable, power up value of a memory element is defined. Applies to registers for example, but not to blockRam.

Instances

Instances details
Eq InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

Data InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitBehavior -> c InitBehavior #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitBehavior #

toConstr :: InitBehavior -> Constr #

dataTypeOf :: InitBehavior -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InitBehavior) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitBehavior) #

gmapT :: (forall b. Data b => b -> b) -> InitBehavior -> InitBehavior #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitBehavior -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitBehavior -> r #

gmapQ :: (forall d. Data d => d -> u) -> InitBehavior -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InitBehavior -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior #

Ord InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

Show InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

Generic InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

Associated Types

type Rep InitBehavior :: Type -> Type #

NFData InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

rnf :: InitBehavior -> () #

Hashable InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep InitBehavior Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep InitBehavior = D1 ('MetaData "InitBehavior" "Clash.Signal.Internal" "clash-prelude-1.2.5-inplace" 'False) (C1 ('MetaCons "Unknown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Defined" 'PrefixI 'False) (U1 :: Type -> Type))

data SInitBehavior (init :: InitBehavior) where Source #

Instances

Instances details
Show (SInitBehavior init) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

showsPrec :: Int -> SInitBehavior init -> ShowS #

show :: SInitBehavior init -> String #

showList :: [SInitBehavior init] -> ShowS #

data ResetKind Source #

Constructors

Asynchronous

Elements respond asynchronously to changes in their reset input. This means that they do not wait for the next active clock edge, but respond immediately instead. Common on Intel FPGA platforms.

Synchronous

Elements respond synchronously to changes in their reset input. This means that changes in their reset input won't take effect until the next active clock edge. Common on Xilinx FPGA platforms.

Instances

Instances details
Eq ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

Data ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResetKind -> c ResetKind #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResetKind #

toConstr :: ResetKind -> Constr #

dataTypeOf :: ResetKind -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ResetKind) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResetKind) #

gmapT :: (forall b. Data b => b -> b) -> ResetKind -> ResetKind #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResetKind -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResetKind -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResetKind -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResetKind -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind #

Ord ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

Show ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

Generic ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

Associated Types

type Rep ResetKind :: Type -> Type #

NFData ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

rnf :: ResetKind -> () #

Hashable ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep ResetKind Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep ResetKind = D1 ('MetaData "ResetKind" "Clash.Signal.Internal" "clash-prelude-1.2.5-inplace" 'False) (C1 ('MetaCons "Asynchronous" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Synchronous" 'PrefixI 'False) (U1 :: Type -> Type))

data SResetKind (resetKind :: ResetKind) where Source #

Singleton version of ResetKind

Instances

Instances details
Show (SResetKind reset) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

showsPrec :: Int -> SResetKind reset -> ShowS #

show :: SResetKind reset -> String #

showList :: [SResetKind reset] -> ShowS #

data ResetPolarity Source #

Determines the value for which a reset line is considered "active"

Constructors

ActiveHigh

Reset is considered active if underlying signal is True.

ActiveLow

Reset is considered active if underlying signal is False.

Instances

Instances details
Eq ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

Data ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResetPolarity -> c ResetPolarity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResetPolarity #

toConstr :: ResetPolarity -> Constr #

dataTypeOf :: ResetPolarity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ResetPolarity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResetPolarity) #

gmapT :: (forall b. Data b => b -> b) -> ResetPolarity -> ResetPolarity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResetPolarity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResetPolarity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity #

Ord ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

Show ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

Generic ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

Associated Types

type Rep ResetPolarity :: Type -> Type #

NFData ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

rnf :: ResetPolarity -> () #

Hashable ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep ResetPolarity Source # 
Instance details

Defined in Clash.Signal.Internal

type Rep ResetPolarity = D1 ('MetaData "ResetPolarity" "Clash.Signal.Internal" "clash-prelude-1.2.5-inplace" 'False) (C1 ('MetaCons "ActiveHigh" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ActiveLow" 'PrefixI 'False) (U1 :: Type -> Type))

data SResetPolarity (polarity :: ResetPolarity) where Source #

Singleton version of ResetPolarity

Instances

Instances details
Show (SResetPolarity polarity) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

showsPrec :: Int -> SResetPolarity polarity -> ShowS #

show :: SResetPolarity polarity -> String #

showList :: [SResetPolarity polarity] -> ShowS #

data DomainConfiguration Source #

A domain with a name (Domain). Configures the behavior of various aspects of a circuits. See the documentation of this record's field types for more information on the options.

See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.

Constructors

DomainConfiguration 

Fields

data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) where Source #

Singleton version of DomainConfiguration

Constructors

SDomainConfiguration :: SSymbol dom -> SNat period -> SActiveEdge edge -> SResetKind reset -> SInitBehavior init -> SResetPolarity polarity -> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity) 

Instances

Instances details
Show (SDomainConfiguration dom conf) Source # 
Instance details

Defined in Clash.Signal.Internal

Configuration type families

type DomainPeriod (dom :: Domain) = DomainConfigurationPeriod (KnownConf dom) Source #

Convenience type to help to extract a period from a domain. Example usage:

myFunc :: (KnownDomain dom, DomainPeriod dom ~ 6000) => ...

type DomainActiveEdge (dom :: Domain) = DomainConfigurationActiveEdge (KnownConf dom) Source #

Convenience type to help to extract the active edge from a domain. Example usage:

myFunc :: (KnownDomain dom, DomainActiveEdge dom ~ 'Rising) => ...

type DomainResetKind (dom :: Domain) = DomainConfigurationResetKind (KnownConf dom) Source #

Convenience type to help to extract the reset synchronicity from a domain. Example usage:

myFunc :: (KnownDomain dom, DomainResetKind dom ~ 'Asynchronous) => ...

type DomainInitBehavior (dom :: Domain) = DomainConfigurationInitBehavior (KnownConf dom) Source #

Convenience type to help to extract the initial value behavior from a domain. Example usage:

myFunc :: (KnownDomain dom, DomainInitBehavior dom ~ 'Defined) => ...

type DomainResetPolarity (dom :: Domain) = DomainConfigurationResetPolarity (KnownConf dom) Source #

Convenience type to help to extract the reset polarity from a domain. Example usage:

myFunc :: (KnownDomain dom, DomainResetPolarity dom ~ 'ActiveHigh) => ...

Default domains

type System = "System" :: Domain Source #

A clock (and reset) dom with clocks running at 100 MHz. Memory elements respond to the rising edge of the clock, and asynchronously to changes in reset signals. It has defined initial values, and active-high resets.

See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.

type XilinxSystem = "XilinxSystem" :: Domain Source #

A clock (and reset) dom with clocks running at 100 MHz. Memory elements respond to the rising edge of the clock, and synchronously to changes in reset signals. It has defined initial values, and active-high resets.

See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.

type IntelSystem = "IntelSystem" :: Domain Source #

A clock (and reset) dom with clocks running at 100 MHz. Memory elements respond to the rising edge of the clock, and asynchronously to changes in reset signals. It has defined initial values, and active-high resets.

See module documentation of Clash.Explicit.Signal for more information on how to create custom synthesis domains.

vSystem :: VDomainConfiguration Source #

Convenience value to allow easy "subclassing" of System domain. Should be used in combination with createDomain. For example, if you just want to change the period but leave all other settings in tact use:

createDomain vSystem{vName="System10", vPeriod=10}

vIntelSystem :: VDomainConfiguration Source #

Convenience value to allow easy "subclassing" of IntelSystem domain. Should be used in combination with createDomain. For example, if you just want to change the period but leave all other settings in tact use:

createDomain vIntelSystem{vName="Intel10", vPeriod=10}

vXilinxSystem :: VDomainConfiguration Source #

Convenience value to allow easy "subclassing" of XilinxSystem domain. Should be used in combination with createDomain. For example, if you just want to change the period but leave all other settings in tact use:

createDomain vXilinxSystem{vName="Xilinx10", vPeriod=10}

Domain utilities

data VDomainConfiguration Source #

Same as SDomainConfiguration but allows for easy updates through record update syntax. Should be used in combination with vDomain and createDomain. Example:

createDomain (knownVDomain @System){vName="System10", vPeriod=10}

This duplicates the settings in the System domain, replaces the name and period, and creates an instance for it. As most users often want to update the system domain, a shortcut is available in the form:

createDomain vSystem{vName="System10", vPeriod=10}

Constructors

VDomainConfiguration 

Fields

vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration Source #

Convert SDomainConfiguration to VDomainConfiguration. Should be used in combination with createDomain only.

createDomain :: VDomainConfiguration -> Q [Dec] Source #

Convenience method to express new domains in terms of others.

createDomain (knownVDomain @System){vName="System10", vPeriod=10}

This duplicates the settings in the System domain, replaces the name and period, and creates an instance for it. As most users often want to update the system domain, a shortcut is available in the form:

createDomain vSystem{vName="System10", vPeriod=10}

The function will create two extra identifiers. The first:

type System10 = ..

You can use that as the dom to Clocks/Resets/Enables/Signals. For example: Signal System10 Int. Additionally, it will create a VDomainConfiguration that you can use in later calls to createDomain:

vSystem10 = knownVDomain @System10

knownVDomain :: forall dom. KnownDomain dom => VDomainConfiguration Source #

Like 'knownDomain but yields a VDomainConfiguration. Should only be used in combination with createDomain.

clockPeriod :: forall dom period. (KnownDomain dom, DomainPeriod dom ~ period) => SNat period Source #

Get the clock period from a KnownDomain context

activeEdge :: forall dom edge. (KnownDomain dom, DomainActiveEdge dom ~ edge) => SActiveEdge edge Source #

Get ActiveEdge from a KnownDomain context. Example usage:

f :: forall dom . KnownDomain dom => ....
f a b c =
  case activeEdge @dom of
    SRising -> foo
    SFalling -> bar

resetKind :: forall dom sync. (KnownDomain dom, DomainResetKind dom ~ sync) => SResetKind sync Source #

Get ResetKind from a KnownDomain context. Example usage:

f :: forall dom . KnownDomain dom => ....
f a b c =
  case resetKind @dom of
    SAsynchronous -> foo
    SSynchronous -> bar

initBehavior :: forall dom init. (KnownDomain dom, DomainInitBehavior dom ~ init) => SInitBehavior init Source #

Get InitBehavior from a KnownDomain context. Example usage:

f :: forall dom . KnownDomain dom => ....
f a b c =
  case initBehavior @dom of
    SDefined -> foo
    SUnknown -> bar

resetPolarity :: forall dom polarity. (KnownDomain dom, DomainResetPolarity dom ~ polarity) => SResetPolarity polarity Source #

Get ResetPolarity from a KnownDomain context. Example usage:

f :: forall dom . KnownDomain dom => ....
f a b c =
  case resetPolarity @dom of
    SActiveHigh -> foo
    SActiveLow -> bar

Enabling

data Enable dom Source #

A signal of booleans, indicating whether a component is enabled. No special meaning is implied, it's up to the component itself to decide how to respond to its enable line. It is used throughout Clash as a global enable signal.

Instances

Instances details
type HasDomain dom1 (Enable dom2) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSpecificDomain

type HasDomain dom1 (Enable dom2) = DomEq dom1 dom2
type TryDomain t (Enable dom) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type TryDomain t (Enable dom) = 'Found dom

toEnable :: Signal dom Bool -> Enable dom Source #

Convert a signal of bools to an Enable construct

fromEnable :: Enable dom -> Signal dom Bool Source #

Convert Enable construct to its underlying representation: a signal of bools.

enableGen :: Enable dom Source #

Enable generator for some domain. Is simply always True.

Clock

data Clock (dom :: Domain) Source #

A clock signal belonging to a domain named dom.

Instances

Instances details
Show (Clock dom) Source # 
Instance details

Defined in Clash.Signal.Internal

Methods

showsPrec :: Int -> Clock dom -> ShowS #

show :: Clock dom -> String #

showList :: [Clock dom] -> ShowS #

Clocks (Clock c1, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source #

Clocks (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

Associated Types

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source #

Methods

clocks :: forall (domIn :: Domain). (KnownDomain domIn, ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool)) => Clock domIn -> Reset domIn -> (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source #

type HasDomain dom1 (Clock dom2) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSpecificDomain

type HasDomain dom1 (Clock dom2) = DomEq dom1 dom2
type TryDomain t (Clock dom) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type TryDomain t (Clock dom) = 'Found dom
type ClocksCxt (Clock c1, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Signal pllLock Bool) = KnownDomain c1
type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13, KnownDomain c14)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13, KnownDomain c14, KnownDomain c15)
type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) Source # 
Instance details

Defined in Clash.Clocks

type ClocksCxt (Clock c1, Clock c2, Clock c3, Clock c4, Clock c5, Clock c6, Clock c7, Clock c8, Clock c9, Clock c10, Clock c11, Clock c12, Clock c13, Clock c14, Clock c15, Clock c16, Signal pllLock Bool) = (KnownDomain c1, KnownDomain c2, KnownDomain c3, KnownDomain c4, KnownDomain c5, KnownDomain c6, KnownDomain c7, KnownDomain c8, KnownDomain c9, KnownDomain c10, KnownDomain c11, KnownDomain c12, KnownDomain c13, KnownDomain c14, KnownDomain c15, KnownDomain c16)

freqCalc :: Double -> Integer Source #

Deprecated: Use hzToPeriod instead.

Calculate the period, in ps, given a frequency in Hz

i.e. to calculate the clock period for a circuit to run at 240 MHz we get

>>> freqCalc 240e6
4167

NB: This function is not synthesizable

periodToHz :: Natural -> Double Source #

Calculate the frequence in Hz, given the period in ps

i.e. to calculate the clock frequency of a clock with a period of 5000 ps:

>>> periodToHz 5000
2.0e8

NB: This function is not synthesizable NB: This function is lossy. I.e., hzToPeriod . periodToHz /= id.

hzToPeriod :: HasCallStack => Double -> Natural Source #

Calculate the period, in ps, given a frequency in Hz

i.e. to calculate the clock period for a circuit to run at 240 MHz we get

>>> hzToPeriod 240e6
4167

NB: This function is not synthesizable NB: This function is lossy. I.e., hzToPeriod . periodToHz /= id.

Synchronization primitive

unsafeSynchronizer Source #

Arguments

:: forall dom1 dom2 a. (KnownDomain dom1, KnownDomain dom2) 
=> Clock dom1

Clock of the incoming signal

-> Clock dom2

Clock of the outgoing signal

-> Signal dom1 a 
-> Signal dom2 a 

The unsafeSynchronizer function is a primitive that must be used to connect one clock domain to the other, and will be synthesized to a (bundle of) wire(s) in the eventual circuit. This function should only be used as part of a proper synchronization component, such as the following dual flip-flop synchronizer:

dualFlipFlop
  :: Clock domA
  -> Clock domB
  -> Enable domA
  -> Enable domB
  -> Bit
  -> Signal domA Bit
  -> Signal domB Bit
dualFlipFlop clkA clkB enA enB dflt =
  delay clkB enB dflt . delay clkB enB dflt . unsafeSynchronizer clkA clkB

The unsafeSynchronizer works in such a way that, given 2 clocks:

createDomain vSystem{vName="Dom7", vPeriod=7}

clk7 :: Clock Dom7
clk7 = clockGen

en7 :: Enable Dom7
en7 = enableGen

and

createDomain vSystem{vName="Dom2", vPeriod=2}

clk2 :: Clock Dom2
clk2 = clockGen

en2 :: Enable Dom2
en2 = enableGen

Oversampling followed by compression is the identity function plus 2 initial values:

delay clkB enB dflt $
unsafeSynchronizer clkA clkB $
delay clkA enA dflt $
unsafeSynchronizer clkB clkA $
delay clkB enB s

==

dflt :- dflt :- s

Something we can easily observe:

oversampling clkA clkB enA enB dflt =
  delay clkB enB dflt
    . unsafeSynchronizer clkA clkB
    . delay clkA enA dflt
almostId clkA clkB enA enB dflt =
  delay clkB enB dflt
    . unsafeSynchronizer clkA clkB
    . delay clkA enA dflt
    . unsafeSynchronizer clkB clkA
    . delay clkB enB dflt
>>> sampleN 37 (oversampling clk7 clk2 en7 en2 0 (fromList [(1::Int)..10]))
[0,0,1,1,1,2,2,2,2,3,3,3,4,4,4,4,5,5,5,6,6,6,6,7,7,7,8,8,8,8,9,9,9,10,10,10,10]
>>> sampleN 12 (almostId clk2 clk7 en2 en7 0 (fromList [(1::Int)..10]))
[0,0,1,2,3,4,5,6,7,8,9,10]

veryUnsafeSynchronizer Source #

Arguments

:: Int

Period of clock belonging to dom1

-> Int

Period of clock belonging to dom2

-> Signal dom1 a 
-> Signal dom2 a 

Same as unsafeSynchronizer, but with manually supplied clock periods.

Note: this unsafeSynchronizer is defined to be consistent with the vhdl and verilog implementations however as only synchronous signals are represented in Clash this cannot be done precisely and can lead to odd behaviour. For example, sample $ unsafeSynchronizer Dom2 Dom7 . unsafeSynchronizer Dom7 Dom2 $ fromList [0..10] > [0,4,4,4,7,7,7,7,11,11,11.. is quite different from the identity, sample $ fromList [0..10] > [0,1,2,3,4,5,6,7,8,9,10.. with values appearing from the "future".

Reset

data Reset (dom :: Domain) Source #

A reset signal belonging to a domain called dom.

The underlying representation of resets is Bool.

Instances

Instances details
type HasDomain dom1 (Reset dom2) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSpecificDomain

type HasDomain dom1 (Reset dom2) = DomEq dom1 dom2
type TryDomain t (Reset dom) Source # 
Instance details

Defined in Clash.Class.HasDomain.HasSingleDomain

type TryDomain t (Reset dom) = 'Found dom

unsafeToReset :: Signal dom Bool -> Reset dom Source #

unsafeToReset is unsafe. For asynchronous resets it is unsafe because it can introduce combinatorial loops. In case of synchronous resets it can lead to meta-stability issues in the presence of asynchronous resets.

NB: You probably want to use unsafeFromLowPolarity or unsafeFromHighPolarity.

unsafeFromReset :: Reset dom -> Signal dom Bool Source #

unsafeFromReset is unsafe because it can introduce:

For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.

NB: You probably want to use unsafeToLowPolarity or unsafeToHighPolarity.

unsafeToHighPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool Source #

Convert a reset to an active high reset. Has no effect if reset is already an active high reset. Is unsafe because it can introduce:

For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.

unsafeToLowPolarity :: forall dom. KnownDomain dom => Reset dom -> Signal dom Bool Source #

Convert a reset to an active low reset. Has no effect if reset is already an active low reset. It is unsafe because it can introduce:

For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.

unsafeFromHighPolarity Source #

Arguments

:: forall dom. KnownDomain dom 
=> Signal dom Bool

Reset signal that's True when active, and False when inactive.

-> Reset dom 

Interpret a signal of bools as an active high reset and convert it to a reset signal corresponding to the domain's setting.

For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.

unsafeFromLowPolarity Source #

Arguments

:: forall dom. KnownDomain dom 
=> Signal dom Bool

Reset signal that's False when active, and True when inactive.

-> Reset dom 

Interpret a signal of bools as an active low reset and convert it to a reset signal corresponding to the domain's setting.

For asynchronous resets it is unsafe because it can cause combinatorial loops. In case of synchronous resets it can lead to meta-stability in the presence of asynchronous resets.

convertReset :: forall domA domB. (KnownDomain domA, KnownDomain domB) => Clock domA -> Clock domB -> Reset domA -> Reset domB Source #

Convert between different types of reset, adding a synchronizer in case it needs to convert from an asynchronous to a synchronous reset.

resetSynchronizer :: forall dom. KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Reset dom Source #

Normally, asynchronous resets can be both asynchronously asserted and de-asserted. Asynchronous de-assertion can induce meta-stability in the component which is being reset. To ensure this doesn't happen, resetSynchronizer ensures that de-assertion of a reset happens synchronously. Assertion of the reset remains asynchronous.

Note that asynchronous assertion does not induce meta-stability in the component whose reset is asserted. However, when a component "A" in another clock or reset domain depends on the value of a component "B" being reset, then asynchronous assertion of the reset of component "B" can induce meta-stability in component "A". To prevent this from happening you need to use a proper synchronizer, for example one of the synchronizers in Clash.Explicit.Synchronizer

Example

Expand
topEntity
  :: Clock  System
  -> Reset  System
  -> Signal System Bit
  -> Signal System (BitVector 8)
topEntity clk rst key1 =
    let  (pllOut,pllStable) = altpll (SSymbol @"altpll50") clk rst
         rstSync            = resetSynchronizer pllOut (unsafeToHighPolarity pllStable)
    in   exposeClockResetEnable leds pllOut rstSync
  where
    key1R  = isRising 1 key1
    leds   = mealy blinkerT (1, False, 0) key1R

holdReset Source #

Arguments

:: forall dom n. KnownDomain dom 
=> Clock dom 
-> Enable dom

Global enable

-> SNat n

Hold for n cycles, counting from the moment the incoming reset signal becomes deasserted.

-> Reset dom

Reset to extend

-> Reset dom 

Hold reset for a number of cycles relative to an incoming reset signal.

Example:

>>> let sampleWithReset = sampleN 8 . unsafeToHighPolarity
>>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (resetGenN (SNat @3)))
[True,True,True,True,True,False,False,False]

holdReset holds the reset for an additional 2 clock cycles for a total of 5 clock cycles where the reset is asserted. holdReset also works on intermediate assertions of the reset signal:

>>> let rst = fromList [True, False, False, False, True, False, False, False]
>>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (unsafeFromHighPolarity rst))
[True,True,True,False,True,True,True,False]

Basic circuit functions

enable :: Enable dom -> Signal dom Bool -> Enable dom Source #

Merge enable signal with signal of bools by applying the boolean AND operation.

dflipflop :: (KnownDomain dom, NFDataX a) => Clock dom -> Signal dom a -> Signal dom a Source #

Special version of delay that doesn't take enable signals of any kind. Initial value will be undefined.

delay Source #

Arguments

:: (KnownDomain dom, NFDataX a) 
=> Clock dom

Clock

-> Enable dom

Global enable

-> a

Initial value

-> Signal dom a 
-> Signal dom a 

"delay clk s" delays the values in Signal s for once cycle, the value at time 0 is dflt.

>>> sampleN 3 (delay systemClockGen enableGen 0 (fromList [1,2,3,4]))
[0,1,2]

delayMaybe Source #

Arguments

:: (KnownDomain dom, NFDataX a) 
=> Clock dom

Clock

-> Enable dom

Global enable

-> a

Initial value

-> Signal dom (Maybe a) 
-> Signal dom a 

Version of delay that only updates when its third argument is a Just value.

>>> let input = fromList [Just 1, Just 2, Nothing, Nothing, Just 5, Just 6, Just (7::Int)]
>>> sampleN 7 (delayMaybe systemClockGen enableGen 0 input)
[0,1,2,2,2,5,6]

delayEn Source #

Arguments

:: (KnownDomain dom, NFDataX a) 
=> Clock dom

Clock

-> Enable dom

Global enable

-> a

Initial value

-> Signal dom Bool

Enable

-> Signal dom a 
-> Signal dom a 

Version of delay that only updates when its third argument is asserted.

>>> let input = fromList [1,2,3,4,5,6,7::Int]
>>> let enable = fromList [True,True,False,False,True,True,True]
>>> sampleN 7 (delayEn systemClockGen enableGen 0 enable input)
[0,1,2,2,2,5,6]

register Source #

Arguments

:: (KnownDomain dom, NFDataX a) 
=> Clock dom

clock

-> Reset dom

Reset, register outputs the reset value when the reset is active

-> Enable dom

Global enable

-> a

Reset value. If the domain has initial values enabled, the reset value will also be the initial value.

-> Signal dom a 
-> Signal dom a 

"register clk rst i s" delays the values in Signal s for one cycle, and sets the value to i the moment the reset becomes False.

>>> sampleN 5 (register systemClockGen resetGen enableGen 8 (fromList [1,1,2,3,4]))
[8,8,1,2,3]

regMaybe Source #

Arguments

:: (KnownDomain dom, NFDataX a) 
=> Clock dom

Clock

-> Reset dom

Reset, regMaybe outputs the reset value when the reset value is active

-> Enable dom

Global enable

-> a

Reset value. If the domain has initial values enabled, the reset value will also be the initial value.

-> Signal dom (Maybe a) 
-> Signal dom a 

Version of register that only updates its content when its fourth argument is a Just value. So given:

sometimes1 clk rst en = s where
  s = register clk rst en Nothing (switch <$> s)

  switch Nothing = Just 1
  switch _       = Nothing

countSometimes clk rst en = s where
  s     = regMaybe clk rst en 0 (plusM (pure <$> s) (sometimes1 clk rst en))
  plusM = liftA2 (liftA2 (+))

We get:

>>> sampleN 9 (sometimes1 systemClockGen resetGen enableGen)
[Nothing,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1]
>>> sampleN 9 (count systemClockGen resetGen enableGen)
[0,0,0,1,1,2,2,3,3]

regEn Source #

Arguments

:: (KnownDomain dom, NFDataX a) 
=> Clock dom

Clock

-> Reset dom

Reset, regEn outputs the reset value when the reset value is active

-> Enable dom

Global enable

-> a

Reset value. If the domain has initial values enabled, the reset value will also be the initial value.

-> Signal dom Bool

Enable signal

-> Signal dom a 
-> Signal dom a 

Version of register that only updates its content when its fourth argument is asserted. So given:

oscillate clk rst en = let s = register clk rst en False (not <$> s) in s
count clk rst en     = let s = 'regEn clk rst en 0 (oscillate clk rst en) (s + 1) in s

We get:

>>> sampleN 9 (oscillate systemClockGen resetGen enableGen)
[False,False,True,False,True,False,True,False,True]
>>> sampleN 9 (count systemClockGen resetGen enableGen)
[0,0,0,1,1,2,2,3,3]

mux :: Applicative f => f Bool -> f a -> f a -> f a Source #

The above type is a generalization for:

mux :: Signal Bool -> Signal a -> Signal a -> Signal a

A multiplexer. Given "mux b t f", output t when b is True, and f when b is False.

Simulation and testbench functions

clockGen :: KnownDomain dom => Clock dom Source #

Clock generator for simulations. Do not use this clock generator for for the testBench function, use tbClockGen instead.

To be used like:

clkSystem = clockGen @System

See DomainConfiguration for more information on how to use synthesis domains.

resetGen :: forall dom. KnownDomain dom => Reset dom Source #

Reset generator

To be used like:

rstSystem = resetGen @System

See tbClockGen for example usage.

resetGenN Source #

Arguments

:: forall dom n. (KnownDomain dom, 1 <= n) 
=> SNat n

Number of initial cycles to hold reset high

-> Reset dom 

Generate reset that's asserted for the first n cycles.

To be used like:

rstSystem5 = resetGen System (SNat 5)

Example usage:

>>> sampleN 7 (unsafeToHighPolarity (resetGenN @System (SNat @3)))
[True,True,True,False,False,False,False]

systemClockGen :: Clock System Source #

Clock generator for the System clock domain.

NB: should only be used for simulation, and not for the testBench function. For the testBench function, used tbSystemClockGen

systemResetGen :: Reset System Source #

Reset generator for the System clock domain.

NB: should only be used for simulation or the testBench function.

Example

Expand
topEntity :: Vec 2 (Vec 3 (Unsigned 8)) -> Vec 6 (Unsigned 8)
topEntity = concat

testBench :: Signal System Bool
testBench = done
  where
    testInput      = pure ((1 :> 2 :> 3 :> Nil) :> (4 :> 5 :> 6 :> Nil) :> Nil)
    expectedOutput = outputVerifier' ((1:>2:>3:>4:>5:>6:>Nil):>Nil)
    done           = exposeClockResetEnable (expectedOutput (topEntity $ testInput)) clk rst
    clk            = tbSystemClockGen (not <$> done)
    rst            = systemResetGen

Boolean connectives

(.&&.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 3 Source #

The above type is a generalization for:

(.&&.) :: Signal Bool -> Signal Bool -> Signal Bool

It is a version of (&&) that returns a Signal of Bool

(.||.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 2 Source #

The above type is a generalization for:

(.||.) :: Signal Bool -> Signal Bool -> Signal Bool

It is a version of (||) that returns a Signal of Bool

Product/Signal isomorphism

class Bundle a where Source #

Isomorphism between a Signal of a product type (e.g. a tuple) and a product type of Signals.

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) @

Minimal complete definition

Nothing

Associated Types

type Unbundled (dom :: Domain) a = res | res -> dom a Source #

type Unbundled dom a = Signal dom a

Methods

bundle :: Unbundled dom a -> Signal dom a Source #

Example:

bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)

However:

bundle :: Signal dom Bit -> Signal dom Bit

default bundle :: Signal dom a ~ Unbundled dom a => Unbundled dom a -> Signal dom a Source #

unbundle :: Signal dom a -> Unbundled dom a Source #

Example:

unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)

However:

unbundle :: Signal dom Bit -> Signal dom Bit

default unbundle :: Unbundled dom a ~ Signal dom a => Signal dom a -> Unbundled dom a Source #

Instances

Instances details
Bundle Bool Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Bool = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Bool -> Signal dom Bool Source #

unbundle :: forall (dom :: Domain). Signal dom Bool -> Unbundled dom Bool Source #

Bundle Double Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Double = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Double -> Signal dom Double Source #

unbundle :: forall (dom :: Domain). Signal dom Double -> Unbundled dom Double Source #

Bundle Float Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Float = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Float -> Signal dom Float Source #

unbundle :: forall (dom :: Domain). Signal dom Float -> Unbundled dom Float Source #

Bundle Int Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Int = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Int -> Signal dom Int Source #

unbundle :: forall (dom :: Domain). Signal dom Int -> Unbundled dom Int Source #

Bundle Integer Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Integer = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Integer -> Signal dom Integer Source #

unbundle :: forall (dom :: Domain). Signal dom Integer -> Unbundled dom Integer Source #

Bundle () Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom () = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom () -> Signal dom () Source #

unbundle :: forall (dom :: Domain). Signal dom () -> Unbundled dom () Source #

Bundle Bit Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Bit = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Bit -> Signal dom Bit Source #

unbundle :: forall (dom :: Domain). Signal dom Bit -> Unbundled dom Bit Source #

Bundle EmptyTuple Source #

See https://github.com/clash-lang/clash-compiler/pull/539/commits/94b0bff5770aa4961e04ddce2515130df3fc7863 and documentation for TaggedEmptyTuple.

Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom EmptyTuple = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom EmptyTuple -> Signal dom EmptyTuple Source #

unbundle :: forall (dom :: Domain). Signal dom EmptyTuple -> Unbundled dom EmptyTuple Source #

Bundle (Maybe a) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Maybe a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Maybe a) -> Signal dom (Maybe a) Source #

unbundle :: forall (dom :: Domain). Signal dom (Maybe a) -> Unbundled dom (Maybe a) Source #

Bundle (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (BitVector n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (BitVector n) -> Signal dom (BitVector n) Source #

unbundle :: forall (dom :: Domain). Signal dom (BitVector n) -> Unbundled dom (BitVector n) Source #

Bundle (Index n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Index n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Index n) -> Signal dom (Index n) Source #

unbundle :: forall (dom :: Domain). Signal dom (Index n) -> Unbundled dom (Index n) Source #

Bundle (Unsigned n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Unsigned n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Unsigned n) -> Signal dom (Unsigned n) Source #

unbundle :: forall (dom :: Domain). Signal dom (Unsigned n) -> Unbundled dom (Unsigned n) Source #

Bundle (Signed n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Signed n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Signed n) -> Signal dom (Signed n) Source #

unbundle :: forall (dom :: Domain). Signal dom (Signed n) -> Unbundled dom (Signed n) Source #

Bundle (Either a b) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Either a b) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Either a b) -> Signal dom (Either a b) Source #

unbundle :: forall (dom :: Domain). Signal dom (Either a b) -> Unbundled dom (Either a b) Source #

Bundle (a1, a2) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2) -> Signal dom (a1, a2) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2) -> Unbundled dom (a1, a2) Source #

KnownNat n => Bundle (Vec n a) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Vec n a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Vec n a) -> Signal dom (Vec n a) Source #

unbundle :: forall (dom :: Domain). Signal dom (Vec n a) -> Unbundled dom (Vec n a) Source #

KnownNat d => Bundle (RTree d a) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (RTree d a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (RTree d a) -> Signal dom (RTree d a) Source #

unbundle :: forall (dom :: Domain). Signal dom (RTree d a) -> Unbundled dom (RTree d a) Source #

Bundle (a1, a2, a3) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3) -> Signal dom (a1, a2, a3) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3) -> Unbundled dom (a1, a2, a3) Source #

Bundle (Fixed rep int frac) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Fixed rep int frac) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Fixed rep int frac) -> Signal dom (Fixed rep int frac) Source #

unbundle :: forall (dom :: Domain). Signal dom (Fixed rep int frac) -> Unbundled dom (Fixed rep int frac) Source #

Bundle ((f :*: g) a) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom ((f :*: g) a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom ((f :*: g) a) -> Signal dom ((f :*: g) a) Source #

unbundle :: forall (dom :: Domain). Signal dom ((f :*: g) a) -> Unbundled dom ((f :*: g) a) Source #

Bundle (a1, a2, a3, a4) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4) -> Signal dom (a1, a2, a3, a4) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4) -> Unbundled dom (a1, a2, a3, a4) Source #

Bundle (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5) -> Signal dom (a1, a2, a3, a4, a5) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5) -> Unbundled dom (a1, a2, a3, a4, a5) Source #

Bundle (a1, a2, a3, a4, a5, a6) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6) -> Signal dom (a1, a2, a3, a4, a5, a6) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6) -> Unbundled dom (a1, a2, a3, a4, a5, a6) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7) -> Signal dom (a1, a2, a3, a4, a5, a6, a7) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source #

data EmptyTuple Source #

Constructors

EmptyTuple 

Instances

Instances details
Bundle EmptyTuple Source #

See https://github.com/clash-lang/clash-compiler/pull/539/commits/94b0bff5770aa4961e04ddce2515130df3fc7863 and documentation for TaggedEmptyTuple.

Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom EmptyTuple = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom EmptyTuple -> Signal dom EmptyTuple Source #

unbundle :: forall (dom :: Domain). Signal dom EmptyTuple -> Unbundled dom EmptyTuple Source #

Bundle EmptyTuple Source #

See https://github.com/clash-lang/clash-compiler/pull/539/commits/94b0bff5770aa4961e04ddce2515130df3fc7863 and documentation for TaggedEmptyTuple.

Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d EmptyTuple = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d EmptyTuple -> DSignal dom d EmptyTuple Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d EmptyTuple -> Unbundled dom d EmptyTuple Source #

type Unbundled dom EmptyTuple Source # 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled dom d EmptyTuple Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

data TaggedEmptyTuple (dom :: Domain) Source #

Helper type to emulate the "old" behavior of Bundle's unit instance. I.e., the instance for Bundle () used to be defined as:

class Bundle () where bundle :: () -> Signal domain () unbundle :: Signal domain () -> ()

In order to have sensible type inference, the Bundle class specifies that the argument type of bundle should uniquely identify the result type, and vice versa for unbundle. The type signatures in the snippet above don't though, as () doesn't uniquely map to a specific domain. In other words, domain should occur in both the argument and result of both functions.

TaggedEmptyTuple tackles this by carrying the domain in its type. The bundle and unbundle instance now looks like:

class Bundle EmptyTuple where bundle :: TaggedEmptyTuple domain -> Signal domain EmptyTuple unbundle :: Signal domain EmptyTuple -> TaggedEmptyTuple domain

domain is now mentioned both the argument and result for both bundle and unbundle.

Constructors

TaggedEmptyTuple 

Simulation functions (not synthesizable)

simulate :: (NFDataX a, NFDataX b) => (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] Source #

Simulate a (Signal a -> Signal b) function given a list of samples of type a

>>> simulate (register systemClockGen resetGen enableGen 8) [1, 1, 2, 3]
[8,8,1,2,3...
...

NB: This function is not synthesizable

simulateB Source #

Arguments

:: (Bundle a, Bundle b, NFDataX a, NFDataX b) 
=> (Unbundled dom1 a -> Unbundled dom2 b)

The function we want to simulate

-> [a]

Input samples

-> [b] 

Simulate a (Unbundled a -> Unbundled b) function given a list of samples of type a

>>> simulateB (unbundle . register systemClockGen resetGen enableGen (8,8) . bundle) [(1,1), (1,1), (2,2), (3,3)] :: [(Int,Int)]
[(8,8),(8,8),(1,1),(2,2),(3,3)...
...

NB: This function is not synthesizable

simulateWithReset Source #

Arguments

:: forall dom a b m. (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) 
=> SNat m

Number of cycles to assert the reset

-> a

Reset value

-> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b)

Circuit to simulate

-> [a] 
-> [b] 

Same as simulate, but with the reset line asserted for n cycles. Similar to simulate, simulateWithReset will drop the output values produced while the reset is asserted. While the reset is asserted, the first value from [a] is fed to the circuit.

simulateWithResetN Source #

Arguments

:: (KnownDomain dom, NFDataX a, NFDataX b, 1 <= m) 
=> SNat m

Number of cycles to assert the reset

-> a

Reset value

-> Int

Number of cycles to simulate (excluding cycle spent in reset)

-> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a -> Signal dom b)

Circuit to simulate

-> [a] 
-> [b] 

Same as simulateWithReset, but only sample the first Int output values.

lazy versions

simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b] Source #

Simulate a (Signal a -> Signal b) function given a list of samples of type a

>>> simulate (register systemClockGen resetGen enableGen 8) [1, 1, 2, 3]
[8,8,1,2,3...
...

NB: This function is not synthesizable

simulateB_lazy Source #

Arguments

:: (Bundle a, Bundle b) 
=> (Unbundled dom1 a -> Unbundled dom2 b)

The function we want to simulate

-> [a]

Input samples

-> [b] 

Lazily simulate a (Unbundled a -> Unbundled b) function given a list of samples of type a

>>> simulateB (unbundle . register systemClockGen resetGen enableGen (8,8) . bundle) [(1,1), (1,1), (2,2), (3,3)] :: [(Int,Int)]
[(8,8),(8,8),(1,1),(2,2),(3,3)...
...

NB: This function is not synthesizable

List <-> Signal conversion (not synthesizable)

sample :: (Foldable f, NFDataX a) => f a -> [a] Source #

The above type is a generalization for:

sample :: Signal a -> [a]

Get an infinite list of samples from a Signal

The elements in the list correspond to the values of the Signal at consecutive clock cycles

sample s == [s0, s1, s2, s3, ...

NB: This function is not synthesizable

sampleN :: (Foldable f, NFDataX a) => Int -> f a -> [a] Source #

The above type is a generalization for:

sampleN :: Int -> Signal a -> [a]

Get a list of n samples from a Signal

The elements in the list correspond to the values of the Signal at consecutive clock cycles

sampleN 3 s == [s0, s1, s2]

NB: This function is not synthesizable

sampleWithReset Source #

Arguments

:: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) 
=> SNat m

Number of cycles to assert the reset

-> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a)

Signal to sample

-> [a] 

Get a list of samples from a Signal, while asserting the reset line for n clock cycles. sampleWithReset does not return the first n cycles, i.e., when the reset is asserted.

NB: This function is not synthesizable

sampleWithResetN Source #

Arguments

:: forall dom a m. (KnownDomain dom, NFDataX a, 1 <= m) 
=> SNat m

Number of cycles to assert the reset

-> Int

Number of samples to produce

-> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Signal dom a)

Signal to sample

-> [a] 

Get a fine list of m samples from a Signal, while asserting the reset line for n clock cycles. sampleWithReset does not return the first n cycles, i.e., while the reset is asserted.

NB: This function is not synthesizable

fromList :: NFDataX a => [a] -> Signal dom a Source #

Create a Signal from a list

Every element in the list will correspond to a value of the signal for one clock cycle.

>>> sampleN 2 (fromList [1,2,3,4,5])
[1,2]

NB: This function is not synthesizable

fromListWithReset :: forall dom a. (KnownDomain dom, NFDataX a) => Reset dom -> a -> [a] -> Signal dom a Source #

Like fromList, but resets on reset and has a defined reset value.

>>> let rst = unsafeFromHighPolarity (fromList [True, True, False, False, True, False])
>>> let res = fromListWithReset @System rst Nothing [Just 'a', Just 'b', Just 'c']
>>> sampleN 6 res
[Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']

NB: This function is not synthesizable

lazy versions

sample_lazy :: Foldable f => f a -> [a] Source #

The above type is a generalization for:

sample :: Signal a -> [a]

Get an infinite list of samples from a Signal

The elements in the list correspond to the values of the Signal at consecutive clock cycles

sample s == [s0, s1, s2, s3, ...

NB: This function is not synthesizable

sampleN_lazy :: Foldable f => Int -> f a -> [a] Source #

The above type is a generalization for:

sampleN :: Int -> Signal a -> [a]

Get a list of n samples from a Signal

The elements in the list correspond to the values of the Signal at consecutive clock cycles

sampleN 3 s == [s0, s1, s2]

NB: This function is not synthesizable

fromList_lazy :: [a] -> Signal dom a Source #

Create a Signal from a list

Every element in the list will correspond to a value of the signal for one clock cycle.

>>> sampleN 2 (fromList [1,2,3,4,5] :: Signal System Int)
[1,2]

NB: This function is not synthesizable

QuickCheck combinators

testFor :: Foldable f => Int -> f Bool -> Property Source #

The above type is a generalization for:

testFor :: Int -> Signal Bool -> Property

testFor n s tests the signal s for n cycles.

NB: This function is not synthesizable

Type classes

Eq-like

(.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 Source #

The above type is a generalization for:

(.==.) :: Eq a => Signal a -> Signal a -> Signal Bool

It is a version of (==) that returns a Signal of Bool

(./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 Source #

The above type is a generalization for:

(./=.) :: Eq a => Signal a -> Signal a -> Signal Bool

It is a version of (/=) that returns a Signal of Bool

Ord-like

(.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source #

The above type is a generalization for:

(.<.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (<) that returns a Signal of Bool

(.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source #

The above type is a generalization for:

(.<=.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (<=) that returns a Signal of Bool

(.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source #

The above type is a generalization for:

(.>=.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (>=) that returns a Signal of Bool

(.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source #

The above type is a generalization for:

(.>.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (>) that returns a Signal of Bool

Bisignal functions

veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n Source #

Converts the out part of a BiSignal to an 'in' part. In simulation it checks whether multiple components are writing and will error accordingly. Make sure this is only called ONCE for every BiSignal.

readFromBiSignal Source #

Arguments

:: (HasCallStack, BitPack a) 
=> BiSignalIn ds d (BitSize a)

A BiSignalIn with a number of bits needed to represent a

-> Signal d a 

Read the value from an inout port

writeToBiSignal Source #

Arguments

:: (HasCallStack, BitPack a) 
=> BiSignalIn ds d (BitSize a) 
-> Signal d (Maybe a)

Value to write

  • Just a writes an a value
  • Nothing puts the port in a high-impedance state
-> BiSignalOut ds d (BitSize a) 

Write to an inout port

mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m Source #

Combine several inout signals into one.