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