{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
module Clash.Xilinx.ClockGen where
import Clash.Annotations.Primitive (hasBlackBox)
import Clash.Promoted.Symbol
import Clash.Signal.Internal
import Unsafe.Coerce
clockWizard
:: forall domIn domOut periodIn periodOut edge init polarity name
. ( KnownConfiguration domIn ('DomainConfiguration domIn periodIn edge 'Asynchronous init polarity)
, KnownConfiguration domOut ('DomainConfiguration domOut periodOut edge 'Asynchronous init polarity) )
=> SSymbol name
-> Clock domIn
-> Reset domIn
-> (Clock domOut, Enable domOut)
clockWizard :: SSymbol name
-> Clock domIn -> Reset domIn -> (Clock domOut, Enable domOut)
clockWizard !SSymbol name
_ Clock domIn
clk Reset domIn
rst =
(Clock domIn -> Clock domOut
forall a b. a -> b
unsafeCoerce Clock domIn
clk, Enable domIn -> Enable domOut
forall a b. a -> b
unsafeCoerce (Signal domIn Bool -> Enable domIn
forall (dom :: Domain). Signal dom Bool -> Enable dom
toEnable (Reset domIn -> Signal domIn Bool
forall (dom :: Domain).
KnownDomain dom =>
Reset dom -> Signal dom Bool
unsafeToHighPolarity Reset domIn
rst)))
{-# NOINLINE clockWizard #-}
{-# ANN clockWizard hasBlackBox #-}
clockWizardDifferential
:: forall domIn domOut periodIn periodOut edge init polarity name
. ( KnownConfiguration domIn ('DomainConfiguration domIn periodIn edge 'Asynchronous init polarity)
, KnownConfiguration domOut ('DomainConfiguration domOut periodOut edge 'Asynchronous init polarity) )
=> SSymbol name
-> Clock domIn
-> Clock domIn
-> Reset domIn
-> (Clock domOut, Enable domOut)
clockWizardDifferential :: SSymbol name
-> Clock domIn
-> Clock domIn
-> Reset domIn
-> (Clock domOut, Enable domOut)
clockWizardDifferential !SSymbol name
_name (Clock SSymbol domIn
_) (Clock SSymbol domIn
_) Reset domIn
rst =
(SSymbol domOut -> Clock domOut
forall (dom :: Domain). SSymbol dom -> Clock dom
Clock SSymbol domOut
forall (s :: Domain). KnownSymbol s => SSymbol s
SSymbol, Enable domIn -> Enable domOut
forall a b. a -> b
unsafeCoerce (Signal domIn Bool -> Enable domIn
forall (dom :: Domain). Signal dom Bool -> Enable dom
toEnable (Reset domIn -> Signal domIn Bool
forall (dom :: Domain).
KnownDomain dom =>
Reset dom -> Signal dom Bool
unsafeToHighPolarity Reset domIn
rst)))
{-# NOINLINE clockWizardDifferential #-}
{-# ANN clockWizardDifferential hasBlackBox #-}