{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ViewPatterns #-}
module Clash.Primitives.Intel.ClockGen where
import Clash.Backend
import Clash.Netlist.BlackBox.Util
import qualified Clash.Netlist.Id as Id
import Clash.Netlist.Types
import Clash.Netlist.Util
import Control.Monad.State
import Data.Monoid (Ap(getAp))
import qualified Data.String.Interpolate.IsString as I
import Data.Text.Prettyprint.Doc.Extra
import qualified Data.Text as TextS
import Data.Text.Extra (showt)
altpllTF :: TemplateFunction
altpllTF :: TemplateFunction
altpllTF = [Int]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [Int]
used BlackBoxContext -> Bool
valid forall s. Backend s => BlackBoxContext -> State s Doc
altpllTemplate
where
used :: [Int]
used = [Int
0..Int
4]
valid :: BlackBoxContext -> Bool
valid BlackBoxContext
bbCtx
| [(Expr, HWType, Bool)
_,(Expr, HWType, Bool)
_,(Expr
nm,HWType
_,Bool
_),(Expr, HWType, Bool)
_,(Expr, HWType, Bool)
_] <- BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx
, Just String
_ <- Expr -> Maybe String
exprToString Expr
nm
, [(Identifier Identifier
_ Maybe Modifier
Nothing,Product {})] <- BlackBoxContext -> [(Expr, HWType)]
bbResults BlackBoxContext
bbCtx
= Bool
True
valid BlackBoxContext
_ = Bool
False
altpllQsysTF :: TemplateFunction
altpllQsysTF :: TemplateFunction
altpllQsysTF = [Int]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [Int]
used BlackBoxContext -> Bool
valid forall s. Backend s => BlackBoxContext -> State s Doc
altpllQsysTemplate
where
used :: [Int]
used = [Int
0..Int
4]
valid :: BlackBoxContext -> Bool
valid BlackBoxContext
bbCtx
| [(Expr, HWType, Bool)
_,(Expr, HWType, Bool)
_,(Expr
nm,HWType
_,Bool
_),(Expr, HWType, Bool)
_,(Expr, HWType, Bool)
_] <- BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx
, Just String
_ <- Expr -> Maybe String
exprToString Expr
nm
, [(Identifier Identifier
_ Maybe Modifier
Nothing,Product {})] <- BlackBoxContext -> [(Expr, HWType)]
bbResults BlackBoxContext
bbCtx
= Bool
True
valid BlackBoxContext
_ = Bool
False
alteraPllTF :: TemplateFunction
alteraPllTF :: TemplateFunction
alteraPllTF = [Int]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [Int]
used BlackBoxContext -> Bool
valid forall s. Backend s => BlackBoxContext -> State s Doc
alteraPllTemplate
where
used :: [Int]
used = [Int
1..Int
20]
valid :: BlackBoxContext -> Bool
valid BlackBoxContext
bbCtx
| ((Expr
nm,HWType
_,Bool
_):[(Expr, HWType, Bool)]
_) <- Int -> [(Expr, HWType, Bool)] -> [(Expr, HWType, Bool)]
forall a. Int -> [a] -> [a]
drop Int
3 (BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx)
, Just String
_ <- Expr -> Maybe String
exprToString Expr
nm
= Bool
True
valid BlackBoxContext
_ = Bool
False
alteraPllQsysTF :: TemplateFunction
alteraPllQsysTF :: TemplateFunction
alteraPllQsysTF = [Int]
-> (BlackBoxContext -> Bool)
-> (forall s. Backend s => BlackBoxContext -> State s Doc)
-> TemplateFunction
TemplateFunction [Int]
used BlackBoxContext -> Bool
valid forall s. Backend s => BlackBoxContext -> State s Doc
alteraPllQsysTemplate
where
used :: [Int]
used = [Int
1..Int
20]
valid :: BlackBoxContext -> Bool
valid BlackBoxContext
bbCtx
| ((Expr
nm,HWType
_,Bool
_):[(Expr, HWType, Bool)]
_) <- Int -> [(Expr, HWType, Bool)] -> [(Expr, HWType, Bool)]
forall a. Int -> [a] -> [a]
drop Int
3 (BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx)
, Just String
_ <- Expr -> Maybe String
exprToString Expr
nm
= Bool
True
valid BlackBoxContext
_ = Bool
False
alteraPllTemplate
:: forall s
. Backend s
=> BlackBoxContext
-> State s Doc
alteraPllTemplate :: BlackBoxContext -> State s Doc
alteraPllTemplate BlackBoxContext
bbCtx = do
Identifier
locked <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.makeBasic Text
"locked"
Identifier
pllLock <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.makeBasic Text
"pllLock"
Identifier
alteraPll <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.makeBasic Text
"altera_pll_block"
Identifier
alteraPll_inst <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.makeBasic Text
instname0
[Identifier]
clocks <- Int -> Identifier -> StateT s Identity [Identifier]
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Int -> Identifier -> m [Identifier]
Id.nextN ([HWType] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [HWType]
tys) (Identifier -> StateT s Identity [Identifier])
-> StateT s Identity Identifier -> StateT s Identity [Identifier]
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.make Text
"pllOut"
let compName :: Identifier
compName = HasCallStack => Text -> Identifier
Text -> Identifier
Id.unsafeMake ([Text] -> Text
forall a. [a] -> a
head (BlackBoxContext -> [Text]
bbQsysIncName BlackBoxContext
bbCtx))
let outclkPorts :: [Expr]
outclkPorts = (Int -> Expr) -> [Int] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
n -> Text -> Expr
instPort (Text
"outclk_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
showt Int
n)) [(Int
0 :: Int)..[Identifier] -> Int
forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [Identifier]
clocksInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1]
Ap (State s) Doc -> State s Doc
forall k (f :: k -> Type) (a :: k). Ap f a -> f a
getAp (Ap (State s) Doc -> State s Doc)
-> Ap (State s) Doc -> State s Doc
forall a b. (a -> b) -> a -> b
$ Identifier -> [Declaration] -> Ap (State s) Doc
forall state.
Backend state =>
Identifier -> [Declaration] -> Ap (State state) Doc
blockDecl Identifier
alteraPll ([Declaration] -> Ap (State s) Doc)
-> [Declaration] -> Ap (State s) Doc
forall a b. (a -> b) -> a -> b
$ [[Declaration]] -> [Declaration]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat
[[ Maybe Text -> Identifier -> HWType -> Declaration
NetDecl Maybe Text
forall a. Maybe a
Nothing Identifier
locked HWType
Bit
, Maybe Text
-> WireOrReg
-> Identifier
-> Either Text HWType
-> Maybe Expr
-> Declaration
NetDecl' Maybe Text
forall a. Maybe a
Nothing WireOrReg
Reg Identifier
pllLock (HWType -> Either Text HWType
forall a b. b -> Either a b
Right HWType
Bool) Maybe Expr
forall a. Maybe a
Nothing]
,[ Maybe Text -> Identifier -> HWType -> Declaration
NetDecl Maybe Text
forall a. Maybe a
Nothing Identifier
clkNm HWType
ty | (Identifier
clkNm,HWType
ty) <- [Identifier] -> [HWType] -> [(Identifier, HWType)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Identifier]
clocks [HWType]
tys]
,[ EntityOrComponent
-> Maybe Text
-> [Attr']
-> Identifier
-> Identifier
-> [(Expr, HWType, Expr)]
-> PortMap
-> Declaration
InstDecl EntityOrComponent
Comp Maybe Text
forall a. Maybe a
Nothing [] Identifier
compName Identifier
alteraPll_inst [] (PortMap -> Declaration) -> PortMap -> Declaration
forall a b. (a -> b) -> a -> b
$ [(Expr, PortDirection, HWType, Expr)] -> PortMap
NamedPortMap ([(Expr, PortDirection, HWType, Expr)] -> PortMap)
-> [(Expr, PortDirection, HWType, Expr)] -> PortMap
forall a b. (a -> b) -> a -> b
$ [[(Expr, PortDirection, HWType, Expr)]]
-> [(Expr, PortDirection, HWType, Expr)]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat
[ [ (Text -> Expr
instPort Text
"refclk", PortDirection
In, HWType
clkTy, Expr
clk)
, (Text -> Expr
instPort Text
"rst", PortDirection
In, HWType
rstTy, Expr
rst)]
, [ (Expr
p, PortDirection
Out, HWType
ty, Identifier -> Maybe Modifier -> Expr
Identifier Identifier
k Maybe Modifier
forall a. Maybe a
Nothing) | (Identifier
k, HWType
ty, Expr
p) <- [Identifier] -> [HWType] -> [Expr] -> [(Identifier, HWType, Expr)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Identifier]
clocks [HWType]
tys [Expr]
outclkPorts ]
, [(Text -> Expr
instPort Text
"locked", PortDirection
Out, HWType
Bit, Identifier -> Maybe Modifier -> Expr
Identifier Identifier
locked Maybe Modifier
forall a. Maybe a
Nothing)]]
, Identifier
-> HWType
-> Expr
-> HWType
-> [(Maybe Literal, Expr)]
-> Declaration
CondAssignment Identifier
pllLock HWType
Bool (Identifier -> Maybe Modifier -> Expr
Identifier Identifier
locked Maybe Modifier
forall a. Maybe a
Nothing) HWType
Bit
[(Literal -> Maybe Literal
forall a. a -> Maybe a
Just (Bit -> Literal
BitLit Bit
H),Maybe (HWType, Int) -> Literal -> Expr
Literal Maybe (HWType, Int)
forall a. Maybe a
Nothing (Bool -> Literal
BoolLit Bool
True))
,(Maybe Literal
forall a. Maybe a
Nothing ,Maybe (HWType, Int) -> Literal -> Expr
Literal Maybe (HWType, Int)
forall a. Maybe a
Nothing (Bool -> Literal
BoolLit Bool
False))]
, Identifier -> Expr -> Declaration
Assignment Identifier
result (HWType -> Modifier -> [Expr] -> Expr
DataCon HWType
resTy ((HWType, Int) -> Modifier
DC (HWType
resTy,Int
0)) ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ [[Expr]] -> [Expr]
forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat
[[Identifier -> Maybe Modifier -> Expr
Identifier Identifier
k Maybe Modifier
forall a. Maybe a
Nothing | Identifier
k <- [Identifier]
clocks]
,[Identifier -> Maybe Modifier -> Expr
Identifier Identifier
pllLock Maybe Modifier
forall a. Maybe a
Nothing]])
]
]
where
[(Identifier Identifier
result Maybe Modifier
Nothing,resTy :: HWType
resTy@(Product Text
_ Maybe [Text]
_ ([HWType] -> [HWType]
forall a. [a] -> [a]
init -> [HWType]
tys)))] = BlackBoxContext -> [(Expr, HWType)]
bbResults BlackBoxContext
bbCtx
[(Expr
nm,HWType
_,Bool
_),(Expr
clk,HWType
clkTy,Bool
_),(Expr
rst,HWType
rstTy,Bool
_)] = Int -> [(Expr, HWType, Bool)] -> [(Expr, HWType, Bool)]
forall a. Int -> [a] -> [a]
drop Int
3 (BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx)
Just String
nm' = Expr -> Maybe String
exprToString Expr
nm
instname0 :: Text
instname0 = String -> Text
TextS.pack String
nm'
altpllTemplate
:: Backend s
=> BlackBoxContext
-> State s Doc
altpllTemplate :: BlackBoxContext -> State s Doc
altpllTemplate BlackBoxContext
bbCtx = do
Identifier
pllOut <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.make Text
"pllOut"
Identifier
locked <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.make Text
"locked"
Identifier
pllLock <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.make Text
"pllLock"
Identifier
alteraPll <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.make Text
"altpll_block"
Identifier
alteraPll_inst <- Text -> StateT s Identity Identifier
forall (m :: Type -> Type).
(HasCallStack, IdentifierSetMonad m) =>
Text -> m Identifier
Id.make Text
instname0
let compName :: Identifier
compName = HasCallStack => Text -> Identifier
Text -> Identifier
Id.unsafeMake ([Text] -> Text
forall a. [a] -> a
head (BlackBoxContext -> [Text]
bbQsysIncName BlackBoxContext
bbCtx))
Ap (State s) Doc -> State s Doc
forall k (f :: k -> Type) (a :: k). Ap f a -> f a
getAp (Ap (State s) Doc -> State s Doc)
-> Ap (State s) Doc -> State s Doc
forall a b. (a -> b) -> a -> b
$ Identifier -> [Declaration] -> Ap (State s) Doc
forall state.
Backend state =>
Identifier -> [Declaration] -> Ap (State state) Doc
blockDecl Identifier
alteraPll
[ Maybe Text -> Identifier -> HWType -> Declaration
NetDecl Maybe Text
forall a. Maybe a
Nothing Identifier
locked HWType
Bit
, Maybe Text
-> WireOrReg
-> Identifier
-> Either Text HWType
-> Maybe Expr
-> Declaration
NetDecl' Maybe Text
forall a. Maybe a
Nothing WireOrReg
Reg Identifier
pllLock (HWType -> Either Text HWType
forall a b. b -> Either a b
Right HWType
Bool) Maybe Expr
forall a. Maybe a
Nothing
, Maybe Text -> Identifier -> HWType -> Declaration
NetDecl Maybe Text
forall a. Maybe a
Nothing Identifier
pllOut HWType
clkOutTy
, EntityOrComponent
-> Maybe Text
-> [Attr']
-> Identifier
-> Identifier
-> [(Expr, HWType, Expr)]
-> PortMap
-> Declaration
InstDecl EntityOrComponent
Comp Maybe Text
forall a. Maybe a
Nothing [] Identifier
compName Identifier
alteraPll_inst [] (PortMap -> Declaration) -> PortMap -> Declaration
forall a b. (a -> b) -> a -> b
$ [(Expr, PortDirection, HWType, Expr)] -> PortMap
NamedPortMap ([(Expr, PortDirection, HWType, Expr)] -> PortMap)
-> [(Expr, PortDirection, HWType, Expr)] -> PortMap
forall a b. (a -> b) -> a -> b
$
[ (Text -> Expr
instPort Text
"clk", PortDirection
In, HWType
clkTy, Expr
clk)
, (Text -> Expr
instPort Text
"areset", PortDirection
In, HWType
rstTy, Expr
rst)
, (Text -> Expr
instPort Text
"c0", PortDirection
Out, HWType
clkOutTy, Identifier -> Maybe Modifier -> Expr
Identifier Identifier
pllOut Maybe Modifier
forall a. Maybe a
Nothing)
, (Text -> Expr
instPort Text
"locked", PortDirection
Out, HWType
Bit, Identifier -> Maybe Modifier -> Expr
Identifier Identifier
locked Maybe Modifier
forall a. Maybe a
Nothing)]
, Identifier
-> HWType
-> Expr
-> HWType
-> [(Maybe Literal, Expr)]
-> Declaration
CondAssignment Identifier
pllLock HWType
Bool (Identifier -> Maybe Modifier -> Expr
Identifier Identifier
locked Maybe Modifier
forall a. Maybe a
Nothing) HWType
Bit
[(Literal -> Maybe Literal
forall a. a -> Maybe a
Just (Bit -> Literal
BitLit Bit
H),Maybe (HWType, Int) -> Literal -> Expr
Literal Maybe (HWType, Int)
forall a. Maybe a
Nothing (Bool -> Literal
BoolLit Bool
True))
,(Maybe Literal
forall a. Maybe a
Nothing ,Maybe (HWType, Int) -> Literal -> Expr
Literal Maybe (HWType, Int)
forall a. Maybe a
Nothing (Bool -> Literal
BoolLit Bool
False))]
, Identifier -> Expr -> Declaration
Assignment Identifier
result (HWType -> Modifier -> [Expr] -> Expr
DataCon HWType
resTy ((HWType, Int) -> Modifier
DC (HWType
resTy,Int
0))
[Identifier -> Maybe Modifier -> Expr
Identifier Identifier
pllOut Maybe Modifier
forall a. Maybe a
Nothing
,Identifier -> Maybe Modifier -> Expr
Identifier Identifier
pllLock Maybe Modifier
forall a. Maybe a
Nothing])
]
where
[(Expr, HWType, Bool)
_,(Expr, HWType, Bool)
_,(Expr
nm,HWType
_,Bool
_),(Expr
clk,HWType
clkTy,Bool
_),(Expr
rst,HWType
rstTy,Bool
_)] = BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx
[(Identifier Identifier
result Maybe Modifier
Nothing,resTy :: HWType
resTy@(Product Text
_ Maybe [Text]
_ [HWType
clkOutTy,HWType
_]))] = BlackBoxContext -> [(Expr, HWType)]
bbResults BlackBoxContext
bbCtx
Just String
nm' = Expr -> Maybe String
exprToString Expr
nm
instname0 :: Text
instname0 = String -> Text
TextS.pack String
nm'
altpllQsysTemplate
:: Backend s
=> BlackBoxContext
-> State s Doc
altpllQsysTemplate :: BlackBoxContext -> State s Doc
altpllQsysTemplate BlackBoxContext
bbCtx = Doc -> State s Doc
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Doc
bbText
where
((Expr
_,HWType -> HWType
stripVoid -> HWType
kdIn,Bool
_):(Expr
_,HWType -> HWType
stripVoid -> HWType
kdOut,Bool
_):[(Expr, HWType, Bool)]
_) = BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx
KnownDomain Text
_ Integer
clkInPeriod ActiveEdge
_ ResetKind
_ InitBehavior
_ ResetPolarity
_ = HWType
kdIn
KnownDomain Text
_ Integer
clkOutPeriod ActiveEdge
_ ResetKind
_ InitBehavior
_ ResetPolarity
_ = HWType
kdOut
clkOutFreq :: Double
clkOutFreq :: Double
clkOutFreq = (Double
1.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
clkOutPeriod Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1.0e-12)) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1e6
clklcm :: Integer
clklcm = Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
lcm Integer
clkInPeriod Integer
clkOutPeriod
clkmult :: Integer
clkmult = Integer
clklcm Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
clkOutPeriod
clkdiv :: Integer
clkdiv = Integer
clklcm Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
clkInPeriod
bbText :: Doc
bbText = [I.i|<?xml version="1.0" encoding="UTF-8"?>
<system name="$${FILENAME}">
<module
name="altpll0"
kind="altpll"
enabled="1"
autoexport="1">
<parameter name="AVALON_USE_SEPARATE_SYSCLK" value="NO" />
<parameter name="BANDWIDTH" value="" />
<parameter name="BANDWIDTH_TYPE" value="AUTO" />
<parameter name="CLK0_DIVIDE_BY" value="#{clkdiv}" />
<parameter name="CLK0_DUTY_CYCLE" value="50" />
<parameter name="CLK0_MULTIPLY_BY" value="#{clkmult}" />
<parameter name="CLK0_PHASE_SHIFT" value="0" />
<parameter name="COMPENSATE_CLOCK" value="CLK0" />
<parameter name="INCLK0_INPUT_FREQUENCY" value="#{clkInPeriod}" />
<parameter name="OPERATION_MODE" value="NORMAL" />
<parameter name="PLL_TYPE" value="AUTO" />
<parameter name="PORT_ARESET" value="PORT_USED" />
<parameter name="PORT_INCLK0" value="PORT_USED" />
<parameter name="PORT_LOCKED" value="PORT_USED" />
<parameter name="PORT_clk0" value="PORT_USED" />
<parameter name="HIDDEN_IS_FIRST_EDIT" value="0" />
<parameter name="HIDDEN_CONSTANTS">
CT#PORT_clk0 PORT_USED
CT#CLK0_MULTIPLY_BY #{clkmult}
CT#WIDTH_CLOCK 5
CT#LPM_TYPE altpll
CT#PLL_TYPE AUTO
CT#CLK0_PHASE_SHIFT 0
CT#OPERATION_MODE NORMAL
CT#COMPENSATE_CLOCK CLK0
CT#INCLK0_INPUT_FREQUENCY #{clkInPeriod}
CT#PORT_INCLK0 PORT_USED
CT#PORT_ARESET PORT_USED
CT#BANDWIDTH_TYPE AUTO
CT#CLK0_DUTY_CYCLE 50
CT#CLK0_DIVIDE_BY #{clkdiv}
CT#PORT_LOCKED PORT_USED</parameter>
<parameter name="HIDDEN_IF_PORTS">
IF#phasecounterselect {input 4}
IF#locked {output 0}
IF#reset {input 0}
IF#clk {input 0}
IF#phaseupdown {input 0}
IF#scandone {output 0}
IF#readdata {output 32}
IF#write {input 0}
IF#scanclk {input 0}
IF#phasedone {output 0}
IF#address {input 2}
IF#c0 {output 0}
IF#writedata {input 32}
IF#read {input 0}
IF#areset {input 0}
IF#scanclkena {input 0}
IF#scandataout {output 0}
IF#configupdate {input 0}
IF#phasestep {input 0}
IF#scandata {input 0}</parameter>
<parameter name="HIDDEN_MF_PORTS">
MF#areset 1
MF#clk 1
MF#locked 1
MF#inclk 1</parameter>
<parameter name="HIDDEN_PRIVATES">
PT#PHASE_SHIFT0 0.00000000
PT#DIV_FACTOR0 #{clkdiv}
PT#EFF_OUTPUT_FREQ_VALUE0 #{clkOutFreq}
PT#MULT_FACTOR0 #{clkmult}
PT#DUTY_CYCLE0 50.00000000</parameter>
</module>
</system>|]
alteraPllQsysTemplate
:: Backend s
=> BlackBoxContext
-> State s Doc
alteraPllQsysTemplate :: BlackBoxContext -> State s Doc
alteraPllQsysTemplate BlackBoxContext
bbCtx = Doc -> State s Doc
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Doc
bbText
where
(Expr, HWType, Bool)
_clocksClass
: (Expr
_,HWType -> HWType
stripVoid -> HWType
kdIn,Bool
_)
: (Expr
_,HWType -> HWType
stripVoid -> Product Text
_ Maybe [Text]
_ ([HWType] -> [HWType]
forall a. [a] -> [a]
init -> [HWType]
kdOuts),Bool
_)
: [(Expr, HWType, Bool)]
_ = BlackBoxContext -> [(Expr, HWType, Bool)]
bbInputs BlackBoxContext
bbCtx
cklFreq :: HWType -> Double
cklFreq (KnownDomain Text
_ Integer
p ActiveEdge
_ ResetKind
_ InitBehavior
_ ResetPolarity
_)
= (Double
1.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
p Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1.0e-12 :: Double)) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1e6
cklFreq HWType
_ = String -> Double
forall a. HasCallStack => String -> a
error String
"internal error: not a KnownDomain"
clkOuts :: Text
clkOuts = [Text] -> Text
TextS.unlines
[[I.i|<parameter name="gui_output_clock_frequency#{n}" value="#{f}"/>|]
| (Word
n,Double
f) <- [Word] -> [Double] -> [(Word, Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip [(Word
0 :: Word)..] ((HWType -> Double) -> [HWType] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map HWType -> Double
cklFreq [HWType]
kdOuts)
]
bbText :: Doc
bbText = [I.i|<?xml version="1.0" encoding="UTF-8"?>
<system name="$${FILENAME}">
<module
name="pll_0"
kind="altera_pll"
enabled="1"
autoexport="1">
<parameter name="gui_feedback_clock" value="Global Clock" />
<parameter name="gui_number_of_clocks" value="#{length kdOuts}" />
<parameter name="gui_operation_mode" value="direct" />
#{clkOuts}
<parameter name="gui_pll_mode" value="Integer-N PLL" />
<parameter name="gui_reference_clock_frequency" value="#{cklFreq kdIn}" />
<parameter name="gui_use_locked" value="true" />
</module>
</system>|]