{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
#if __GLASGOW_HASKELL__ >= 806
{-# LANGUAGE NoStarIsType #-}
#endif
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
{-# LANGUAGE Unsafe #-}
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.Extra.Solver #-}
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.Normalise #-}
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.KnownNat.Solver #-}
{-# OPTIONS_GHC -fno-cpr-anal #-}
{-# OPTIONS_HADDOCK show-extensions not-home #-}
module Clash.Signal.Internal
(
Signal(..)
, head#
, tail#
, Domain
, KnownDomain(..)
, KnownConfiguration
, knownDomainByName
, ActiveEdge(..)
, SActiveEdge(..)
, InitBehavior(..)
, SInitBehavior(..)
, ResetKind(..)
, SResetKind(..)
, ResetPolarity(..)
, SResetPolarity(..)
, DomainConfiguration(..)
, SDomainConfiguration(..)
, DomainPeriod
, DomainActiveEdge
, DomainResetKind
, DomainInitBehavior
, DomainResetPolarity
, System
, XilinxSystem
, IntelSystem
, vSystem
, vIntelSystem
, vXilinxSystem
, VDomainConfiguration(..)
, vDomain
, createDomain
, Clock (..)
, clockTag
, hzToPeriod
, periodToHz
, Enable(..)
, toEnable
, fromEnable
, enableGen
, Reset(..)
, unsafeToReset
, unsafeFromReset
, unsafeToHighPolarity
, unsafeToLowPolarity
, unsafeFromHighPolarity
, unsafeFromLowPolarity
, invertReset
, delay#
, register#
, mux
, clockGen
, resetGen
, resetGenN
, (.&&.), (.||.)
, simulate
, simulate_lazy
, sample
, sampleN
, fromList
, sample_lazy
, sampleN_lazy
, fromList_lazy
, testFor
, (.==.), (./=.)
, (.<.), (.<=.), (.>=.), (.>.)
, mapSignal#
, signal#
, appSignal#
, foldr#
, traverse#
, joinSignal#
)
where
import Type.Reflection (Typeable)
import Control.Applicative (liftA2, liftA3)
import Control.DeepSeq (NFData)
import Clash.Annotations.Primitive (hasBlackBox)
import Data.Binary (Binary)
import Data.Char (isAsciiUpper, isAlphaNum, isAscii)
import Data.Coerce (coerce)
import Data.Data (Data)
import Data.Default.Class (Default (..))
import Data.Hashable (Hashable)
import Data.Proxy (Proxy(..))
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack)
import GHC.TypeLits (KnownSymbol, Nat, Symbol, type (<=))
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Compat (mkTySynInstD)
import Numeric.Natural (Natural)
import Test.QuickCheck (Arbitrary (..), CoArbitrary(..), Property,
property)
import Clash.Promoted.Nat (SNat (..), snatToNum, snatToNatural)
import Clash.Promoted.Symbol (SSymbol (..), ssymbolToString)
import Clash.XException
(NFDataX, errorX, deepseqX, defaultSeqX, deepErrorX)
data ActiveEdge
= Rising
| Falling
deriving (Int -> ActiveEdge -> ShowS
[ActiveEdge] -> ShowS
ActiveEdge -> String
(Int -> ActiveEdge -> ShowS)
-> (ActiveEdge -> String)
-> ([ActiveEdge] -> ShowS)
-> Show ActiveEdge
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActiveEdge] -> ShowS
$cshowList :: [ActiveEdge] -> ShowS
show :: ActiveEdge -> String
$cshow :: ActiveEdge -> String
showsPrec :: Int -> ActiveEdge -> ShowS
$cshowsPrec :: Int -> ActiveEdge -> ShowS
Show, ActiveEdge -> ActiveEdge -> Bool
(ActiveEdge -> ActiveEdge -> Bool)
-> (ActiveEdge -> ActiveEdge -> Bool) -> Eq ActiveEdge
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActiveEdge -> ActiveEdge -> Bool
$c/= :: ActiveEdge -> ActiveEdge -> Bool
== :: ActiveEdge -> ActiveEdge -> Bool
$c== :: ActiveEdge -> ActiveEdge -> Bool
Eq, Eq ActiveEdge
Eq ActiveEdge =>
(ActiveEdge -> ActiveEdge -> Ordering)
-> (ActiveEdge -> ActiveEdge -> Bool)
-> (ActiveEdge -> ActiveEdge -> Bool)
-> (ActiveEdge -> ActiveEdge -> Bool)
-> (ActiveEdge -> ActiveEdge -> Bool)
-> (ActiveEdge -> ActiveEdge -> ActiveEdge)
-> (ActiveEdge -> ActiveEdge -> ActiveEdge)
-> Ord ActiveEdge
ActiveEdge -> ActiveEdge -> Bool
ActiveEdge -> ActiveEdge -> Ordering
ActiveEdge -> ActiveEdge -> ActiveEdge
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ActiveEdge -> ActiveEdge -> ActiveEdge
$cmin :: ActiveEdge -> ActiveEdge -> ActiveEdge
max :: ActiveEdge -> ActiveEdge -> ActiveEdge
$cmax :: ActiveEdge -> ActiveEdge -> ActiveEdge
>= :: ActiveEdge -> ActiveEdge -> Bool
$c>= :: ActiveEdge -> ActiveEdge -> Bool
> :: ActiveEdge -> ActiveEdge -> Bool
$c> :: ActiveEdge -> ActiveEdge -> Bool
<= :: ActiveEdge -> ActiveEdge -> Bool
$c<= :: ActiveEdge -> ActiveEdge -> Bool
< :: ActiveEdge -> ActiveEdge -> Bool
$c< :: ActiveEdge -> ActiveEdge -> Bool
compare :: ActiveEdge -> ActiveEdge -> Ordering
$ccompare :: ActiveEdge -> ActiveEdge -> Ordering
$cp1Ord :: Eq ActiveEdge
Ord, (forall x. ActiveEdge -> Rep ActiveEdge x)
-> (forall x. Rep ActiveEdge x -> ActiveEdge) -> Generic ActiveEdge
forall x. Rep ActiveEdge x -> ActiveEdge
forall x. ActiveEdge -> Rep ActiveEdge x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActiveEdge x -> ActiveEdge
$cfrom :: forall x. ActiveEdge -> Rep ActiveEdge x
Generic, ActiveEdge -> ()
(ActiveEdge -> ()) -> NFData ActiveEdge
forall a. (a -> ()) -> NFData a
rnf :: ActiveEdge -> ()
$crnf :: ActiveEdge -> ()
NFData, Typeable ActiveEdge
DataType
Constr
Typeable ActiveEdge =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ActiveEdge -> c ActiveEdge)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActiveEdge)
-> (ActiveEdge -> Constr)
-> (ActiveEdge -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActiveEdge))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActiveEdge))
-> ((forall b. Data b => b -> b) -> ActiveEdge -> ActiveEdge)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r)
-> (forall u. (forall d. Data d => d -> u) -> ActiveEdge -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ActiveEdge -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge)
-> Data ActiveEdge
ActiveEdge -> DataType
ActiveEdge -> Constr
(forall b. Data b => b -> b) -> ActiveEdge -> ActiveEdge
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ActiveEdge -> c ActiveEdge
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActiveEdge
forall a.
Typeable a =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ActiveEdge -> u
forall u. (forall d. Data d => d -> u) -> ActiveEdge -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActiveEdge
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ActiveEdge -> c ActiveEdge
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActiveEdge)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActiveEdge)
$cFalling :: Constr
$cRising :: Constr
$tActiveEdge :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
gmapMp :: (forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
gmapM :: (forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ActiveEdge -> m ActiveEdge
gmapQi :: Int -> (forall d. Data d => d -> u) -> ActiveEdge -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ActiveEdge -> u
gmapQ :: (forall d. Data d => d -> u) -> ActiveEdge -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ActiveEdge -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ActiveEdge -> r
gmapT :: (forall b. Data b => b -> b) -> ActiveEdge -> ActiveEdge
$cgmapT :: (forall b. Data b => b -> b) -> ActiveEdge -> ActiveEdge
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActiveEdge)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActiveEdge)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ActiveEdge)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActiveEdge)
dataTypeOf :: ActiveEdge -> DataType
$cdataTypeOf :: ActiveEdge -> DataType
toConstr :: ActiveEdge -> Constr
$ctoConstr :: ActiveEdge -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActiveEdge
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActiveEdge
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ActiveEdge -> c ActiveEdge
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ActiveEdge -> c ActiveEdge
$cp1Data :: Typeable ActiveEdge
Data, Int -> ActiveEdge -> Int
ActiveEdge -> Int
(Int -> ActiveEdge -> Int)
-> (ActiveEdge -> Int) -> Hashable ActiveEdge
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ActiveEdge -> Int
$chash :: ActiveEdge -> Int
hashWithSalt :: Int -> ActiveEdge -> Int
$chashWithSalt :: Int -> ActiveEdge -> Int
Hashable, Get ActiveEdge
[ActiveEdge] -> Put
ActiveEdge -> Put
(ActiveEdge -> Put)
-> Get ActiveEdge -> ([ActiveEdge] -> Put) -> Binary ActiveEdge
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [ActiveEdge] -> Put
$cputList :: [ActiveEdge] -> Put
get :: Get ActiveEdge
$cget :: Get ActiveEdge
put :: ActiveEdge -> Put
$cput :: ActiveEdge -> Put
Binary)
data SActiveEdge (edge :: ActiveEdge) where
SRising :: SActiveEdge 'Rising
SFalling :: SActiveEdge 'Falling
instance Show (SActiveEdge edge) where
show :: SActiveEdge edge -> String
show SRising = "SRising"
show SFalling = "SFalling"
data ResetKind
= Asynchronous
| Synchronous
deriving (Int -> ResetKind -> ShowS
[ResetKind] -> ShowS
ResetKind -> String
(Int -> ResetKind -> ShowS)
-> (ResetKind -> String)
-> ([ResetKind] -> ShowS)
-> Show ResetKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetKind] -> ShowS
$cshowList :: [ResetKind] -> ShowS
show :: ResetKind -> String
$cshow :: ResetKind -> String
showsPrec :: Int -> ResetKind -> ShowS
$cshowsPrec :: Int -> ResetKind -> ShowS
Show, ResetKind -> ResetKind -> Bool
(ResetKind -> ResetKind -> Bool)
-> (ResetKind -> ResetKind -> Bool) -> Eq ResetKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetKind -> ResetKind -> Bool
$c/= :: ResetKind -> ResetKind -> Bool
== :: ResetKind -> ResetKind -> Bool
$c== :: ResetKind -> ResetKind -> Bool
Eq, Eq ResetKind
Eq ResetKind =>
(ResetKind -> ResetKind -> Ordering)
-> (ResetKind -> ResetKind -> Bool)
-> (ResetKind -> ResetKind -> Bool)
-> (ResetKind -> ResetKind -> Bool)
-> (ResetKind -> ResetKind -> Bool)
-> (ResetKind -> ResetKind -> ResetKind)
-> (ResetKind -> ResetKind -> ResetKind)
-> Ord ResetKind
ResetKind -> ResetKind -> Bool
ResetKind -> ResetKind -> Ordering
ResetKind -> ResetKind -> ResetKind
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ResetKind -> ResetKind -> ResetKind
$cmin :: ResetKind -> ResetKind -> ResetKind
max :: ResetKind -> ResetKind -> ResetKind
$cmax :: ResetKind -> ResetKind -> ResetKind
>= :: ResetKind -> ResetKind -> Bool
$c>= :: ResetKind -> ResetKind -> Bool
> :: ResetKind -> ResetKind -> Bool
$c> :: ResetKind -> ResetKind -> Bool
<= :: ResetKind -> ResetKind -> Bool
$c<= :: ResetKind -> ResetKind -> Bool
< :: ResetKind -> ResetKind -> Bool
$c< :: ResetKind -> ResetKind -> Bool
compare :: ResetKind -> ResetKind -> Ordering
$ccompare :: ResetKind -> ResetKind -> Ordering
$cp1Ord :: Eq ResetKind
Ord, (forall x. ResetKind -> Rep ResetKind x)
-> (forall x. Rep ResetKind x -> ResetKind) -> Generic ResetKind
forall x. Rep ResetKind x -> ResetKind
forall x. ResetKind -> Rep ResetKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetKind x -> ResetKind
$cfrom :: forall x. ResetKind -> Rep ResetKind x
Generic, ResetKind -> ()
(ResetKind -> ()) -> NFData ResetKind
forall a. (a -> ()) -> NFData a
rnf :: ResetKind -> ()
$crnf :: ResetKind -> ()
NFData, Typeable ResetKind
DataType
Constr
Typeable ResetKind =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetKind -> c ResetKind)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetKind)
-> (ResetKind -> Constr)
-> (ResetKind -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ResetKind))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResetKind))
-> ((forall b. Data b => b -> b) -> ResetKind -> ResetKind)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r)
-> (forall u. (forall d. Data d => d -> u) -> ResetKind -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ResetKind -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind)
-> Data ResetKind
ResetKind -> DataType
ResetKind -> Constr
(forall b. Data b => b -> b) -> ResetKind -> ResetKind
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetKind -> c ResetKind
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetKind
forall a.
Typeable a =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ResetKind -> u
forall u. (forall d. Data d => d -> u) -> ResetKind -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetKind
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetKind -> c ResetKind
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ResetKind)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResetKind)
$cSynchronous :: Constr
$cAsynchronous :: Constr
$tResetKind :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
gmapMp :: (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
gmapM :: (forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ResetKind -> m ResetKind
gmapQi :: Int -> (forall d. Data d => d -> u) -> ResetKind -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ResetKind -> u
gmapQ :: (forall d. Data d => d -> u) -> ResetKind -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ResetKind -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetKind -> r
gmapT :: (forall b. Data b => b -> b) -> ResetKind -> ResetKind
$cgmapT :: (forall b. Data b => b -> b) -> ResetKind -> ResetKind
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResetKind)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResetKind)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ResetKind)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ResetKind)
dataTypeOf :: ResetKind -> DataType
$cdataTypeOf :: ResetKind -> DataType
toConstr :: ResetKind -> Constr
$ctoConstr :: ResetKind -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetKind
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetKind
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetKind -> c ResetKind
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetKind -> c ResetKind
$cp1Data :: Typeable ResetKind
Data, Int -> ResetKind -> Int
ResetKind -> Int
(Int -> ResetKind -> Int)
-> (ResetKind -> Int) -> Hashable ResetKind
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ResetKind -> Int
$chash :: ResetKind -> Int
hashWithSalt :: Int -> ResetKind -> Int
$chashWithSalt :: Int -> ResetKind -> Int
Hashable)
data SResetKind (resetKind :: ResetKind) where
SAsynchronous :: SResetKind 'Asynchronous
SSynchronous :: SResetKind 'Synchronous
instance Show (SResetKind reset) where
show :: SResetKind reset -> String
show SAsynchronous = "SAsynchronous"
show SSynchronous = "SSynchronous"
data ResetPolarity
= ActiveHigh
| ActiveLow
deriving (ResetPolarity -> ResetPolarity -> Bool
(ResetPolarity -> ResetPolarity -> Bool)
-> (ResetPolarity -> ResetPolarity -> Bool) -> Eq ResetPolarity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetPolarity -> ResetPolarity -> Bool
$c/= :: ResetPolarity -> ResetPolarity -> Bool
== :: ResetPolarity -> ResetPolarity -> Bool
$c== :: ResetPolarity -> ResetPolarity -> Bool
Eq, Eq ResetPolarity
Eq ResetPolarity =>
(ResetPolarity -> ResetPolarity -> Ordering)
-> (ResetPolarity -> ResetPolarity -> Bool)
-> (ResetPolarity -> ResetPolarity -> Bool)
-> (ResetPolarity -> ResetPolarity -> Bool)
-> (ResetPolarity -> ResetPolarity -> Bool)
-> (ResetPolarity -> ResetPolarity -> ResetPolarity)
-> (ResetPolarity -> ResetPolarity -> ResetPolarity)
-> Ord ResetPolarity
ResetPolarity -> ResetPolarity -> Bool
ResetPolarity -> ResetPolarity -> Ordering
ResetPolarity -> ResetPolarity -> ResetPolarity
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ResetPolarity -> ResetPolarity -> ResetPolarity
$cmin :: ResetPolarity -> ResetPolarity -> ResetPolarity
max :: ResetPolarity -> ResetPolarity -> ResetPolarity
$cmax :: ResetPolarity -> ResetPolarity -> ResetPolarity
>= :: ResetPolarity -> ResetPolarity -> Bool
$c>= :: ResetPolarity -> ResetPolarity -> Bool
> :: ResetPolarity -> ResetPolarity -> Bool
$c> :: ResetPolarity -> ResetPolarity -> Bool
<= :: ResetPolarity -> ResetPolarity -> Bool
$c<= :: ResetPolarity -> ResetPolarity -> Bool
< :: ResetPolarity -> ResetPolarity -> Bool
$c< :: ResetPolarity -> ResetPolarity -> Bool
compare :: ResetPolarity -> ResetPolarity -> Ordering
$ccompare :: ResetPolarity -> ResetPolarity -> Ordering
$cp1Ord :: Eq ResetPolarity
Ord, Int -> ResetPolarity -> ShowS
[ResetPolarity] -> ShowS
ResetPolarity -> String
(Int -> ResetPolarity -> ShowS)
-> (ResetPolarity -> String)
-> ([ResetPolarity] -> ShowS)
-> Show ResetPolarity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetPolarity] -> ShowS
$cshowList :: [ResetPolarity] -> ShowS
show :: ResetPolarity -> String
$cshow :: ResetPolarity -> String
showsPrec :: Int -> ResetPolarity -> ShowS
$cshowsPrec :: Int -> ResetPolarity -> ShowS
Show, (forall x. ResetPolarity -> Rep ResetPolarity x)
-> (forall x. Rep ResetPolarity x -> ResetPolarity)
-> Generic ResetPolarity
forall x. Rep ResetPolarity x -> ResetPolarity
forall x. ResetPolarity -> Rep ResetPolarity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetPolarity x -> ResetPolarity
$cfrom :: forall x. ResetPolarity -> Rep ResetPolarity x
Generic, ResetPolarity -> ()
(ResetPolarity -> ()) -> NFData ResetPolarity
forall a. (a -> ()) -> NFData a
rnf :: ResetPolarity -> ()
$crnf :: ResetPolarity -> ()
NFData, Typeable ResetPolarity
DataType
Constr
Typeable ResetPolarity =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetPolarity -> c ResetPolarity)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetPolarity)
-> (ResetPolarity -> Constr)
-> (ResetPolarity -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ResetPolarity))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ResetPolarity))
-> ((forall b. Data b => b -> b) -> ResetPolarity -> ResetPolarity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r)
-> (forall u. (forall d. Data d => d -> u) -> ResetPolarity -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ResetPolarity -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity)
-> Data ResetPolarity
ResetPolarity -> DataType
ResetPolarity -> Constr
(forall b. Data b => b -> b) -> ResetPolarity -> ResetPolarity
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetPolarity -> c ResetPolarity
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetPolarity
forall a.
Typeable a =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ResetPolarity -> u
forall u. (forall d. Data d => d -> u) -> ResetPolarity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetPolarity
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetPolarity -> c ResetPolarity
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ResetPolarity)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ResetPolarity)
$cActiveLow :: Constr
$cActiveHigh :: Constr
$tResetPolarity :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
gmapMp :: (forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
gmapM :: (forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> ResetPolarity -> m ResetPolarity
gmapQi :: Int -> (forall d. Data d => d -> u) -> ResetPolarity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ResetPolarity -> u
gmapQ :: (forall d. Data d => d -> u) -> ResetPolarity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ResetPolarity -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ResetPolarity -> r
gmapT :: (forall b. Data b => b -> b) -> ResetPolarity -> ResetPolarity
$cgmapT :: (forall b. Data b => b -> b) -> ResetPolarity -> ResetPolarity
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ResetPolarity)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ResetPolarity)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ResetPolarity)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ResetPolarity)
dataTypeOf :: ResetPolarity -> DataType
$cdataTypeOf :: ResetPolarity -> DataType
toConstr :: ResetPolarity -> Constr
$ctoConstr :: ResetPolarity -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetPolarity
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ResetPolarity
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetPolarity -> c ResetPolarity
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ResetPolarity -> c ResetPolarity
$cp1Data :: Typeable ResetPolarity
Data, Int -> ResetPolarity -> Int
ResetPolarity -> Int
(Int -> ResetPolarity -> Int)
-> (ResetPolarity -> Int) -> Hashable ResetPolarity
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ResetPolarity -> Int
$chash :: ResetPolarity -> Int
hashWithSalt :: Int -> ResetPolarity -> Int
$chashWithSalt :: Int -> ResetPolarity -> Int
Hashable)
data SResetPolarity (polarity :: ResetPolarity) where
SActiveHigh :: SResetPolarity 'ActiveHigh
SActiveLow :: SResetPolarity 'ActiveLow
instance Show (SResetPolarity polarity) where
show :: SResetPolarity polarity -> String
show SActiveHigh = "SActiveHigh"
show SActiveLow = "SActiveLow"
data InitBehavior
= Unknown
| Defined
deriving (Int -> InitBehavior -> ShowS
[InitBehavior] -> ShowS
InitBehavior -> String
(Int -> InitBehavior -> ShowS)
-> (InitBehavior -> String)
-> ([InitBehavior] -> ShowS)
-> Show InitBehavior
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InitBehavior] -> ShowS
$cshowList :: [InitBehavior] -> ShowS
show :: InitBehavior -> String
$cshow :: InitBehavior -> String
showsPrec :: Int -> InitBehavior -> ShowS
$cshowsPrec :: Int -> InitBehavior -> ShowS
Show, InitBehavior -> InitBehavior -> Bool
(InitBehavior -> InitBehavior -> Bool)
-> (InitBehavior -> InitBehavior -> Bool) -> Eq InitBehavior
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InitBehavior -> InitBehavior -> Bool
$c/= :: InitBehavior -> InitBehavior -> Bool
== :: InitBehavior -> InitBehavior -> Bool
$c== :: InitBehavior -> InitBehavior -> Bool
Eq, Eq InitBehavior
Eq InitBehavior =>
(InitBehavior -> InitBehavior -> Ordering)
-> (InitBehavior -> InitBehavior -> Bool)
-> (InitBehavior -> InitBehavior -> Bool)
-> (InitBehavior -> InitBehavior -> Bool)
-> (InitBehavior -> InitBehavior -> Bool)
-> (InitBehavior -> InitBehavior -> InitBehavior)
-> (InitBehavior -> InitBehavior -> InitBehavior)
-> Ord InitBehavior
InitBehavior -> InitBehavior -> Bool
InitBehavior -> InitBehavior -> Ordering
InitBehavior -> InitBehavior -> InitBehavior
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InitBehavior -> InitBehavior -> InitBehavior
$cmin :: InitBehavior -> InitBehavior -> InitBehavior
max :: InitBehavior -> InitBehavior -> InitBehavior
$cmax :: InitBehavior -> InitBehavior -> InitBehavior
>= :: InitBehavior -> InitBehavior -> Bool
$c>= :: InitBehavior -> InitBehavior -> Bool
> :: InitBehavior -> InitBehavior -> Bool
$c> :: InitBehavior -> InitBehavior -> Bool
<= :: InitBehavior -> InitBehavior -> Bool
$c<= :: InitBehavior -> InitBehavior -> Bool
< :: InitBehavior -> InitBehavior -> Bool
$c< :: InitBehavior -> InitBehavior -> Bool
compare :: InitBehavior -> InitBehavior -> Ordering
$ccompare :: InitBehavior -> InitBehavior -> Ordering
$cp1Ord :: Eq InitBehavior
Ord, (forall x. InitBehavior -> Rep InitBehavior x)
-> (forall x. Rep InitBehavior x -> InitBehavior)
-> Generic InitBehavior
forall x. Rep InitBehavior x -> InitBehavior
forall x. InitBehavior -> Rep InitBehavior x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InitBehavior x -> InitBehavior
$cfrom :: forall x. InitBehavior -> Rep InitBehavior x
Generic, InitBehavior -> ()
(InitBehavior -> ()) -> NFData InitBehavior
forall a. (a -> ()) -> NFData a
rnf :: InitBehavior -> ()
$crnf :: InitBehavior -> ()
NFData, Typeable InitBehavior
DataType
Constr
Typeable InitBehavior =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InitBehavior -> c InitBehavior)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InitBehavior)
-> (InitBehavior -> Constr)
-> (InitBehavior -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InitBehavior))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InitBehavior))
-> ((forall b. Data b => b -> b) -> InitBehavior -> InitBehavior)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r)
-> (forall u. (forall d. Data d => d -> u) -> InitBehavior -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> InitBehavior -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior)
-> Data InitBehavior
InitBehavior -> DataType
InitBehavior -> Constr
(forall b. Data b => b -> b) -> InitBehavior -> InitBehavior
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InitBehavior -> c InitBehavior
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InitBehavior
forall a.
Typeable a =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> InitBehavior -> u
forall u. (forall d. Data d => d -> u) -> InitBehavior -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InitBehavior
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InitBehavior -> c InitBehavior
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InitBehavior)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InitBehavior)
$cDefined :: Constr
$cUnknown :: Constr
$tInitBehavior :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
gmapMp :: (forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
gmapM :: (forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> InitBehavior -> m InitBehavior
gmapQi :: Int -> (forall d. Data d => d -> u) -> InitBehavior -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> InitBehavior -> u
gmapQ :: (forall d. Data d => d -> u) -> InitBehavior -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> InitBehavior -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InitBehavior -> r
gmapT :: (forall b. Data b => b -> b) -> InitBehavior -> InitBehavior
$cgmapT :: (forall b. Data b => b -> b) -> InitBehavior -> InitBehavior
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InitBehavior)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InitBehavior)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c InitBehavior)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InitBehavior)
dataTypeOf :: InitBehavior -> DataType
$cdataTypeOf :: InitBehavior -> DataType
toConstr :: InitBehavior -> Constr
$ctoConstr :: InitBehavior -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InitBehavior
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InitBehavior
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InitBehavior -> c InitBehavior
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InitBehavior -> c InitBehavior
$cp1Data :: Typeable InitBehavior
Data, Int -> InitBehavior -> Int
InitBehavior -> Int
(Int -> InitBehavior -> Int)
-> (InitBehavior -> Int) -> Hashable InitBehavior
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InitBehavior -> Int
$chash :: InitBehavior -> Int
hashWithSalt :: Int -> InitBehavior -> Int
$chashWithSalt :: Int -> InitBehavior -> Int
Hashable)
data SInitBehavior (init :: InitBehavior) where
SUnknown :: SInitBehavior 'Unknown
SDefined :: SInitBehavior 'Defined
instance Show (SInitBehavior init) where
show :: SInitBehavior init -> String
show SUnknown = "SUnknown"
show SDefined = "SDefined"
data DomainConfiguration
= DomainConfiguration
{ DomainConfiguration -> Domain
_name :: Domain
, DomainConfiguration -> Nat
_period :: Nat
, DomainConfiguration -> ActiveEdge
_activeEdge :: ActiveEdge
, DomainConfiguration -> ResetKind
_resetKind :: ResetKind
, DomainConfiguration -> InitBehavior
_initBehavior :: InitBehavior
, DomainConfiguration -> ResetPolarity
_resetPolarity :: ResetPolarity
}
deriving (Typeable)
type family DomainConfigurationPeriod (config :: DomainConfiguration) :: Nat where
DomainConfigurationPeriod ('DomainConfiguration name period edge reset init polarity) = period
type family DomainConfigurationActiveEdge (config :: DomainConfiguration) :: ActiveEdge where
DomainConfigurationActiveEdge ('DomainConfiguration name period edge reset init polarity) = edge
type family DomainConfigurationResetKind (config :: DomainConfiguration) :: ResetKind where
DomainConfigurationResetKind ('DomainConfiguration name period edge reset init polarity) = reset
type family DomainConfigurationInitBehavior (config :: DomainConfiguration) :: InitBehavior where
DomainConfigurationInitBehavior ('DomainConfiguration name period edge reset init polarity) = init
type family DomainConfigurationResetPolarity (config :: DomainConfiguration) :: ResetPolarity where
DomainConfigurationResetPolarity ('DomainConfiguration name period edge reset init polarity) = polarity
type DomainPeriod (dom :: Domain) =
DomainConfigurationPeriod (KnownConf dom)
type DomainActiveEdge (dom :: Domain) =
DomainConfigurationActiveEdge (KnownConf dom)
type DomainResetKind (dom :: Domain) =
DomainConfigurationResetKind (KnownConf dom)
type DomainInitBehavior (dom :: Domain) =
DomainConfigurationInitBehavior (KnownConf dom)
type DomainResetPolarity (dom :: Domain) =
DomainConfigurationResetPolarity (KnownConf dom)
data SDomainConfiguration (dom :: Domain) (conf :: DomainConfiguration) where
SDomainConfiguration
:: SSymbol dom
-> SNat period
-> SActiveEdge edge
-> SResetKind reset
-> SInitBehavior init
-> SResetPolarity polarity
-> SDomainConfiguration dom ('DomainConfiguration dom period edge reset init polarity)
deriving instance Show (SDomainConfiguration dom conf)
type KnownConfiguration dom conf = (KnownDomain dom, KnownConf dom ~ conf)
class KnownSymbol dom => KnownDomain (dom :: Domain) where
type KnownConf dom :: DomainConfiguration
knownDomain :: SDomainConfiguration dom (KnownConf dom)
knownDomainByName
:: forall dom
. KnownDomain dom
=> SSymbol dom
-> SDomainConfiguration dom (KnownConf dom)
knownDomainByName :: SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
knownDomainByName =
SDomainConfiguration dom (KnownConf dom)
-> SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
forall a b. a -> b -> a
const SDomainConfiguration dom (KnownConf dom)
forall (dom :: Domain).
KnownDomain dom =>
SDomainConfiguration dom (KnownConf dom)
knownDomain
{-# INLINE knownDomainByName #-}
instance KnownDomain System where
type KnownConf System = 'DomainConfiguration System 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh
knownDomain :: SDomainConfiguration System (KnownConf System)
knownDomain = SSymbol System
-> SNat 10000
-> SActiveEdge 'Rising
-> SResetKind 'Asynchronous
-> SInitBehavior 'Defined
-> SResetPolarity 'ActiveHigh
-> SDomainConfiguration
System
('DomainConfiguration
System 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh)
forall (dom :: Domain) (period :: Nat) (edge :: ActiveEdge)
(reset :: ResetKind) (init :: InitBehavior)
(polarity :: ResetPolarity).
SSymbol dom
-> SNat period
-> SActiveEdge edge
-> SResetKind reset
-> SInitBehavior init
-> SResetPolarity polarity
-> SDomainConfiguration
dom ('DomainConfiguration dom period edge reset init polarity)
SDomainConfiguration SSymbol System
forall (s :: Domain). KnownSymbol s => SSymbol s
SSymbol SNat 10000
forall (n :: Nat). KnownNat n => SNat n
SNat SActiveEdge 'Rising
SRising SResetKind 'Asynchronous
SAsynchronous SInitBehavior 'Defined
SDefined SResetPolarity 'ActiveHigh
SActiveHigh
instance KnownDomain XilinxSystem where
type KnownConf XilinxSystem = 'DomainConfiguration XilinxSystem 10000 'Rising 'Synchronous 'Defined 'ActiveHigh
knownDomain :: SDomainConfiguration XilinxSystem (KnownConf XilinxSystem)
knownDomain = SSymbol XilinxSystem
-> SNat 10000
-> SActiveEdge 'Rising
-> SResetKind 'Synchronous
-> SInitBehavior 'Defined
-> SResetPolarity 'ActiveHigh
-> SDomainConfiguration
XilinxSystem
('DomainConfiguration
XilinxSystem 10000 'Rising 'Synchronous 'Defined 'ActiveHigh)
forall (dom :: Domain) (period :: Nat) (edge :: ActiveEdge)
(reset :: ResetKind) (init :: InitBehavior)
(polarity :: ResetPolarity).
SSymbol dom
-> SNat period
-> SActiveEdge edge
-> SResetKind reset
-> SInitBehavior init
-> SResetPolarity polarity
-> SDomainConfiguration
dom ('DomainConfiguration dom period edge reset init polarity)
SDomainConfiguration SSymbol XilinxSystem
forall (s :: Domain). KnownSymbol s => SSymbol s
SSymbol SNat 10000
forall (n :: Nat). KnownNat n => SNat n
SNat SActiveEdge 'Rising
SRising SResetKind 'Synchronous
SSynchronous SInitBehavior 'Defined
SDefined SResetPolarity 'ActiveHigh
SActiveHigh
instance KnownDomain IntelSystem where
type KnownConf IntelSystem = 'DomainConfiguration IntelSystem 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh
knownDomain :: SDomainConfiguration IntelSystem (KnownConf IntelSystem)
knownDomain = SSymbol IntelSystem
-> SNat 10000
-> SActiveEdge 'Rising
-> SResetKind 'Asynchronous
-> SInitBehavior 'Defined
-> SResetPolarity 'ActiveHigh
-> SDomainConfiguration
IntelSystem
('DomainConfiguration
IntelSystem 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh)
forall (dom :: Domain) (period :: Nat) (edge :: ActiveEdge)
(reset :: ResetKind) (init :: InitBehavior)
(polarity :: ResetPolarity).
SSymbol dom
-> SNat period
-> SActiveEdge edge
-> SResetKind reset
-> SInitBehavior init
-> SResetPolarity polarity
-> SDomainConfiguration
dom ('DomainConfiguration dom period edge reset init polarity)
SDomainConfiguration SSymbol IntelSystem
forall (s :: Domain). KnownSymbol s => SSymbol s
SSymbol SNat 10000
forall (n :: Nat). KnownNat n => SNat n
SNat SActiveEdge 'Rising
SRising SResetKind 'Asynchronous
SAsynchronous SInitBehavior 'Defined
SDefined SResetPolarity 'ActiveHigh
SActiveHigh
vSystem :: VDomainConfiguration
vSystem :: VDomainConfiguration
vSystem = SDomainConfiguration
System
('DomainConfiguration
System 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh)
-> VDomainConfiguration
forall (dom :: Domain) (conf :: DomainConfiguration).
SDomainConfiguration dom conf -> VDomainConfiguration
vDomain (KnownDomain System =>
SDomainConfiguration System (KnownConf System)
forall (dom :: Domain).
KnownDomain dom =>
SDomainConfiguration dom (KnownConf dom)
knownDomain @System)
type System = ("System" :: Domain)
vIntelSystem :: VDomainConfiguration
vIntelSystem :: VDomainConfiguration
vIntelSystem = SDomainConfiguration
IntelSystem
('DomainConfiguration
IntelSystem 10000 'Rising 'Asynchronous 'Defined 'ActiveHigh)
-> VDomainConfiguration
forall (dom :: Domain) (conf :: DomainConfiguration).
SDomainConfiguration dom conf -> VDomainConfiguration
vDomain (KnownDomain IntelSystem =>
SDomainConfiguration IntelSystem (KnownConf IntelSystem)
forall (dom :: Domain).
KnownDomain dom =>
SDomainConfiguration dom (KnownConf dom)
knownDomain @IntelSystem)
type IntelSystem = ("IntelSystem" :: Domain)
vXilinxSystem :: VDomainConfiguration
vXilinxSystem :: VDomainConfiguration
vXilinxSystem = SDomainConfiguration
XilinxSystem
('DomainConfiguration
XilinxSystem 10000 'Rising 'Synchronous 'Defined 'ActiveHigh)
-> VDomainConfiguration
forall (dom :: Domain) (conf :: DomainConfiguration).
SDomainConfiguration dom conf -> VDomainConfiguration
vDomain (KnownDomain XilinxSystem =>
SDomainConfiguration XilinxSystem (KnownConf XilinxSystem)
forall (dom :: Domain).
KnownDomain dom =>
SDomainConfiguration dom (KnownConf dom)
knownDomain @XilinxSystem)
type XilinxSystem = ("XilinxSystem" :: Domain)
data VDomainConfiguration
= VDomainConfiguration
{ VDomainConfiguration -> String
vName :: String
, VDomainConfiguration -> Natural
vPeriod :: Natural
, VDomainConfiguration -> ActiveEdge
vActiveEdge :: ActiveEdge
, VDomainConfiguration -> ResetKind
vResetKind :: ResetKind
, VDomainConfiguration -> InitBehavior
vInitBehavior :: InitBehavior
, VDomainConfiguration -> ResetPolarity
vResetPolarity :: ResetPolarity
}
vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration
vDomain :: SDomainConfiguration dom conf -> VDomainConfiguration
vDomain (SDomainConfiguration dom :: SSymbol dom
dom period :: SNat period
period edge :: SActiveEdge edge
edge reset :: SResetKind reset
reset init_ :: SInitBehavior init
init_ polarity :: SResetPolarity polarity
polarity) =
String
-> Natural
-> ActiveEdge
-> ResetKind
-> InitBehavior
-> ResetPolarity
-> VDomainConfiguration
VDomainConfiguration
(SSymbol dom -> String
forall (s :: Domain). SSymbol s -> String
ssymbolToString SSymbol dom
dom)
(SNat period -> Natural
forall (n :: Nat). SNat n -> Natural
snatToNatural SNat period
period)
(case SActiveEdge edge
edge of {SRising -> ActiveEdge
Rising; SFalling -> ActiveEdge
Falling})
(case SResetKind reset
reset of {SAsynchronous -> ResetKind
Asynchronous; SSynchronous -> ResetKind
Synchronous})
(case SInitBehavior init
init_ of {SDefined -> InitBehavior
Defined; SUnknown -> InitBehavior
Unknown})
(case SResetPolarity polarity
polarity of {SActiveHigh -> ResetPolarity
ActiveHigh; SActiveLow -> ResetPolarity
ActiveLow})
isValidDomainName :: String -> Bool
isValidDomainName :: String -> Bool
isValidDomainName (x :: Char
x:xs :: String
xs) = Char -> Bool
isAsciiUpper Char
x Bool -> Bool -> Bool
&& (Char -> Bool) -> String -> Bool
forall (t :: Type -> Type) a.
Foldable t =>
(a -> Bool) -> t a -> Bool
all Char -> Bool
isAscii String
xs Bool -> Bool -> Bool
&& (Char -> Bool) -> String -> Bool
forall (t :: Type -> Type) a.
Foldable t =>
(a -> Bool) -> t a -> Bool
all Char -> Bool
isAlphaNum String
xs
isValidDomainName _ = Bool
False
createDomain :: VDomainConfiguration -> Q [Dec]
createDomain :: VDomainConfiguration -> Q [Dec]
createDomain (VDomainConfiguration name :: String
name period :: Natural
period edge :: ActiveEdge
edge reset :: ResetKind
reset init_ :: InitBehavior
init_ polarity :: ResetPolarity
polarity) =
if String -> Bool
isValidDomainName String
name then do
Type
kdType <- [t| KnownDomain $nameT |]
Type
kcType <- [t| ('DomainConfiguration $nameT $periodT $edgeT $resetKindT $initT $polarityT) |]
Exp
sDom <- [| SDomainConfiguration SSymbol SNat $edgeE $resetKindE $initE $polarityE |]
let vNameImpl :: Exp
vNameImpl = Exp -> Exp -> Exp
AppE (Name -> Exp
VarE 'vDomain) (Exp -> Type -> Exp
AppTypeE (Name -> Exp
VarE 'knownDomain) (TyLit -> Type
LitT (String -> TyLit
StrTyLit String
name)))
kdImpl :: Dec
kdImpl = Name -> [Clause] -> Dec
FunD 'knownDomain [[Pat] -> Body -> [Dec] -> Clause
Clause [] (Exp -> Body
NormalB Exp
sDom) []]
kcImpl :: Dec
kcImpl = Name -> [Type] -> Type -> Dec
mkTySynInstD ''KnownConf [TyLit -> Type
LitT (String -> TyLit
StrTyLit String
name)] Type
kcType
vName' :: Name
vName' = String -> Name
mkName ('v'Char -> ShowS
forall a. a -> [a] -> [a]
:String
name)
[Dec] -> Q [Dec]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure [
Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec
InstanceD Maybe Overlap
forall a. Maybe a
Nothing [] Type
kdType [Dec
kcImpl, Dec
kdImpl]
, Name -> [TyVarBndr] -> Type -> Dec
TySynD (String -> Name
mkName String
name) [] (TyLit -> Type
LitT (String -> TyLit
StrTyLit String
name) Type -> Type -> Type
`SigT` Name -> Type
ConT ''Domain)
, Name -> Type -> Dec
SigD Name
vName' (Name -> Type
ConT ''VDomainConfiguration)
, Name -> [Clause] -> Dec
FunD Name
vName' [[Pat] -> Body -> [Dec] -> Clause
Clause [] (Exp -> Body
NormalB Exp
vNameImpl) []]
]
else
String -> Q [Dec]
forall a. HasCallStack => String -> a
error ("Domain names should be a valid Haskell type name, not: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name)
where
edgeE :: Q Exp
edgeE =
Exp -> Q Exp
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Exp -> Q Exp) -> Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$
case ActiveEdge
edge of
Rising -> Name -> Exp
ConE 'SRising
Falling -> Name -> Exp
ConE 'SFalling
resetKindE :: Q Exp
resetKindE =
Exp -> Q Exp
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Exp -> Q Exp) -> Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$
case ResetKind
reset of
Asynchronous -> Name -> Exp
ConE 'SAsynchronous
Synchronous -> Name -> Exp
ConE 'SSynchronous
initE :: Q Exp
initE =
Exp -> Q Exp
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Exp -> Q Exp) -> Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$
case InitBehavior
init_ of
Unknown -> Name -> Exp
ConE 'SUnknown
Defined -> Name -> Exp
ConE 'SDefined
polarityE :: Q Exp
polarityE =
Exp -> Q Exp
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Exp -> Q Exp) -> Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$
case ResetPolarity
polarity of
ActiveHigh -> Name -> Exp
ConE 'SActiveHigh
ActiveLow -> Name -> Exp
ConE 'SActiveLow
nameT :: Q Type
nameT = Type -> Q Type
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (TyLit -> Type
LitT (String -> TyLit
StrTyLit String
name))
periodT :: Q Type
periodT = Type -> Q Type
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (TyLit -> Type
LitT (Integer -> TyLit
NumTyLit (Natural -> Integer
forall a. Integral a => a -> Integer
toInteger Natural
period)))
edgeT :: Q Type
edgeT =
Type -> Q Type
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Type -> Q Type) -> Type -> Q Type
forall a b. (a -> b) -> a -> b
$
case ActiveEdge
edge of
Rising -> Name -> Type
PromotedT 'Rising
Falling -> Name -> Type
PromotedT 'Falling
resetKindT :: Q Type
resetKindT =
Type -> Q Type
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Type -> Q Type) -> Type -> Q Type
forall a b. (a -> b) -> a -> b
$
case ResetKind
reset of
Asynchronous -> Name -> Type
PromotedT 'Asynchronous
Synchronous -> Name -> Type
PromotedT 'Synchronous
initT :: Q Type
initT =
Type -> Q Type
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Type -> Q Type) -> Type -> Q Type
forall a b. (a -> b) -> a -> b
$
case InitBehavior
init_ of
Unknown -> Name -> Type
PromotedT 'Unknown
Defined -> Name -> Type
PromotedT 'Defined
polarityT :: Q Type
polarityT =
Type -> Q Type
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Type -> Q Type) -> Type -> Q Type
forall a b. (a -> b) -> a -> b
$
case ResetPolarity
polarity of
ActiveHigh -> Name -> Type
PromotedT 'ActiveHigh
ActiveLow -> Name -> Type
PromotedT 'ActiveLow
type Domain = Symbol
infixr 5 :-
data Signal (dom :: Domain) a
= a :- Signal dom a
head# :: Signal dom a -> a
head# :: Signal dom a -> a
head# (x' :: a
x' :- _ ) = a
x'
tail# :: Signal dom a -> Signal dom a
tail# :: Signal dom a -> Signal dom a
tail# (_ :- xs' :: Signal dom a
xs') = Signal dom a
xs'
instance Show a => Show (Signal dom a) where
show :: Signal dom a -> String
show (x :: a
x :- xs :: Signal dom a
xs) = a -> String
forall a. Show a => a -> String
show a
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ " " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Signal dom a -> String
forall a. Show a => a -> String
show Signal dom a
xs
instance Lift a => Lift (Signal dom a) where
lift :: Signal dom a -> Q Exp
lift ~(x :: a
x :- _) = [| signal# x |]
instance Default a => Default (Signal dom a) where
def :: Signal dom a
def = a -> Signal dom a
forall a (dom :: Domain). a -> Signal dom a
signal# a
forall a. Default a => a
def
instance Functor (Signal dom) where
fmap :: (a -> b) -> Signal dom a -> Signal dom b
fmap = (a -> b) -> Signal dom a -> Signal dom b
forall a b (dom :: Domain).
(a -> b) -> Signal dom a -> Signal dom b
mapSignal#
mapSignal# :: (a -> b) -> Signal dom a -> Signal dom b
mapSignal# :: (a -> b) -> Signal dom a -> Signal dom b
mapSignal# f :: a -> b
f (a :: a
a :- as :: Signal dom a
as) = a -> b
f a
a b -> Signal dom b -> Signal dom b
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- (a -> b) -> Signal dom a -> Signal dom b
forall a b (dom :: Domain).
(a -> b) -> Signal dom a -> Signal dom b
mapSignal# a -> b
f Signal dom a
as
{-# NOINLINE mapSignal# #-}
{-# ANN mapSignal# hasBlackBox #-}
instance Applicative (Signal dom) where
pure :: a -> Signal dom a
pure = a -> Signal dom a
forall a (dom :: Domain). a -> Signal dom a
signal#
<*> :: Signal dom (a -> b) -> Signal dom a -> Signal dom b
(<*>) = Signal dom (a -> b) -> Signal dom a -> Signal dom b
forall (dom :: Domain) a b.
Signal dom (a -> b) -> Signal dom a -> Signal dom b
appSignal#
signal# :: a -> Signal dom a
signal# :: a -> Signal dom a
signal# a :: a
a = let s :: Signal dom a
s = a
a a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- Signal dom a
s in Signal dom a
s
{-# NOINLINE signal# #-}
{-# ANN signal# hasBlackBox #-}
appSignal# :: Signal dom (a -> b) -> Signal dom a -> Signal dom b
appSignal# :: Signal dom (a -> b) -> Signal dom a -> Signal dom b
appSignal# (f :: a -> b
f :- fs :: Signal dom (a -> b)
fs) xs :: Signal dom a
xs@(~(a :: a
a :- as :: Signal dom a
as)) = a -> b
f a
a b -> Signal dom b -> Signal dom b
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- (Signal dom a
xs Signal dom a -> Signal dom b -> Signal dom b
forall a b. a -> b -> b
`seq` Signal dom (a -> b) -> Signal dom a -> Signal dom b
forall (dom :: Domain) a b.
Signal dom (a -> b) -> Signal dom a -> Signal dom b
appSignal# Signal dom (a -> b)
fs Signal dom a
as)
{-# NOINLINE appSignal# #-}
{-# ANN appSignal# hasBlackBox #-}
joinSignal# :: Signal dom (Signal dom a) -> Signal dom a
joinSignal# :: Signal dom (Signal dom a) -> Signal dom a
joinSignal# ~(xs :: Signal dom a
xs :- xss :: Signal dom (Signal dom a)
xss) = Signal dom a -> a
forall (dom :: Domain) a. Signal dom a -> a
head# Signal dom a
xs a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- Signal dom (Signal dom a) -> Signal dom a
forall (dom :: Domain) a. Signal dom (Signal dom a) -> Signal dom a
joinSignal# ((Signal dom a -> Signal dom a)
-> Signal dom (Signal dom a) -> Signal dom (Signal dom a)
forall a b (dom :: Domain).
(a -> b) -> Signal dom a -> Signal dom b
mapSignal# Signal dom a -> Signal dom a
forall (dom :: Domain) a. Signal dom a -> Signal dom a
tail# Signal dom (Signal dom a)
xss)
{-# NOINLINE joinSignal# #-}
{-# ANN joinSignal# hasBlackBox #-}
instance Num a => Num (Signal dom a) where
+ :: Signal dom a -> Signal dom a -> Signal dom a
(+) = (a -> a -> a) -> Signal dom a -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(+)
(-) = (a -> a -> a) -> Signal dom a -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (-)
* :: Signal dom a -> Signal dom a -> Signal dom a
(*) = (a -> a -> a) -> Signal dom a -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Num a => a -> a -> a
(*)
negate :: Signal dom a -> Signal dom a
negate = (a -> a) -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
negate
abs :: Signal dom a -> Signal dom a
abs = (a -> a) -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
abs
signum :: Signal dom a -> Signal dom a
signum = (a -> a) -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
signum
fromInteger :: Integer -> Signal dom a
fromInteger = a -> Signal dom a
forall a (dom :: Domain). a -> Signal dom a
signal# (a -> Signal dom a) -> (Integer -> a) -> Integer -> Signal dom a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger
instance Foldable (Signal dom) where
foldr :: (a -> b -> b) -> b -> Signal dom a -> b
foldr = (a -> b -> b) -> b -> Signal dom a -> b
forall a b (dom :: Domain). (a -> b -> b) -> b -> Signal dom a -> b
foldr#
foldr# :: (a -> b -> b) -> b -> Signal dom a -> b
foldr# :: (a -> b -> b) -> b -> Signal dom a -> b
foldr# f :: a -> b -> b
f z :: b
z (a :: a
a :- s :: Signal dom a
s) = a
a a -> b -> b
`f` ((a -> b -> b) -> b -> Signal dom a -> b
forall a b (dom :: Domain). (a -> b -> b) -> b -> Signal dom a -> b
foldr# a -> b -> b
f b
z Signal dom a
s)
{-# NOINLINE foldr# #-}
{-# ANN foldr# hasBlackBox #-}
instance Traversable (Signal dom) where
traverse :: (a -> f b) -> Signal dom a -> f (Signal dom b)
traverse = (a -> f b) -> Signal dom a -> f (Signal dom b)
forall (f :: Type -> Type) a b (dom :: Domain).
Applicative f =>
(a -> f b) -> Signal dom a -> f (Signal dom b)
traverse#
traverse# :: Applicative f => (a -> f b) -> Signal dom a -> f (Signal dom b)
traverse# :: (a -> f b) -> Signal dom a -> f (Signal dom b)
traverse# f :: a -> f b
f (a :: a
a :- s :: Signal dom a
s) = b -> Signal dom b -> Signal dom b
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
(:-) (b -> Signal dom b -> Signal dom b)
-> f b -> f (Signal dom b -> Signal dom b)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a f (Signal dom b -> Signal dom b)
-> f (Signal dom b) -> f (Signal dom b)
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (a -> f b) -> Signal dom a -> f (Signal dom b)
forall (f :: Type -> Type) a b (dom :: Domain).
Applicative f =>
(a -> f b) -> Signal dom a -> f (Signal dom b)
traverse# a -> f b
f Signal dom a
s
{-# NOINLINE traverse# #-}
{-# ANN traverse# hasBlackBox #-}
newtype Enable dom = Enable (Signal dom Bool)
fromEnable :: Enable dom -> Signal dom Bool
fromEnable :: Enable dom -> Signal dom Bool
fromEnable = Enable dom -> Signal dom Bool
forall a b. Coercible a b => a -> b
coerce
{-# INLINE fromEnable #-}
toEnable :: Signal dom Bool -> Enable dom
toEnable :: Signal dom Bool -> Enable dom
toEnable = Signal dom Bool -> Enable dom
forall a b. Coercible a b => a -> b
coerce
{-# INLINE toEnable #-}
enableGen :: Enable dom
enableGen :: Enable dom
enableGen = Signal dom Bool -> Enable dom
forall (dom :: Domain). Signal dom Bool -> Enable dom
toEnable (Bool -> Signal dom Bool
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Bool
True)
data Clock (dom :: Domain) = Clock (SSymbol dom)
instance Show (Clock dom) where
show :: Clock dom -> String
show (Clock dom :: SSymbol dom
dom) = "<Clock: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SSymbol dom -> String
forall (s :: Domain). SSymbol s -> String
ssymbolToString SSymbol dom
dom String -> ShowS
forall a. [a] -> [a] -> [a]
++ ">"
clockTag
:: Clock dom
-> SSymbol dom
clockTag :: Clock dom -> SSymbol dom
clockTag (Clock dom :: SSymbol dom
dom) = SSymbol dom
dom
clockGen
:: KnownDomain dom
=> Clock dom
clockGen :: Clock dom
clockGen = SSymbol dom -> Clock dom
forall (dom :: Domain). SSymbol dom -> Clock dom
Clock SSymbol dom
forall (s :: Domain). KnownSymbol s => SSymbol s
SSymbol
{-# NOINLINE clockGen #-}
{-# ANN clockGen hasBlackBox #-}
resetGen
:: forall dom
. KnownDomain dom
=> Reset dom
resetGen :: Reset dom
resetGen = SNat 1 -> Reset dom
forall (dom :: Domain) (n :: Nat).
(KnownDomain dom, 1 <= n) =>
SNat n -> Reset dom
resetGenN (KnownNat 1 => SNat 1
forall (n :: Nat). KnownNat n => SNat n
SNat @1)
{-# INLINE resetGen #-}
resetGenN
:: forall dom n
. (KnownDomain dom, 1 <= n)
=> SNat n
-> Reset dom
resetGenN :: SNat n -> Reset dom
resetGenN n :: SNat n
n =
let asserted :: [Bool]
asserted = Int -> Bool -> [Bool]
forall a. Int -> a -> [a]
replicate (SNat n -> Int
forall a (n :: Nat). Num a => SNat n -> a
snatToNum SNat n
n) Bool
True in
Signal dom Bool -> Reset dom
forall (dom :: Domain).
KnownDomain dom =>
Signal dom Bool -> Reset dom
unsafeFromHighPolarity ([Bool] -> Signal dom Bool
forall a (dom :: Domain). NFDataX a => [a] -> Signal dom a
fromList ([Bool]
asserted [Bool] -> [Bool] -> [Bool]
forall a. [a] -> [a] -> [a]
++ Bool -> [Bool]
forall a. a -> [a]
repeat Bool
False))
{-# ANN resetGenN hasBlackBox #-}
{-# NOINLINE resetGenN #-}
data Reset (dom :: Domain) = Reset (Signal dom Bool)
resetPolarityProxy
:: forall dom proxy polarity
. (KnownDomain dom, DomainResetPolarity dom ~ polarity)
=> proxy dom
-> SResetPolarity polarity
resetPolarityProxy :: proxy dom -> SResetPolarity polarity
resetPolarityProxy _proxy :: proxy dom
_proxy =
case KnownDomain dom => SDomainConfiguration dom (KnownConf dom)
forall (dom :: Domain).
KnownDomain dom =>
SDomainConfiguration dom (KnownConf dom)
knownDomain @dom of
SDomainConfiguration _dom :: SSymbol dom
_dom _period :: SNat period
_period _edge :: SActiveEdge edge
_edge _sync :: SResetKind reset
_sync _init :: SInitBehavior init
_init polarity :: SResetPolarity polarity
polarity ->
SResetPolarity polarity
SResetPolarity polarity
polarity
unsafeToHighPolarity
:: forall dom
. KnownDomain dom
=> Reset dom
-> Signal dom Bool
unsafeToHighPolarity :: Reset dom -> Signal dom Bool
unsafeToHighPolarity (Reset dom -> Signal dom Bool
forall (dom :: Domain). Reset dom -> Signal dom Bool
unsafeFromReset -> Signal dom Bool
r) =
case Proxy dom
-> SResetPolarity
(DomainConfigurationResetPolarity (KnownConf dom))
forall (dom :: Domain) (proxy :: Domain -> Type)
(polarity :: ResetPolarity).
(KnownDomain dom, DomainResetPolarity dom ~ polarity) =>
proxy dom -> SResetPolarity polarity
resetPolarityProxy (Proxy dom
forall k (t :: k). Proxy t
Proxy @dom) of
SActiveHigh -> Signal dom Bool
r
SActiveLow -> Bool -> Bool
not (Bool -> Bool) -> Signal dom Bool -> Signal dom Bool
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom Bool
r
{-# INLINE unsafeToHighPolarity #-}
unsafeToLowPolarity
:: forall dom
. KnownDomain dom
=> Reset dom
-> Signal dom Bool
unsafeToLowPolarity :: Reset dom -> Signal dom Bool
unsafeToLowPolarity (Reset dom -> Signal dom Bool
forall (dom :: Domain). Reset dom -> Signal dom Bool
unsafeFromReset -> Signal dom Bool
r) =
case Proxy dom
-> SResetPolarity
(DomainConfigurationResetPolarity (KnownConf dom))
forall (dom :: Domain) (proxy :: Domain -> Type)
(polarity :: ResetPolarity).
(KnownDomain dom, DomainResetPolarity dom ~ polarity) =>
proxy dom -> SResetPolarity polarity
resetPolarityProxy (Proxy dom
forall k (t :: k). Proxy t
Proxy @dom) of
SActiveHigh -> Bool -> Bool
not (Bool -> Bool) -> Signal dom Bool -> Signal dom Bool
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom Bool
r
SActiveLow -> Signal dom Bool
r
{-# INLINE unsafeToLowPolarity #-}
unsafeFromReset
:: Reset dom
-> Signal dom Bool
unsafeFromReset :: Reset dom -> Signal dom Bool
unsafeFromReset (Reset r :: Signal dom Bool
r) = Signal dom Bool
r
{-# NOINLINE unsafeFromReset #-}
{-# ANN unsafeFromReset hasBlackBox #-}
unsafeToReset
:: Signal dom Bool
-> Reset dom
unsafeToReset :: Signal dom Bool -> Reset dom
unsafeToReset r :: Signal dom Bool
r = Signal dom Bool -> Reset dom
forall (dom :: Domain). Signal dom Bool -> Reset dom
Reset Signal dom Bool
r
{-# NOINLINE unsafeToReset #-}
{-# ANN unsafeToReset hasBlackBox #-}
unsafeFromHighPolarity
:: forall dom
. KnownDomain dom
=> Signal dom Bool
-> Reset dom
unsafeFromHighPolarity :: Signal dom Bool -> Reset dom
unsafeFromHighPolarity r :: Signal dom Bool
r =
Signal dom Bool -> Reset dom
forall (dom :: Domain). Signal dom Bool -> Reset dom
unsafeToReset (Signal dom Bool -> Reset dom) -> Signal dom Bool -> Reset dom
forall a b. (a -> b) -> a -> b
$
case Proxy dom
-> SResetPolarity
(DomainConfigurationResetPolarity (KnownConf dom))
forall (dom :: Domain) (proxy :: Domain -> Type)
(polarity :: ResetPolarity).
(KnownDomain dom, DomainResetPolarity dom ~ polarity) =>
proxy dom -> SResetPolarity polarity
resetPolarityProxy (Proxy dom
forall k (t :: k). Proxy t
Proxy @dom) of
SActiveHigh -> Signal dom Bool
r
SActiveLow -> Bool -> Bool
not (Bool -> Bool) -> Signal dom Bool -> Signal dom Bool
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom Bool
r
unsafeFromLowPolarity
:: forall dom
. KnownDomain dom
=> Signal dom Bool
-> Reset dom
unsafeFromLowPolarity :: Signal dom Bool -> Reset dom
unsafeFromLowPolarity r :: Signal dom Bool
r =
Signal dom Bool -> Reset dom
forall (dom :: Domain). Signal dom Bool -> Reset dom
unsafeToReset (Signal dom Bool -> Reset dom) -> Signal dom Bool -> Reset dom
forall a b. (a -> b) -> a -> b
$
case Proxy dom
-> SResetPolarity
(DomainConfigurationResetPolarity (KnownConf dom))
forall (dom :: Domain) (proxy :: Domain -> Type)
(polarity :: ResetPolarity).
(KnownDomain dom, DomainResetPolarity dom ~ polarity) =>
proxy dom -> SResetPolarity polarity
resetPolarityProxy (Proxy dom
forall k (t :: k). Proxy t
Proxy @dom) of
SActiveHigh -> Bool -> Bool
not (Bool -> Bool) -> Signal dom Bool -> Signal dom Bool
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom Bool
r
SActiveLow -> Signal dom Bool
r
invertReset :: Reset dom -> Reset dom
invertReset :: Reset dom -> Reset dom
invertReset = Signal dom Bool -> Reset dom
forall (dom :: Domain). Signal dom Bool -> Reset dom
unsafeToReset (Signal dom Bool -> Reset dom)
-> (Reset dom -> Signal dom Bool) -> Reset dom -> Reset dom
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Bool) -> Signal dom Bool -> Signal dom Bool
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Bool
not (Signal dom Bool -> Signal dom Bool)
-> (Reset dom -> Signal dom Bool) -> Reset dom -> Signal dom Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Reset dom -> Signal dom Bool
forall (dom :: Domain). Reset dom -> Signal dom Bool
unsafeFromReset
infixr 2 .||.
(.||.) :: Applicative f => f Bool -> f Bool -> f Bool
.||. :: f Bool -> f Bool -> f Bool
(.||.) = (Bool -> Bool -> Bool) -> f Bool -> f Bool -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Bool -> Bool -> Bool
(||)
infixr 3 .&&.
(.&&.) :: Applicative f => f Bool -> f Bool -> f Bool
.&&. :: f Bool -> f Bool -> f Bool
(.&&.) = (Bool -> Bool -> Bool) -> f Bool -> f Bool -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Bool -> Bool -> Bool
(&&)
delay#
:: forall dom a
. ( KnownDomain dom
, NFDataX a )
=> Clock dom
-> Enable dom
-> a
-> Signal dom a
-> Signal dom a
delay# :: Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a
delay# (Clock dom :: SSymbol dom
dom) (Enable dom -> Signal dom Bool
forall (dom :: Domain). Enable dom -> Signal dom Bool
fromEnable -> Signal dom Bool
en) powerUpVal0 :: a
powerUpVal0 =
a -> Signal dom Bool -> Signal dom a -> Signal dom a
forall t (dom :: Domain) (dom :: Domain) (dom :: Domain).
NFDataX t =>
t -> Signal dom Bool -> Signal dom t -> Signal dom t
go a
powerUpVal1 Signal dom Bool
en
where
powerUpVal1 :: a
powerUpVal1 :: a
powerUpVal1 =
case SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
forall (dom :: Domain).
KnownDomain dom =>
SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
knownDomainByName SSymbol dom
dom of
SDomainConfiguration _dom :: SSymbol dom
_dom _period :: SNat period
_period _edge :: SActiveEdge edge
_edge _sync :: SResetKind reset
_sync SDefined _polarity :: SResetPolarity polarity
_polarity ->
a
powerUpVal0
SDomainConfiguration _dom :: SSymbol dom
_dom _period :: SNat period
_period _edge :: SActiveEdge edge
_edge _sync :: SResetKind reset
_sync SUnknown _polarity :: SResetPolarity polarity
_polarity ->
String -> a
forall a. (NFDataX a, HasCallStack) => String -> a
deepErrorX ("First value of `delay` unknown on domain " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SSymbol dom -> String
forall a. Show a => a -> String
show SSymbol dom
dom)
go :: t -> Signal dom Bool -> Signal dom t -> Signal dom t
go o :: t
o (e :: Bool
e :- es :: Signal dom Bool
es) as :: Signal dom t
as@(~(x :: t
x :- xs :: Signal dom t
xs)) =
let o' :: t
o' = if Bool
e then t
x else t
o
in t
o t -> t -> t
forall a b. NFDataX a => a -> b -> b
`defaultSeqX` t
o t -> Signal dom t -> Signal dom t
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- (Signal dom t
as Signal dom t -> Signal dom t -> Signal dom t
forall a b. a -> b -> b
`seq` t -> Signal dom Bool -> Signal dom t -> Signal dom t
go t
o' Signal dom Bool
es Signal dom t
xs)
{-# NOINLINE delay# #-}
{-# ANN delay# hasBlackBox #-}
register#
:: forall dom a
. ( KnownDomain dom
, NFDataX a )
=> Clock dom
-> Reset dom
-> Enable dom
-> a
-> a
-> Signal dom a
-> Signal dom a
register# :: Clock dom
-> Reset dom
-> Enable dom
-> a
-> a
-> Signal dom a
-> Signal dom a
register# (Clock dom :: SSymbol dom
dom) rst :: Reset dom
rst (Enable dom -> Signal dom Bool
forall (dom :: Domain). Enable dom -> Signal dom Bool
fromEnable -> Signal dom Bool
ena) powerUpVal0 :: a
powerUpVal0 resetVal :: a
resetVal =
case SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
forall (dom :: Domain).
KnownDomain dom =>
SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
knownDomainByName SSymbol dom
dom of
SDomainConfiguration _name :: SSymbol dom
_name _period :: SNat period
_period _edge :: SActiveEdge edge
_edge SSynchronous _init :: SInitBehavior init
_init _polarity :: SResetPolarity polarity
_polarity ->
a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goSync a
powerUpVal1 (Reset dom -> Signal dom Bool
forall (dom :: Domain).
KnownDomain dom =>
Reset dom -> Signal dom Bool
unsafeToHighPolarity Reset dom
rst) Signal dom Bool
ena
SDomainConfiguration _name :: SSymbol dom
_name _period :: SNat period
_period _edge :: SActiveEdge edge
_edge SAsynchronous _init :: SInitBehavior init
_init _polarity :: SResetPolarity polarity
_polarity ->
a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goAsync a
powerUpVal1 (Reset dom -> Signal dom Bool
forall (dom :: Domain).
KnownDomain dom =>
Reset dom -> Signal dom Bool
unsafeToHighPolarity Reset dom
rst) Signal dom Bool
ena
where
powerUpVal1 :: a
powerUpVal1 :: a
powerUpVal1 =
case SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
forall (dom :: Domain).
KnownDomain dom =>
SSymbol dom -> SDomainConfiguration dom (KnownConf dom)
knownDomainByName SSymbol dom
dom of
SDomainConfiguration _dom :: SSymbol dom
_dom _period :: SNat period
_period _edge :: SActiveEdge edge
_edge _sync :: SResetKind reset
_sync SDefined _polarity :: SResetPolarity polarity
_polarity ->
a
powerUpVal0
SDomainConfiguration _dom :: SSymbol dom
_dom _period :: SNat period
_period _edge :: SActiveEdge edge
_edge _sync :: SResetKind reset
_sync SUnknown _polarity :: SResetPolarity polarity
_polarity ->
String -> a
forall a. (NFDataX a, HasCallStack) => String -> a
deepErrorX ("First value of register undefined on domain " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SSymbol dom -> String
forall a. Show a => a -> String
show SSymbol dom
dom)
goSync
:: a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goSync :: a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goSync o :: a
o rt :: Signal dom Bool
rt@(~(r :: Bool
r :- rs :: Signal dom Bool
rs)) enas :: Signal dom Bool
enas@(~(e :: Bool
e :- es :: Signal dom Bool
es)) as :: Signal dom a
as@(~(x :: a
x :- xs :: Signal dom a
xs)) =
let oE :: a
oE = if Bool
e then a
x else a
o
oR :: a
oR = if Bool
r then a
resetVal else a
oE
in a
o a -> a -> a
forall a b. NFDataX a => a -> b -> b
`defaultSeqX` a
o a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- (Signal dom Bool
rt Signal dom Bool -> Signal dom a -> Signal dom a
forall a b. a -> b -> b
`seq` Signal dom Bool
enas Signal dom Bool -> Signal dom a -> Signal dom a
forall a b. a -> b -> b
`seq` Signal dom a
as Signal dom a -> Signal dom a -> Signal dom a
forall a b. a -> b -> b
`seq` a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goSync a
oR Signal dom Bool
rs Signal dom Bool
es Signal dom a
xs)
goAsync
:: a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goAsync :: a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goAsync o :: a
o (r :: Bool
r :- rs :: Signal dom Bool
rs) enas :: Signal dom Bool
enas@(~(e :: Bool
e :- es :: Signal dom Bool
es)) as :: Signal dom a
as@(~(x :: a
x :- xs :: Signal dom a
xs)) =
let oR :: a
oR = if Bool
r then a
resetVal else a
o
oE :: a
oE = if Bool
r then a
resetVal else (if Bool
e then a
x else a
o)
in a
oR a -> a -> a
forall a b. NFDataX a => a -> b -> b
`defaultSeqX` a
oR a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- (Signal dom a
as Signal dom a -> Signal dom a -> Signal dom a
forall a b. a -> b -> b
`seq` Signal dom Bool
enas Signal dom Bool -> Signal dom a -> Signal dom a
forall a b. a -> b -> b
`seq` a
-> Signal dom Bool
-> Signal dom Bool
-> Signal dom a
-> Signal dom a
goAsync a
oE Signal dom Bool
rs Signal dom Bool
es Signal dom a
xs)
{-# NOINLINE register# #-}
{-# ANN register# hasBlackBox #-}
mux :: Applicative f => f Bool -> f a -> f a -> f a
mux :: f Bool -> f a -> f a -> f a
mux = (Bool -> a -> a -> a) -> f Bool -> f a -> f a -> f a
forall (f :: Type -> Type) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 (\b :: Bool
b t :: a
t f :: a
f -> if Bool
b then a
t else a
f)
{-# INLINE mux #-}
infix 4 .==.
(.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
.==. :: f a -> f a -> f Bool
(.==.) = (a -> a -> Bool) -> f a -> f a -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
infix 4 ./=.
(./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
./=. :: f a -> f a -> f Bool
(./=.) = (a -> a -> Bool) -> f a -> f a -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
infix 4 .<.
(.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
.<. :: f a -> f a -> f Bool
(.<.) = (a -> a -> Bool) -> f a -> f a -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<)
infix 4 .<=.
(.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
.<=. :: f a -> f a -> f Bool
(.<=.) = (a -> a -> Bool) -> f a -> f a -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
infix 4 .>.
(.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
.>. :: f a -> f a -> f Bool
(.>.) = (a -> a -> Bool) -> f a -> f a -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>)
infix 4 .>=.
(.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
.>=. :: f a -> f a -> f Bool
(.>=.) = (a -> a -> Bool) -> f a -> f a -> f Bool
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>=)
instance Fractional a => Fractional (Signal dom a) where
/ :: Signal dom a -> Signal dom a -> Signal dom a
(/) = (a -> a -> a) -> Signal dom a -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Fractional a => a -> a -> a
(/)
recip :: Signal dom a -> Signal dom a
recip = (a -> a) -> Signal dom a -> Signal dom a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Fractional a => a -> a
recip
fromRational :: Rational -> Signal dom a
fromRational = a -> Signal dom a
forall a (dom :: Domain). a -> Signal dom a
signal# (a -> Signal dom a) -> (Rational -> a) -> Rational -> Signal dom a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> a
forall a. Fractional a => Rational -> a
fromRational
instance Arbitrary a => Arbitrary (Signal dom a) where
arbitrary :: Gen (Signal dom a)
arbitrary = (a -> Signal dom a -> Signal dom a)
-> Gen a -> Gen (Signal dom a) -> Gen (Signal dom a)
forall (f :: Type -> Type) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
(:-) Gen a
forall a. Arbitrary a => Gen a
arbitrary Gen (Signal dom a)
forall a. Arbitrary a => Gen a
arbitrary
instance CoArbitrary a => CoArbitrary (Signal dom a) where
coarbitrary :: Signal dom a -> Gen b -> Gen b
coarbitrary xs :: Signal dom a
xs gen :: Gen b
gen = do
Int
n <- Gen Int
forall a. Arbitrary a => Gen a
arbitrary
[a] -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take (Int -> Int
forall a. Num a => a -> a
abs Int
n) (Signal dom a -> [a]
forall (f :: Type -> Type) a. Foldable f => f a -> [a]
sample_lazy Signal dom a
xs)) Gen b
gen
testFor :: Foldable f => Int -> f Bool -> Property
testFor :: Int -> f Bool -> Property
testFor n :: Int
n = Bool -> Property
forall prop. Testable prop => prop -> Property
property (Bool -> Property) -> (f Bool -> Bool) -> f Bool -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Bool] -> Bool
forall (t :: Type -> Type). Foldable t => t Bool -> Bool
and ([Bool] -> Bool) -> (f Bool -> [Bool]) -> f Bool -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Bool] -> [Bool]
forall a. Int -> [a] -> [a]
take Int
n ([Bool] -> [Bool]) -> (f Bool -> [Bool]) -> f Bool -> [Bool]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f Bool -> [Bool]
forall (f :: Type -> Type) a. (Foldable f, NFDataX a) => f a -> [a]
sample
sample :: (Foldable f, NFDataX a) => f a -> [a]
sample :: f a -> [a]
sample = (a -> [a] -> [a]) -> [a] -> f a -> [a]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a :: a
a b :: [a]
b -> a -> [a] -> [a]
forall a b. NFDataX a => a -> b -> b
deepseqX a
a (a
a a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
b)) []
sampleN :: (Foldable f, NFDataX a) => Int -> f a -> [a]
sampleN :: Int -> f a -> [a]
sampleN n :: Int
n = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
n ([a] -> [a]) -> (f a -> [a]) -> f a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [a]
forall (f :: Type -> Type) a. (Foldable f, NFDataX a) => f a -> [a]
sample
fromList :: NFDataX a => [a] -> Signal dom a
fromList :: [a] -> Signal dom a
fromList = (a -> Signal dom a -> Signal dom a)
-> Signal dom a -> [a] -> Signal dom a
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Prelude.foldr (\a :: a
a b :: Signal dom a
b -> a -> Signal dom a -> Signal dom a
forall a b. NFDataX a => a -> b -> b
deepseqX a
a (a
a a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
:- Signal dom a
b)) (String -> Signal dom a
forall a. HasCallStack => String -> a
errorX "finite list")
simulate :: (NFDataX a, NFDataX b) => (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
simulate :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
simulate f :: Signal dom1 a -> Signal dom2 b
f = Signal dom2 b -> [b]
forall (f :: Type -> Type) a. (Foldable f, NFDataX a) => f a -> [a]
sample (Signal dom2 b -> [b]) -> ([a] -> Signal dom2 b) -> [a] -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Signal dom1 a -> Signal dom2 b
f (Signal dom1 a -> Signal dom2 b)
-> ([a] -> Signal dom1 a) -> [a] -> Signal dom2 b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Signal dom1 a
forall a (dom :: Domain). NFDataX a => [a] -> Signal dom a
fromList
sample_lazy :: Foldable f => f a -> [a]
sample_lazy :: f a -> [a]
sample_lazy = (a -> [a] -> [a]) -> [a] -> f a -> [a]
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (:) []
sampleN_lazy :: Foldable f => Int -> f a -> [a]
sampleN_lazy :: Int -> f a -> [a]
sampleN_lazy n :: Int
n = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
n ([a] -> [a]) -> (f a -> [a]) -> f a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [a]
forall (f :: Type -> Type) a. Foldable f => f a -> [a]
sample_lazy
fromList_lazy :: [a] -> Signal dom a
fromList_lazy :: [a] -> Signal dom a
fromList_lazy = (a -> Signal dom a -> Signal dom a)
-> Signal dom a -> [a] -> Signal dom a
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Prelude.foldr a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a. a -> Signal dom a -> Signal dom a
(:-) (String -> Signal dom a
forall a. HasCallStack => String -> a
error "finite list")
simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
simulate_lazy :: (Signal dom1 a -> Signal dom2 b) -> [a] -> [b]
simulate_lazy f :: Signal dom1 a -> Signal dom2 b
f = Signal dom2 b -> [b]
forall (f :: Type -> Type) a. Foldable f => f a -> [a]
sample_lazy (Signal dom2 b -> [b]) -> ([a] -> Signal dom2 b) -> [a] -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Signal dom1 a -> Signal dom2 b
f (Signal dom1 a -> Signal dom2 b)
-> ([a] -> Signal dom1 a) -> [a] -> Signal dom2 b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Signal dom1 a
forall a (dom :: Domain). [a] -> Signal dom a
fromList_lazy
hzToPeriod :: HasCallStack => Double -> Natural
hzToPeriod :: Double -> Natural
hzToPeriod freq :: Double
freq | Double
freq Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= 0.0 = String -> Natural
forall a. HasCallStack => String -> a
error "Frequency must be strictly positive"
| Bool
otherwise = Double -> Natural
forall a b. (RealFrac a, Integral b) => a -> b
ceiling ((1.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
freq) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ 1.0e-12)
periodToHz :: Natural -> Double
periodToHz :: Natural -> Double
periodToHz period :: Natural
period = 1.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (1.0e-12 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Natural -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
period)