clash-prelude-1.4.6: Clash: a functional hardware description language - Prelude library
Copyright(C) 2013-2016 University of Twente
2016-2019 Myrtle Software Ltd
2017 Google Inc.
2021 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • ScopedTypeVariables
  • BangPatterns
  • ViewPatterns
  • GADTs
  • GADTSyntax
  • ConstraintKinds
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveLift
  • DerivingStrategies
  • FlexibleContexts
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • MagicHash
  • KindSignatures
  • TupleSections
  • RankNTypes
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Signal

Description

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. More specifically, a domain looks like:

DomainConfiguration
  { _name :: Domain
  -- ^ Domain name
  , _period :: Nat
  -- ^ Clock period in ps
  , _activeEdge :: ActiveEdge
  -- ^ Active edge of the clock
  , _resetKind :: ResetKind
  -- ^ Whether resets are synchronous (edge-sensitive) or asynchronous (level-sensitive)
  , _initBehavior :: InitBehavior
  -- ^ Whether the initial (or "power up") value of memory elements is
  -- unknown/undefined, or configurable to a specific value
  , _resetPolarity :: 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 an implementation System with some common options chosen:

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. Memory elements respond to the rising edge of the clock, asynchronously to changes in their resets, 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: Whether System has good defaults depends on your target platform. Check out IntelSystem and XilinxSystem too!
Synopsis

Synchronous signals

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!

Signals have the type role

>>> :i Signal
type role Signal nominal representational
...

as it is safe to coerce the underlying value of a signal, but not safe to coerce a signal between different synthesis domains.

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

AssertionValue dom (Signal dom Bool) Source #

Stream of booleans, originating from a circuit

Instance details

Defined in Clash.Verification.Internal

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. BiSignalIn has the type role

>>> :i BiSignalIn
type role BiSignalIn nominal nominal nominal
...

as it is not safe to coerce the default behaviour, synthesis domain or width of the data in the signal.

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.

BiSignalOut has the type role

>>> :i BiSignalOut
type role BiSignalOut nominal nominal nominal
...

as it is not safe to coerce the default behaviour, synthesis domain or width of the data in the signal.

Instances

Instances details
Semigroup (BiSignalOut defaultState dom n) Source #

NB Not synthesizable

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

sameDomain :: forall (domA :: Domain) (domB :: Domain). (KnownDomain domA, KnownDomain domB) => Maybe (domA :~: domB) Source #

We either get evidence that this function was instantiated with the same domains, or Nothing.

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
SDomainConfiguration (SSymbol @"System") (SNat @10000) SRising SAsynchronous SDefined SActiveHigh

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

Read 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.4.6-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

Read 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.4.6-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

Read 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.4.6-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

Read 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.4.6-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 ~ 'Synchronous) => ...

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 intact 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 intact 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 intact 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}

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

It will also make System10 an instance of KnownDomain.

If either identifier is already in scope it will not be generated a second time. Note: This can be useful for example when documenting a new domain:

-- | Here is some documentation for CustomDomain
type CustomDomain = ("CustomDomain" :: Domain)

-- | Here is some documentation for vCustomDomain
createDomain vSystem{vName="CustomDomain"}

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

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)

periodToHz :: Natural -> Ratio Natural 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
200000000 % 1

NB: This function is not synthesizable

hzToPeriod :: HasCallStack => Ratio Natural -> 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
4166

NB: This function is not synthesizable

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

Synchronization primitive

unsafeSynchronizer :: forall dom1 dom2 a. (HiddenClock dom1, HiddenClock dom2) => Signal dom1 a -> Signal dom2 a Source #

Implicit version of unsafeSynchronizer.

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. (HiddenClock domA, HiddenClock 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 Source #

Arguments

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

Warning: this argument will be removed in future versions of Clash.

-> Reset dom 

The resetSynchronizer will synchronize an incoming reset according to whether the domain is synchronous or asynchronous.

For asynchronous resets this synchronizer ensures the reset will only be de-asserted synchronously but it can still be asserted asynchronously. The reset assert is immediate, but reset de-assertion is delayed by two cycles.

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.

For synchronous resets this function ensures that the reset is asserted and de-asserted synchronously. Both the assertion and de-assertion of the reset are delayed by two cycles.

Example 1

Expand

The circuit below detects a rising bit (i.e., a transition from 0 to 1) in a given argument. It takes a reset that is not synchronized to any of the other incoming signals and synchronizes it using resetSynchronizer.

topEntity
  :: Clock  System
  -> Reset  System
  -> Enable System
  -> Signal System Bit
  -> Signal System (BitVector 8)
topEntity clk asyncRst ena key1 =
  withClockResetEnable clk rst ena leds
 where
  rst   = resetSynchronizer clk asyncRst ena
  key1R = isRising 1 key1
  leds  = mealy blinkerT (1, False, 0) key1R

Example 2

Expand

Similar to Example 1 this circuit detects a rising bit (i.e., a transition from 0 to 1) in a given argument. It takes a clock that is not stable yet and a reset singal that is not synchronized to any other signals. It stabalizes the clock and then synchronizes the reset signal.

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

Implementation details

Expand

resetSynchronizer implements the following circuit for asynchronous domains:

                                  rst
  --------------------------------------+
                      |                 |
                 +----v----+       +----v----+
    deasserted   |         |       |         |
  --------------->         +------->         +-------->
                 |         |       |         |
             +---|>        |   +---|>        |
             |   |         |   |   |         |
             |   +---------+   |   +---------+
     clk     |                 |
  -----------------------------+

This corresponds to figure 3d at https://www.embedded.com/asynchronous-reset-synchronization-and-distribution-challenges-and-solutions/

For synchronous domains two sequential dflipflops are used:

                 +---------+       +---------+
    rst          |         |       |         |
  --------------->         +------->         +-------->
                 |         |       |         |
             +---|>        |   +---|>        |
             |   |         |   |   |         |
             |   +---------+   |   +---------+
     clk     |                 |
  -----------------------------+

resetGlitchFilter Source #

Arguments

:: forall dom glitchlessPeriod n. (KnownDomain dom, glitchlessPeriod ~ (n + 1)) 
=> SNat glitchlessPeriod

Consider a reset signal to be properly asserted after having seen the reset asserted for glitchlessPeriod cycles straight.

-> Clock dom 
-> Reset dom 
-> Reset dom 

Filter glitches from reset signals by only triggering a reset after it has been asserted for glitchlessPeriod cycles. It will then stay asserted for as long as the given reset was asserted consecutively.

If synthesized on a domain with initial values, resetGlitchFilter will output an asserted reset for glitchlessPeriod cycles (plus any cycles added by the given reset). If initial values can't be used, it will only output defined reset values after glitchlessPeriod cycles.

Example 1

Expand
>>> let sampleResetN n = sampleN n . unsafeToHighPolarity
>>> let resetFromList = unsafeFromHighPolarity . fromList
>>> let rst = resetFromList [True, True, False, False, True, False, False, True, True, False, True]
>>> sampleResetN 12 (resetGlitchFilter d2 systemClockGen rst)
[True,True,True,True,False,False,False,False,False,True,True,False]

holdReset Source #

Arguments

:: forall dom m. HiddenClockResetEnable dom 
=> SNat m

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

-> Reset dom 

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

Example:

>>> sampleN @System 8 (unsafeToHighPolarity (holdReset (SNat @2)))
[True,True,True,False,False,False,False,False]

holdReset holds the reset for an additional 2 clock cycles for a total of 3 clock cycles where the reset is asserted.

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.

Hidden clock, reset, and enable arguments

Clocks, resets and enables are by default implicitly routed to their components. You can see from the type of a component whether it has hidden clock, reset or enable arguments:

It has a hidden clock when it has a:

f :: HiddenClock dom => ...

Constraint.

Or it has a hidden reset when it has a:

g :: HiddenReset dom => ...

Constraint.

Or it has a hidden enable when it has a:

g :: HiddenEnable dom => ...

Constraint.

Or it has a hidden clock argument, a hidden reset argument and a hidden enable argument when it has a:

h :: HiddenClockResetEnable dom  => ..

Constraint.

Given a component with explicit clock, reset and enable arguments, you can turn them into hidden arguments using hideClock, hideReset, and hideEnable. So given a:

f :: Clock dom -> Reset dom -> Enable dom -> Signal dom a -> ...

You hide the clock and reset arguments by:

-- g :: HiddenClockResetEnable dom  => Signal dom a -> ...
g = hideClockResetEnable f

Or, alternatively, by:

-- h :: HiddenClockResetEnable dom  => Signal dom a -> ...
h = f hasClock hasReset hasEnable

Assigning explicit clock, reset and enable arguments to hidden clocks, resets and enables

Given a component:

f :: HiddenClockResetEnable dom
  => Signal dom Int
  -> Signal dom Int

which has hidden clock, reset and enable arguments, we expose those hidden arguments so that we can explicitly apply them:

-- g :: Clock dom -> Reset dom -> Enable dom -> Signal dom Int -> Signal dom Int
g = exposeClockResetEnable f

or, alternatively, by:

-- h :: Clock dom -> Reset dom -> Enable dom -> Signal dom Int -> Signal dom Int
h clk rst en = withClockResetEnable clk rst en f

Similarly, there are exposeClock, exposeReset and exposeEnable to just expose the hidden clock, the hidden reset or the hidden enable argument.

You will need to explicitly apply clocks and resets when you want to use components such as PLLs and resetSynchronizer:

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) enableGen
    in   exposeClockResetEnable leds pllOut rstSync enableGen
  where
    key1R  = isRising 1 key1
    leds   = mealy blinkerT (1, False, 0) key1R

or, using the alternative method:

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) enableGen
    in   withClockResetEnable pllOut rstSync enableGen leds
  where
    key1R  = isRising 1 key1
    leds   = mealy blinkerT (1, False, 0) key1R

Hidden clock

type HiddenClock dom = (Hidden (HiddenClockName dom) (Clock dom), KnownDomain dom) Source #

A constraint that indicates the component has a hidden Clock

Click here to read more about hidden clocks, resets, and enables

hideClock Source #

Arguments

:: forall dom r. HiddenClock dom 
=> (Clock dom -> r)

Function whose clock argument you want to hide

-> r 

Hide the Clock argument of a component, so it can be routed implicitly.

Click here to read more about hidden clocks, resets, and enables

exposeClock Source #

Arguments

:: forall dom r. WithSingleDomain dom r 
=> (HiddenClock dom => r)

The component with a hidden clock

-> KnownDomain dom => Clock dom -> r

The component with its clock argument exposed

Expose a hidden Clock argument of a component, so it can be applied explicitly.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenClock dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenClock dom => Signal dom a -> Signal dom a

If you want to expose a clock of a component working on multiple domains (such as the first example), use exposeSpecificClock.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = exposeClock reg clockGen
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force exposeClock to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = exposeClock @System reg clockGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

withClock Source #

Arguments

:: forall dom r. WithSingleDomain dom r 
=> KnownDomain dom 
=> Clock dom

The Clock we want to connect

-> (HiddenClock dom => r)

The function with a hidden Clock argument

-> r 

Connect an explicit Clock to a function with a hidden Clock.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenClock dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenClock dom => Signal dom a -> Signal dom a

If you want to connect a clock to a component working on multiple domains (such as the first example), use withSpecificClock.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = withClock clockGen reg
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force withClock to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = withClock @System clockGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

exposeSpecificClock Source #

Arguments

:: forall dom r. WithSpecificDomain dom r 
=> (HiddenClock dom => r)

The component with a hidden clock

-> KnownDomain dom => Clock dom -> r

The component with its clock argument exposed

Expose a hidden Clock argument of a component, so it can be applied explicitly. This function can be used on components with multiple domains. As opposed to exposeClock, callers should explicitly state what the clock domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

exposeSpecificClock can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = exposeSpecificClock @System reg clockGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = exposeSpecificClock @dom reg clockGen

withSpecificClock Source #

Arguments

:: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) 
=> Clock dom

The Clock we want to connect

-> (HiddenClock dom => r)

The function with a hidden Clock argument

-> r 

Connect an explicit Clock to a function with a hidden Clock. This function can be used on components with multiple domains. As opposed to withClock, callers should explicitly state what the clock domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

withSpecificClock can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = withSpecificClock @System clockGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = withSpecificClock @dom clockGen reg

hasClock :: forall dom. HiddenClock dom => Clock dom Source #

Connect a hidden Clock to an argument where a normal Clock argument was expected.

Click here to read more about hidden clocks, resets, and enables

Hidden reset

type HiddenReset dom = (Hidden (HiddenResetName dom) (Reset dom), KnownDomain dom) Source #

A constraint that indicates the component needs a Reset

Click here to read more about hidden clocks, resets, and enables

hideReset Source #

Arguments

:: forall dom r. HiddenReset dom 
=> (Reset dom -> r)

Component whose reset argument you want to hide

-> r 

Hide the Reset argument of a component, so it can be routed implicitly.

Click here to read more about hidden clocks, resets, and enables

exposeReset Source #

Arguments

:: forall dom r. WithSingleDomain dom r 
=> (HiddenReset dom => r)

The component with a hidden reset

-> KnownDomain dom => Reset dom -> r

The component with its reset argument exposed

Expose a hidden Reset argument of a component, so it can be applied explicitly.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenReset dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenReset dom => Signal dom a -> Signal dom a

If you want to expose a reset of a component working on multiple domains (such as the first example), use exposeSpecificReset.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = exposeReset reg resetGen
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force exposeReset to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = exposeReset @System reg resetGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

withReset Source #

Arguments

:: forall dom r. WithSingleDomain dom r 
=> KnownDomain dom 
=> Reset dom

The Reset we want to connect

-> (HiddenReset dom => r)

The function with a hidden Reset argument

-> r 

Connect an explicit Reset to a function with a hidden Reset.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenReset dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenReset dom => Signal dom a -> Signal dom a

If you want to connect a reset to a component working on multiple domains (such as the first example), use withSpecificReset.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = withReset resetGen reg
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force withReset to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = withReset @System resetGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

exposeSpecificReset Source #

Arguments

:: forall dom r. WithSpecificDomain dom r 
=> (HiddenReset dom => r)

The component with a hidden reset

-> KnownDomain dom => Reset dom -> r

The component with its reset argument exposed

Expose a hidden Reset argument of a component, so it can be applied explicitly. This function can be used on components with multiple domains. As opposed to exposeReset, callers should explicitly state what the reset domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

exposeSpecificReset can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = exposeSpecificReset @System reg resetGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = exposeSpecificReset @dom reg resetGen

withSpecificReset Source #

Arguments

:: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) 
=> Reset dom

The Reset we want to connect

-> (HiddenReset dom => r)

The function with a hidden Reset argument

-> r 

Connect an explicit Reset to a function with a hidden Reset. This function can be used on components with multiple domains. As opposed to withReset, callers should explicitly state what the reset domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

withSpecificReset can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = withSpecificReset @System resetGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = withSpecificReset @dom resetGen reg

hasReset :: forall dom. HiddenReset dom => Reset dom Source #

Connect a hidden Reset to an argument where a normal Reset argument was expected.

Click here to read more about hidden clocks, resets, and enables

Hidden enable

type HiddenEnable dom = (Hidden (HiddenEnableName dom) (Enable dom), KnownDomain dom) Source #

A constraint that indicates the component needs an Enable

Click here to read more about hidden clocks, resets, and enables

hideEnable Source #

Arguments

:: forall dom r. HiddenEnable dom 
=> (Enable dom -> r)

Component whose enable argument you want to hide

-> r 

Hide the Enable argument of a component, so it can be routed implicitly.

Click here to read more about hidden clocks, resets, and enables

exposeEnable Source #

Arguments

:: forall dom r. WithSingleDomain dom r 
=> (HiddenEnable dom => r)

The component with a hidden enable

-> KnownDomain dom => Enable dom -> r

The component with its enable argument exposed

Expose a hidden Enable argument of a component, so it can be applied explicitly.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenEnable dom => Signal dom a -> Signal dom a

If you want to expose a enable of a component working on multiple domains (such as the first example), use exposeSpecificEnable.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = exposeEnable reg enableGen
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force exposeEnable to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = exposeEnable @System reg enableGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

withEnable Source #

Arguments

:: forall dom r. KnownDomain dom 
=> WithSingleDomain dom r 
=> Enable dom

The Enable we want to connect

-> (HiddenEnable dom => r)

The function with a hidden Enable argument

-> r 

Connect an explicit Enable to a function with a hidden Enable.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenEnable dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenEnable dom => Signal dom a -> Signal dom a

If you want to connect a enable to a component working on multiple domains (such as the first example), use withSpecificEnable.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = withEnable enableGen reg
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force withEnable to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = withEnable @System enableGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

exposeSpecificEnable Source #

Arguments

:: forall dom r. WithSpecificDomain dom r 
=> (HiddenEnable dom => r)

The component with a hidden enable

-> KnownDomain dom => Enable dom -> r

The component with its enable argument exposed

Expose a hidden Enable argument of a component, so it can be applied explicitly. This function can be used on components with multiple domains. As opposed to exposeEnable, callers should explicitly state what the enable domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

exposeSpecificEnable can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = exposeSpecificEnable @System reg enableGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = exposeSpecificEnable @dom reg enableGen

withSpecificEnable Source #

Arguments

:: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) 
=> Enable dom

The Enable we want to connect

-> (HiddenEnable dom => r)

The function with a hidden Enable argument

-> r 

Connect an explicit Enable to a function with a hidden Enable. This function can be used on components with multiple domains. As opposed to withEnable, callers should explicitly state what the enable domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

withSpecificEnable can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = withSpecificEnable @System enableGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = withSpecificEnable @dom enableGen reg

hasEnable :: forall dom. HiddenEnable dom => Enable dom Source #

Connect a hidden Enable to an argument where a normal Enable argument was expected.

Click here to read more about hidden clocks, resets, and enables

Hidden clock, reset, and enable

type HiddenClockResetEnable dom = (HiddenClock dom, HiddenReset dom, HiddenEnable dom) Source #

A constraint that indicates the component needs a Clock, a Reset, and an Enable belonging to the same dom.

Click here to read more about hidden clocks, resets, and enables

hideClockResetEnable Source #

Arguments

:: forall dom r. HiddenClockResetEnable dom 
=> (KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r)

Component whose clock, reset, and enable argument you want to hide

-> r 

Hide the Clock, Reset, and Enable arguments of a component, so they can be routed implicitly.

Click here to read more about hidden clocks, resets, and enables

exposeClockResetEnable Source #

Arguments

:: forall dom r. WithSingleDomain dom r 
=> (HiddenClockResetEnable dom => r)

The component with hidden clock, reset, and enable arguments

-> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r

The component with its clock, reset, and enable arguments exposed

Expose hidden Clock, Reset, and Enable arguments of a component, so they can be applied explicitly.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenClockResetEnable dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenClockResetEnable dom => Signal dom a -> Signal dom a

If you want to expose a clock, reset, and enable of a component working on multiple domains (such as the first example), use exposeSpecificClockResetEnable.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = exposeClockResetEnable reg clockGen resetGen enableGen
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force exposeClockResetEnable to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = exposeClockResetEnable @System reg clockGen resetGen enableGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Usage in a testbench context:

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 en
    clk            = tbSystemClockGen (not <$> done)
    rst            = systemResetGen
    en             = enableGen

withClockResetEnable Source #

Arguments

:: forall dom r. KnownDomain dom 
=> WithSingleDomain dom r 
=> Clock dom

The Clock we want to connect

-> Reset dom

The Reset we want to connect

-> Enable dom

The Enable we want to connect

-> (HiddenClockResetEnable dom => r)

The function with a hidden Clock, hidden Reset, and hidden Enable argument

-> r 

Connect an explicit Clock, Reset, and Enable to a function with a hidden Clock, Reset, and Enable.

This function can only be used on components with a single domain. For example, this function will refuse when:

r ~ HiddenClockResetEnable dom1 => Signal dom1 a -> Signal dom2 a

But will work when:

r ~ HiddenClockResetEnable dom => Signal dom a -> Signal dom a

If you want to connect a clock, reset, and enable to a component working on multiple domains (such as the first example), use withSpecificClockResetEnable.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

Usage with a polymorphic domain:

>>> reg = register 5 (reg + 1)
>>> sig = withClockResetEnable clockGen resetGen enableGen reg
>>> sampleN @System 10 sig
[5,5,6,7,8,9,10,11,12,13]

Force withClockResetEnable to work on System (hence sampleN not needing an explicit domain later):

>>> reg = register 5 (reg + 1)
>>> sig = withClockResetEnable @System clockGen resetGen enableGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

exposeSpecificClockResetEnable Source #

Arguments

:: forall dom r. WithSpecificDomain dom r 
=> (HiddenClockResetEnable dom => r)

The function with hidden Clock, Reset, and Enable arguments

-> KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r

The component with its Clock, Reset, and Enable arguments exposed

Expose hidden Clock, Reset, and Enable arguments of a component, so they can be applied explicitly. This function can be used on components with multiple domains. As opposed to exposeClockResetEnable, callers should explicitly state what the domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

exposeSpecificClockResetEnable can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = exposeSpecificClockResetEnable @System reg clockGen resetGen enableGen
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = exposeSpecificClockResetEnable @dom reg clockGen resetGen enableGen

withSpecificClockResetEnable Source #

Arguments

:: forall dom r. (KnownDomain dom, WithSpecificDomain dom r) 
=> Clock dom

The Clock we want to connect

-> Reset dom

The Reset we want to connect

-> Enable dom

The Enable we want to connect

-> (HiddenClockResetEnable dom => r)

The function with hidden Clock, Reset, and Enable arguments

-> r 

Connect an explicit Clock, Reset, and Enable to a function with hidden Clock, Reset, and Enable arguments. This function can be used on components with multiple domains. As opposed to withClockResetEnable, callers should explicitly state what the domain is. See the examples for more information.

Click here to read more about hidden clocks, resets, and enables

Example

Expand

withSpecificClockResetEnable can only be used when it can find the specified domain in r:

>>> reg = register @System 5 (reg + 1)
>>> sig = withSpecificClockResetEnable @System clockGen resetGen enableGen reg
>>> sampleN 10 sig
[5,5,6,7,8,9,10,11,12,13]

Type variables work too, if they are in scope. For example:

reg = register @dom 5 (reg + 1)
sig = withSpecificClockResetEnable @dom clockGen resetGen enableGen reg

Basic circuit functions

dflipflop :: forall dom a. (HiddenClock dom, NFDataX a) => 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

:: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) 
=> a

Initial value

-> Signal dom a

Signal to delay

-> Signal dom a 

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

>>> sampleN @System 3 (delay 0 (fromList [1,2,3,4]))
[0,1,2]

delayMaybe Source #

Arguments

:: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) 
=> a

Initial value

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

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

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

delayEn Source #

Arguments

:: forall dom a. (NFDataX a, HiddenClock dom, HiddenEnable dom) 
=> a

Initial value

-> Signal dom Bool

Enable

-> Signal dom a 
-> Signal dom a 

Version of delay that only updates when its second 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 @System 7 (delayEn 0 enable input)
[0,1,2,2,2,5,6]

register infixr 3 Source #

Arguments

:: forall dom a. (HiddenClockResetEnable dom, NFDataX a) 
=> a

Reset value. register outputs the reset value when the reset is active. If the domain has initial values enabled, the reset value will also be the initial value.

-> Signal dom a 
-> Signal dom a 

register i s delays the values in Signal s for one cycle, and sets the value at time 0 to i

>>> sampleN @System 5 (register 8 (fromList [1,1,2,3,4]))
[8,8,1,2,3]

regMaybe infixr 3 Source #

Arguments

:: forall dom a. (HiddenClockResetEnable dom, NFDataX a) 
=> a

Reset value. regMaybe outputs the reset value when the reset is active. 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 second argument is a Just value. So given:

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

  switch Nothing = Just 1
  switch _       = Nothing

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

We get:

>>> sampleN @System 9 sometimes1
[Nothing,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1,Nothing,Just 1]
>>> sampleN @System 9 countSometimes
[0,0,0,1,1,2,2,3,3]

regEn Source #

Arguments

:: forall dom a. (HiddenClockResetEnable dom, NFDataX a) 
=> a

Reset value. regEn outputs the reset value when the reset is active. If the domain has initial values enabled, the reset value will also be the initial value.

-> Signal dom Bool 
-> Signal dom a 
-> Signal dom a 

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

oscillate = register False (not <$> oscillate)
count     = regEn 0 oscillate (count + 1)

We get:

>>> sampleN @System 9 oscillate
[False,False,True,False,True,False,True,False,True]
>>> sampleN @System 9 count
[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 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 commit 94b0bff5 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 #

N.B.: The documentation only shows instances up to 3-tuples. By default, instances up to and including 12-tuples will exist. If the flag large-tuples is set instances up to the GHC imposed limit will exist. The GHC imposed limit is either 62 or 64 depending on the GHC version.

Instance 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 #

data EmptyTuple Source #

Constructors

EmptyTuple 

Instances

Instances details
Bundle EmptyTuple Source #

See commit 94b0bff5 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 commit 94b0bff5 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 dom ()
  unbundle :: Signal dom () -> ()

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 dom -> Signal dom EmptyTuple
  unbundle :: Signal dom EmptyTuple -> TaggedEmptyTuple dom

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

Constructors

TaggedEmptyTuple 

Simulation functions (not synthesizable)

simulate Source #

Arguments

:: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) 
=> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b)

Circuit to simulate, whose source potentially has a hidden clock, reset, and/or enable.

-> [a] 
-> [b] 

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

>>> simulate @System (register 8) [1, 2, 3]
[8,1,2,3...
...

Where System denotes the domain to simulate on. The reset line is asserted for a single cycle. The first value is therefore supplied twice to the circuit: once while reset is high, and once directly after. The first output value (the value produced while the reset is asserted) is dropped.

If you only want to simulate a finite number of samples, see simulateN. If you need the reset line to be asserted for more than one cycle or if you need a custom reset value, see simulateWithReset and simulateWithResetN.

NB: This function is not synthesizable

simulateB Source #

Arguments

:: forall dom a b. (KnownDomain dom, Bundle a, Bundle b, NFDataX a, NFDataX b) 
=> (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b)

Function we want to simulate, whose components potentially have a hidden clock (and reset)

-> [a] 
-> [b] 

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

>>> simulateB @System (unbundle . register (8,8) . bundle) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)...
...

NB: This function is not synthesizable

simulateN Source #

Arguments

:: forall dom a b. (KnownDomain dom, NFDataX a, NFDataX b) 
=> Int

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

-> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b)

Signal we want to sample, whose source potentially has a hidden clock (and reset)

-> [a] 
-> [b] 

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

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

-> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b)

Signal we want to sample, whose source potentially has a hidden clock (and reset)

-> [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 reset value a is supplied to the circuit.

simulateWithResetN 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

-> Int

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

-> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b)

Signal we want to sample, whose source potentially has a hidden clock (and reset)

-> [a] 
-> [b] 

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

lazy versions

simulate_lazy Source #

Arguments

:: forall dom a b. KnownDomain dom 
=> (HiddenClockResetEnable dom => Signal dom a -> Signal dom b)

Function we want to simulate, whose components potentially have a hidden clock (and reset)

-> [a] 
-> [b] 

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

>>> simulate @System (register 8) [1, 2, 3]
[8,1,2,3...
...

NB: This function is not synthesizable

simulateB_lazy Source #

Arguments

:: forall dom a b. (KnownDomain dom, Bundle a, Bundle b) 
=> (HiddenClockResetEnable dom => Unbundled dom a -> Unbundled dom b)

Function we want to simulate, whose components potentially have a hidden clock (and reset)

-> [a] 
-> [b] 

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

>>> simulateB @System (unbundle . register (8,8) . bundle) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)...
...

NB: This function is not synthesizable

Automaton

signalAutomaton :: forall dom a b. KnownDomain dom => (HiddenClockResetEnable dom => Signal dom a -> Signal dom b) -> Automaton (->) a b Source #

Build an Automaton from a function over Signals.

NB: Consumption of continuation of the Automaton must be affine; that is, you can only apply the continuation associated with a particular element at most once.

List <-> Signal conversion (not synthesizable)

sample Source #

Arguments

:: forall dom a. (KnownDomain dom, NFDataX a) 
=> (HiddenClockResetEnable dom => Signal dom a)

Signal we want to sample, whose source potentially has a hidden clock (and reset)

-> [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, ...

If the given component has not yet been given a clock, reset, or enable line, sample will supply them. The reset will be asserted for a single cycle. sample will not drop the value produced by the circuit while the reset was asserted. If you want this, or if you want more than a single cycle reset, consider using sampleWithReset.

NB: This function is not synthesizable

sampleN Source #

Arguments

:: forall dom a. (KnownDomain dom, NFDataX a) 
=> Int

Number of samples to produce

-> (HiddenClockResetEnable dom => Signal dom a)

Signal to sample, whose source potentially has a hidden clock (and reset)

-> [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 @System 3 s == [s0, s1, s2]

If the given component has not yet been given a clock, reset, or enable line, sampleN will supply them. The reset will be asserted for a single cycle. sampleN will not drop the value produced by the circuit while the reset was asserted. If you want this, or if you want more than a single cycle reset, consider using sampleWithResetN.

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

-> (HiddenClockResetEnable dom => Signal dom a)

Signal to sample, whose source potentially has a hidden clock (and reset)

-> [a] 

Get an infinite list of samples from a Signal, while asserting the reset line for m clock cycles. sampleWithReset does not return the first m 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

-> (HiddenClockResetEnable dom => Signal dom a)

Signal to sample, whose source potentially has a hidden clock (and reset)

-> [a] 

Get a list of n samples from a Signal, while asserting the reset line for m clock cycles. sampleWithReset does not return the first m 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. (HiddenReset dom, NFDataX a) => 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 = withReset rst (fromListWithReset Nothing [Just 'a', Just 'b', Just 'c'])
>>> sampleN @System 6 res
[Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']

NB: This function is not synthesizable

lazy versions

sample_lazy Source #

Arguments

:: forall dom a. KnownDomain dom 
=> (HiddenClockResetEnable dom => Signal dom a)

Signal we want to sample, whose source potentially has a hidden clock (and reset)

-> [a] 

Lazily 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, ...

If the given component has not yet been given a clock, reset, or enable line, sample_lazy will supply them. The reset will be asserted for a single cycle. sample_lazy will not drop the value produced by the circuit while the reset was asserted.

NB: This function is not synthesizable

sampleN_lazy Source #

Arguments

:: forall dom a. KnownDomain dom 
=> Int 
-> (HiddenClockResetEnable dom => Signal dom a)

Signal we want to sample, whose source potentially has a hidden clock (and reset)

-> [a] 

Lazily 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 @System 3 s == [s0, s1, s2]

If the given component has not yet been given a clock, reset, or enable line, sampleN_lazy will supply them. The reset will be asserted for a single cycle. sampleN_lazy will not drop the value produced by the circuit while the reset was asserted.

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 Source #

Arguments

:: KnownDomain dom 
=> Int

The number of cycles we want to test for

-> (HiddenClockResetEnable dom => Signal dom Bool)

Signal we want to evaluate, whose source potentially has a hidden clock (and reset)

-> 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.

Internals

type HiddenClockName dom = AppendSymbol dom "_clk" Source #

type HiddenResetName dom = AppendSymbol dom "_rst" Source #

type HiddenEnableName dom = AppendSymbol dom "_en" Source #