{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
module Clash.Xilinx.DDR
( iddr
, oddr
)
where
import GHC.Stack (HasCallStack, withFrozenCallStack)
import Clash.Annotations.Primitive (hasBlackBox)
import Clash.Explicit.Prelude
import Clash.Explicit.DDR
iddr
:: forall fast fPeriod edge reset init polarity slow m
. ( HasCallStack
, KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) edge reset init polarity)
, KnownNat m )
=> Clock slow
-> Reset slow
-> Enable slow
-> Signal fast (BitVector m)
-> Signal slow ((BitVector m),(BitVector m))
iddr =
case activeEdge @slow of
SRising ->
withFrozenCallStack iddr#
SFalling ->
clashCompileError
"iddr: Primitive only supports rising active edge"
iddr#
:: ( HasCallStack
, KnownConfiguration fast ('DomainConfiguration fast fPeriod 'Rising reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) 'Rising reset init polarity)
, KnownNat m )
=> Clock slow
-> Reset slow
-> Enable slow
-> Signal fast (BitVector m)
-> Signal slow ((BitVector m),(BitVector m))
iddr# clk rst en = withFrozenCallStack ddrIn# clk rst en 0 0 0
{-# CLASH_OPAQUE iddr# #-}
{-# ANN iddr# hasBlackBox #-}
oddr
:: forall fast fPeriod edge reset init polarity slow m
. ( KnownConfiguration fast ('DomainConfiguration fast fPeriod edge reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) edge reset init polarity)
, KnownNat m )
=> Clock slow
-> Reset slow
-> Enable slow
-> Signal slow (BitVector m, BitVector m)
-> Signal fast (BitVector m)
oddr clk rst en =
case activeEdge @slow of
SRising ->
uncurry (withFrozenCallStack oddr# clk rst en) . unbundle
SFalling ->
clashCompileError
"oddr: Primitive only supports rising active edge"
oddr#
:: ( KnownConfiguration fast ('DomainConfiguration fast fPeriod 'Rising reset init polarity)
, KnownConfiguration slow ('DomainConfiguration slow (2*fPeriod) 'Rising reset init polarity)
, KnownNat m )
=> Clock slow
-> Reset slow
-> Enable slow
-> Signal slow (BitVector m)
-> Signal slow (BitVector m)
-> Signal fast (BitVector m)
oddr# clk rst en = ddrOut# clk rst en 0
{-# CLASH_OPAQUE oddr# #-}
{-# ANN oddr# hasBlackBox #-}