clash-prelude-1.4.0: Clash: a functional hardware description language - Prelude library
Copyright(C) 2013-2016 University of Twente
2017-2019 Myrtle Software Ltd
2017 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellUnsafe
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • BangPatterns
  • TypeFamilies
  • ViewPatterns
  • GADTs
  • GADTSyntax
  • ConstraintKinds
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveAnyClass
  • DeriveLift
  • DerivingStrategies
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • MagicHash
  • KindSignatures
  • RoleAnnotations
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Signal.Internal

Description

 
Synopsis

Datatypes

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.

Constructors

a :- (Signal dom a) infixr 5

The constructor, (:-), is not synthesizable.

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)

head# :: Signal dom a -> a Source #

tail# :: Signal dom a -> Signal dom a Source #

Domains

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

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 #

knownDomainByName :: forall dom. KnownDomain dom => SSymbol dom -> SDomainConfiguration dom (KnownConf dom) Source #

Version of knownDomain that takes a SSymbol. For example:

>>> knownDomainByName (SSymbol @"System")
SDomainConfiguration (SSymbol @"System") (SNat @10000) SRising SAsynchronous SDefined SActiveHigh

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.0-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.0-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.0-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.0-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) => ...

type family DomainConfigurationPeriod (config :: DomainConfiguration) :: Nat where ... Source #

Helper type family for DomainPeriod

Equations

DomainConfigurationPeriod ('DomainConfiguration name period edge reset init polarity) = period 

type family DomainConfigurationActiveEdge (config :: DomainConfiguration) :: ActiveEdge where ... Source #

Helper type family for DomainActiveEdge

Equations

DomainConfigurationActiveEdge ('DomainConfiguration name period edge reset init polarity) = edge 

type family DomainConfigurationResetKind (config :: DomainConfiguration) :: ResetKind where ... Source #

Helper type family for DomainResetKind

Equations

DomainConfigurationResetKind ('DomainConfiguration name period edge reset init polarity) = reset 

type family DomainConfigurationInitBehavior (config :: DomainConfiguration) :: InitBehavior where ... Source #

Helper type family for DomainInitBehavior

Equations

DomainConfigurationInitBehavior ('DomainConfiguration name period edge reset init polarity) = init 

type family DomainConfigurationResetPolarity (config :: DomainConfiguration) :: ResetPolarity where ... Source #

Helper type family for DomainResetPolarity

Equations

DomainConfigurationResetPolarity ('DomainConfiguration name period edge reset init polarity) = polarity 

Default domains

type System = "System" :: Domain Source #

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

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

type XilinxSystem = "XilinxSystem" :: Domain Source #

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

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

type IntelSystem = "IntelSystem" :: Domain Source #

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

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

vSystem :: VDomainConfiguration Source #

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

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

vIntelSystem :: VDomainConfiguration Source #

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

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

vXilinxSystem :: VDomainConfiguration Source #

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

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

Domain utilities

data VDomainConfiguration Source #

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

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

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

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

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

Clocks

data Clock (dom :: Domain) Source #

A clock signal belonging to a domain named dom.

Constructors

Clock (SSymbol 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)

clockTag :: Clock dom -> SSymbol dom Source #

Extract dom symbol from Clock

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.

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

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.

Constructors

Enable (Signal dom Bool) 

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.

Resets

data Reset (dom :: Domain) Source #

A reset signal belonging to a domain called dom.

The underlying representation of resets is Bool.

Constructors

Reset (Signal dom 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.

invertReset :: Reset dom -> Reset dom Source #

Invert reset signal

Basic circuits

delay# :: forall dom a. (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a Source #

register# Source #

Arguments

:: forall dom a. (KnownDomain dom, NFDataX a) 
=> Clock dom 
-> Reset dom 
-> Enable dom 
-> a

Power up value

-> a

Reset value

-> Signal dom a 
-> Signal dom a 

A register with a power up and reset value. Power up values are not supported on all platforms, please consult the manual of your target platform and check the notes below.

Xilinx: power up values and reset values MUST be the same. If they are not, the Xilinx tooling will ignore the reset value and use the power up value instead. Source: MIA

Intel: power up values and reset values MUST be the same. If they are not, the Intel tooling will ignore the power up value and use the reset value instead. Source: https://www.intel.com/content/www/us/en/programmable/support/support-resources/knowledge-base/solutions/rd01072011_91.html

asyncRegister# Source #

Arguments

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

Clock signal

-> Reset dom

Reset signal

-> Enable dom

Enable signal

-> a

Power up value

-> a

Reset value

-> Signal dom a 
-> Signal dom a 

Version of register# that simulates a register on an asynchronous domain. Is synthesizable.

syncRegister# Source #

Arguments

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

Clock signal

-> Reset dom

Reset signal

-> Enable dom

Enable signal

-> a

Power up value

-> a

Reset value

-> Signal dom a 
-> Signal dom a 

Version of register# that simulates a register on a synchronous domain. Not synthesizable.

registerPowerup# :: forall dom a. (KnownDomain dom, NFDataX a, HasCallStack) => Clock dom -> a -> a Source #

Acts like id if given domain allows powerup values, but returns a value constructed with deepErrorX otherwise.

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

The above type is a generalization for:

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

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

Simulation and testbench functions

clockGen :: KnownDomain dom => Clock dom Source #

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

To be used like:

clkSystem = clockGen @System

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

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

Reset generator

To be used like:

rstSystem = resetGen @System

See tbClockGen for example usage.

resetGenN Source #

Arguments

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

Number of initial cycles to hold reset high

-> Reset dom 

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

To be used like:

rstSystem5 = resetGen System (SNat 5)

Example usage:

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

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

Simulation functions (not synthesizable)

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

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

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

NB: This function is not synthesizable

lazy version

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

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

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

NB: This function is not synthesizable

Automaton

signalAutomaton :: forall dom a b. (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 :: (Foldable f, NFDataX a) => f a -> [a] Source #

The above type is a generalization for:

sample :: Signal a -> [a]

Get an infinite list of samples from a Signal

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

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

NB: This function is not synthesizable

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

The above type is a generalization for:

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

Get a list of n samples from a Signal

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

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

NB: This function is not synthesizable

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

lazy versions

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

The above type is a generalization for:

sample :: Signal a -> [a]

Get an infinite list of samples from a Signal

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

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

NB: This function is not synthesizable

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

The above type is a generalization for:

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

Get a list of n samples from a Signal

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

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

NB: This function is not synthesizable

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

Create a Signal from a list

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

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

NB: This function is not synthesizable

QuickCheck combinators

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

The above type is a generalization for:

testFor :: Int -> Signal Bool -> Property

testFor n s tests the signal s for n cycles.

NB: This function is not synthesizable

Type classes

Eq-like

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

The above type is a generalization for:

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

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

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

The above type is a generalization for:

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

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

Ord-like

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

The above type is a generalization for:

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

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

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

The above type is a generalization for:

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

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

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

The above type is a generalization for:

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

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

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

The above type is a generalization for:

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

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

Functor

mapSignal# :: forall a b dom. (a -> b) -> Signal dom a -> Signal dom b Source #

Applicative

signal# :: a -> Signal dom a Source #

appSignal# :: Signal dom (a -> b) -> Signal dom a -> Signal dom b Source #

Foldable

foldr# :: (a -> b -> b) -> b -> Signal dom a -> b 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.

Traversable

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

EXTREMELY EXPERIMENTAL

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

WARNING: EXTREMELY EXPERIMENTAL

The circuit semantics of this operation are unclear and/or non-existent. There is a good reason there is no Monad instance for Signal.

Is currently treated as id by the Clash compiler.