retroclash-lib-0.1.2.2: Code shared across the code samples in the book "Retrocomputing with Clash"
Safe HaskellSafe-Inferred
LanguageHaskell2010

RetroClash.Utils

Documentation

withEnableGen :: KnownDomain dom => (HiddenClockResetEnable dom => r) -> Clock dom -> Reset dom -> r Source #

withStart :: HiddenClockResetEnable dom => a -> Signal dom a -> Signal dom a Source #

data Polarity Source #

Constructors

High 
Low 

Instances

Instances details
Show Polarity Source # 
Instance details

Defined in RetroClash.Utils

Eq Polarity Source # 
Instance details

Defined in RetroClash.Utils

data Active (p :: Polarity) Source #

Instances

Instances details
Generic (Active p) Source # 
Instance details

Defined in RetroClash.Utils

Associated Types

type Rep (Active p) :: Type -> Type #

Methods

from :: Active p -> Rep (Active p) x #

to :: Rep (Active p) x -> Active p #

Show (Active p) Source # 
Instance details

Defined in RetroClash.Utils

Methods

showsPrec :: Int -> Active p -> ShowS #

show :: Active p -> String #

showList :: [Active p] -> ShowS #

BitPack (Active p) Source # 
Instance details

Defined in RetroClash.Utils

Associated Types

type BitSize (Active p) :: Nat #

NFDataX (Active p) Source # 
Instance details

Defined in RetroClash.Utils

Methods

deepErrorX :: String -> Active p #

hasUndefined :: Active p -> Bool #

ensureSpine :: Active p -> Active p #

rnfX :: Active p -> () #

Eq (Active p) Source # 
Instance details

Defined in RetroClash.Utils

Methods

(==) :: Active p -> Active p -> Bool #

(/=) :: Active p -> Active p -> Bool #

Ord (Active p) Source # 
Instance details

Defined in RetroClash.Utils

Methods

compare :: Active p -> Active p -> Ordering #

(<) :: Active p -> Active p -> Bool #

(<=) :: Active p -> Active p -> Bool #

(>) :: Active p -> Active p -> Bool #

(>=) :: Active p -> Active p -> Bool #

max :: Active p -> Active p -> Active p #

min :: Active p -> Active p -> Active p #

type Rep (Active p) Source # 
Instance details

Defined in RetroClash.Utils

type Rep (Active p) = D1 ('MetaData "Active" "RetroClash.Utils" "retroclash-lib-0.1.2.2-8zTx05WshYzIbWBY4X0pgW" 'True) (C1 ('MetaCons "MkActive" 'PrefixI 'True) (S1 ('MetaSel ('Just "activeLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bit)))
type BitSize (Active p) Source # 
Instance details

Defined in RetroClash.Utils

class IsActive p where Source #

Instances

Instances details
IsActive 'High Source # 
Instance details

Defined in RetroClash.Utils

IsActive 'Low Source # 
Instance details

Defined in RetroClash.Utils

bitwise :: BitPack a => (BitVector (BitSize a) -> BitVector (BitSize a)) -> a -> a Source #

parity :: forall a n. (BitPack a, BitSize a ~ (n + 1)) => a -> Bit Source #

half :: Bits a => a -> a Source #

halfIndex :: (KnownNat n, 1 <= (2 * n), CLog 2 (2 * n) ~ (CLog 2 n + 1)) => Index (2 * n) -> Index n Source #

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

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

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

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

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

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

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

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

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

(.!!.) :: (KnownNat n, Enum i, Applicative f) => f (Vec n a) -> f i -> f a Source #

(.!!) :: (KnownNat n, Enum i, Functor f) => f (Vec n a) -> i -> f a Source #

(!!.) :: (KnownNat n, Enum i, Functor f) => Vec n a -> f i -> f a Source #

changed :: (HiddenClockResetEnable dom, Eq a, NFDataX a) => a -> Signal dom a -> Signal dom Bool Source #

integrate :: (Monoid a, NFDataX a, HiddenClockResetEnable dom) => Signal dom Bool -> Signal dom a -> Signal dom a Source #

debounce :: forall ps a dom. (Eq a, NFDataX a, HiddenClockResetEnable dom, KnownNat (ClockDivider dom ps)) => SNat ps -> a -> Signal dom a -> Signal dom a Source #

riseEveryWhen :: forall n dom. (HiddenClockResetEnable dom, KnownNat n) => SNat n -> Signal dom Bool -> Signal dom Bool Source #

oneHot :: forall n. KnownNat n => Index n -> Vec n Bool Source #

roundRobin :: forall n dom a. (KnownNat n, HiddenClockResetEnable dom) => Signal dom Bool -> (Signal dom (Vec n Bool), Signal dom (Index n)) Source #

countFromTo :: (Eq a, Enum a, NFDataX a, HiddenClockResetEnable dom) => a -> a -> Signal dom Bool -> Signal dom a Source #

nextIdx :: (Eq a, Enum a, Bounded a) => a -> a Source #

prevIdx :: (Eq a, Enum a, Bounded a) => a -> a Source #

succIdx :: (Eq a, Enum a, Bounded a) => a -> Maybe a Source #

predIdx :: (Eq a, Enum a, Bounded a) => a -> Maybe a Source #

moreIdx :: (Eq a, Enum a, Bounded a) => a -> a Source #

lessIdx :: (Eq a, Enum a, Bounded a) => a -> a Source #

mealyState :: (HiddenClockResetEnable dom, NFDataX s) => (i -> State s o) -> s -> Signal dom i -> Signal dom o Source #

mealyStateB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o Source #

mooreState :: (HiddenClockResetEnable dom, NFDataX s) => (i -> State s ()) -> (s -> o) -> s -> Signal dom i -> Signal dom o Source #

mooreStateB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (i -> State s ()) -> (s -> o) -> s -> Unbundled dom i -> Unbundled dom o Source #

enable :: Applicative f => f Bool -> f a -> f (Maybe a) Source #

guardA :: (Applicative f, Alternative m) => f Bool -> f (m a) -> f (m a) Source #

muxA :: (Foldable t, Alternative m, Applicative f) => t (f (m a)) -> f (m a) Source #

(.<|>.) :: (Applicative f, Alternative m) => f (m a) -> f (m a) -> f (m a) infixl 3 Source #

(.|>.) :: Applicative f => f a -> f (Maybe a) -> f a infix 2 Source #

(|>.) :: Applicative f => a -> f (Maybe a) -> f a infix 2 Source #

(.<|.) :: Applicative f => f (Maybe a) -> f a -> f a infix 2 Source #

(.<|) :: Applicative f => f (Maybe a) -> a -> f a infix 2 Source #

muxMaybe :: Applicative f => f a -> f (Maybe a) -> f a Source #

packWrite :: addr -> Maybe val -> Maybe (addr, val) Source #

noWrite :: Applicative f => f (Maybe addr) -> f (Maybe (addr, Maybe wr)) Source #

withWrite :: Applicative f => f (Maybe addr) -> f (Maybe wr) -> f (Maybe (addr, Maybe wr)) Source #

singlePort :: Applicative f => (f addr -> f (Maybe (addr, wr)) -> r) -> f addr -> f (Maybe wr) -> r Source #

unbraid :: (KnownNat n, KnownNat k, 1 <= n, 1 <= (n * (2 ^ k)), CLog 2 (2 ^ k) ~ k, CLog 2 (n * (2 ^ k)) ~ (CLog 2 n + k)) => Maybe (Index (n * (2 ^ k))) -> Vec (2 ^ k) (Maybe (Index n)) Source #