Skip to content

Commit c3233c7

Browse files
Implement safe PLL's
1 parent 35cf9e9 commit c3233c7

File tree

5 files changed

+180
-19
lines changed

5 files changed

+180
-19
lines changed

clash-prelude/src/Clash/Clocks.hs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,14 +8,36 @@ Maintainer : QBayLogic B.V. <[email protected]>
88
Generic clock related utilities.
99
-}
1010

11+
{-# LANGUAGE ConstraintKinds #-}
12+
{-# LANGUAGE FlexibleContexts #-}
1113
{-# LANGUAGE FlexibleInstances #-}
1214
{-# LANGUAGE TemplateHaskell #-}
1315
{-# LANGUAGE TypeFamilies #-}
1416

1517
{-# OPTIONS_GHC "-Wno-orphans" #-}
1618

17-
module Clash.Clocks (Clocks(..)) where
19+
module Clash.Clocks
20+
( Clocks(..)
21+
, ClocksSync(..)
22+
, ClocksSyncCxt
23+
, NumOutClocksSync
24+
) where
1825

19-
import Clash.Clocks.Internal (Clocks(..), deriveClocksInstances)
26+
import Clash.Clocks.Internal
27+
(Clocks(..), ClocksSync(..), deriveClocksInstances, deriveClocksSyncInstances)
28+
import Clash.Signal.Internal (Domain, KnownDomain)
2029

2130
deriveClocksInstances
31+
32+
type ClocksSyncCxt t (domIn :: Domain) =
33+
( KnownDomain domIn
34+
, ClocksSync t
35+
, ClocksResetSynchronizerCxt t
36+
, Clocks (ClocksSyncClocksInst t domIn)
37+
, ClocksCxt (ClocksSyncClocksInst t domIn)
38+
)
39+
40+
type NumOutClocksSync t (domIn :: Domain) =
41+
NumOutClocks (ClocksSyncClocksInst t domIn)
42+
43+
deriveClocksSyncInstances

clash-prelude/src/Clash/Clocks/Internal.hs

Lines changed: 86 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11,18 +11,26 @@ Maintainer : QBayLogic B.V. <[email protected]>
1111
{-# LANGUAGE TemplateHaskell #-}
1212
{-# LANGUAGE TypeFamilies #-}
1313

14-
module Clash.Clocks.Internal (Clocks(..), deriveClocksInstances) where
14+
module Clash.Clocks.Internal
15+
( Clocks(..)
16+
, deriveClocksInstances
17+
, ClocksSync(..)
18+
, deriveClocksSyncInstances
19+
) where
1520

1621
import Control.Monad.Extra (concatMapM)
17-
import Data.Kind (Constraint)
22+
import Data.Kind (Constraint, Type)
1823
import GHC.TypeLits (Nat)
19-
import Language.Haskell.TH
24+
import Language.Haskell.TH hiding (Type)
2025

2126
import Clash.CPP (haddockOnly)
27+
import Clash.Explicit.Reset (resetSynchronizer)
2228
import Clash.Explicit.Signal (unsafeSynchronizer)
29+
import Clash.Magic (setName)
2330
import Clash.Promoted.Symbol (SSymbol(..))
2431
import Clash.Signal.Internal
25-
(clockGen, Clock(..), KnownDomain, Reset, Signal, unsafeToActiveLow)
32+
(clockGen, Clock(..), Domain, KnownDomain, Reset, Signal, unsafeFromActiveLow,
33+
unsafeToActiveLow)
2634

2735
-- | __NB__: The documentation only shows instances up to /3/ output clocks. By
2836
-- default, instances up to and including /18/ clocks will exist.
@@ -75,3 +83,77 @@ deriveClocksInstances = concatMapM deriveClocksInstance [1..n]
7583
where
7684
n | haddockOnly = 3
7785
| otherwise = 18
86+
87+
-- | __NB__: The documentation only shows instances up to /3/ output clocks. By
88+
-- default, instances up to and including /18/ clocks will exist.
89+
class ClocksSync t where
90+
type ClocksSyncClocksInst t (domIn :: Domain) :: Type
91+
type ClocksResetSynchronizerCxt t :: Constraint
92+
93+
clocksResetSynchronizer ::
94+
( KnownDomain domIn
95+
, ClocksResetSynchronizerCxt t
96+
) =>
97+
ClocksSyncClocksInst t domIn ->
98+
Clock domIn ->
99+
t
100+
101+
-- Derive instance for /n/ clocks
102+
deriveClocksSyncInstance :: Int -> DecsQ
103+
deriveClocksSyncInstance n =
104+
[d|
105+
instance ClocksSync $instType where
106+
type ClocksSyncClocksInst $instType $domInTyVar = $clocksInstType
107+
type ClocksResetSynchronizerCxt $instType = $cxtType
108+
109+
clocksResetSynchronizer pllOut $(varP clkIn) =
110+
let $pllPat = pllOut
111+
in $funcImpl
112+
|]
113+
where
114+
clkVarName m = mkName $ "c" <> show m
115+
clkTyVar :: Int -> TypeQ
116+
clkTyVar = varT . clkVarName
117+
clkAndRstTy m = [ [t| Clock $(clkTyVar m) |]
118+
, [t| Reset $(clkTyVar m) |]
119+
]
120+
-- (Clock c1, Reset c1, Clock c2, Reset c2, ...)
121+
instType = foldl appT (tupleT $ n * 2) $ concatMap clkAndRstTy [1..n]
122+
domInTyVar = varT $ mkName "domIn"
123+
clkTypes = map (\m -> [t| Clock $(clkTyVar m) |]) [1..n]
124+
-- (Clock c1, Clock c2, ..., Signal domIn Bool)
125+
clocksInstType = foldl appT (tupleT $ n + 1) $
126+
clkTypes <> [ [t| Signal $domInTyVar Bool |] ]
127+
-- (KnownDomain c1, KnownDomain c2, ...)
128+
cxtType
129+
| n == 1
130+
= [t| KnownDomain $(clkTyVar 1) |]
131+
| otherwise
132+
= foldl appT (tupleT n) $
133+
map (\m -> [t| KnownDomain $(clkTyVar m) |]) [1..n]
134+
135+
-- 'clocksResetSynchronizer' function
136+
clkIn = mkName "clkIn"
137+
pllLock = mkName "pllLock"
138+
-- (c1, c2, ..., pllLock)
139+
pllPat = tupP $ map (varP . clkVarName) [1..n] <> [varP pllLock]
140+
syncImpl m =
141+
[|
142+
setName @"resetSynchronizer" (resetSynchronizer $(varE $ clkVarName m)
143+
(unsafeFromActiveLow
144+
(unsafeSynchronizer $(varE clkIn) $(varE $ clkVarName m)
145+
$(varE pllLock))))
146+
|]
147+
clkAndRstExp m = [ varE $ clkVarName m
148+
, syncImpl m
149+
]
150+
-- (c1, r1, c2, r2, ...) where rN is the synchronized reset for clock N
151+
funcImpl = tupE $ concatMap clkAndRstExp [1..n]
152+
153+
-- Derive instances for up to and including 18 clocks, except when we are
154+
-- generating Haddock
155+
deriveClocksSyncInstances :: DecsQ
156+
deriveClocksSyncInstances = concatMapM deriveClocksSyncInstance [1..n]
157+
where
158+
n | haddockOnly = 3
159+
| otherwise = 18

clash-prelude/src/Clash/Intel/ClockGen.hs

Lines changed: 34 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,9 @@ you want to run your circuit at.
3030
{-# LANGUAGE TypeFamilies #-}
3131

3232
module Clash.Intel.ClockGen
33-
( unsafeAltpll
33+
( altpllSync
34+
, alteraPllSync
35+
, unsafeAltpll
3436
, unsafeAlteraPll
3537
-- ** Deprecated
3638
, altpll
@@ -40,10 +42,24 @@ module Clash.Intel.ClockGen
4042
import GHC.TypeLits (type (<=))
4143

4244
import Clash.Annotations.Primitive (hasBlackBox)
43-
import Clash.Clocks (Clocks(..))
45+
import Clash.Clocks
46+
(Clocks(..), ClocksSync(..), ClocksSyncCxt, NumOutClocksSync)
4447
import Clash.Magic (setName)
4548
import Clash.Promoted.Symbol (SSymbol)
46-
import Clash.Signal.Internal (Signal, Clock, Reset, KnownDomain)
49+
import Clash.Signal.Internal
50+
(Signal, Clock, Reset, KnownDomain, HasAsynchronousReset)
51+
52+
altpllSync ::
53+
forall t domIn .
54+
( HasAsynchronousReset domIn
55+
, ClocksSyncCxt t domIn
56+
, NumOutClocksSync t domIn <= 5
57+
) =>
58+
Clock domIn ->
59+
Reset domIn ->
60+
t
61+
altpllSync clkIn rstIn =
62+
clocksResetSynchronizer (unsafeAltpll clkIn rstIn) clkIn
4763

4864
-- | A clock source that corresponds to the Intel/Quartus \"ALTPLL\" component
4965
-- (Arria GX, Arria II, Stratix IV, Stratix III, Stratix II, Stratix,
@@ -107,7 +123,7 @@ import Clash.Signal.Internal (Signal, Clock, Reset, KnownDomain)
107123
-- @
108124
altpll ::
109125
forall domOut domIn name .
110-
( KnownDomain domIn
126+
( HasAsynchronousReset domIn
111127
, KnownDomain domOut
112128
) =>
113129
-- | Name of the component instance
@@ -139,6 +155,18 @@ unsafeAltpll = clocks
139155
{-# CLASH_OPAQUE unsafeAltpll #-}
140156
{-# ANN unsafeAltpll hasBlackBox #-}
141157

158+
alteraPllSync ::
159+
forall t domIn .
160+
( HasAsynchronousReset domIn
161+
, ClocksSyncCxt t domIn
162+
, NumOutClocksSync t domIn <= 18
163+
) =>
164+
Clock domIn ->
165+
Reset domIn ->
166+
t
167+
alteraPllSync clkIn rstIn =
168+
clocksResetSynchronizer (unsafeAlteraPll clkIn rstIn) clkIn
169+
142170
-- | A clock source that corresponds to the Intel/Quartus \"Altera PLL\"
143171
-- component (Arria V, Stratix V, Cyclone V) with settings to provide a stable
144172
-- 'Clock' from a single free-running input
@@ -213,8 +241,8 @@ unsafeAltpll = clocks
213241
-- if the component doesn't need a reset).
214242
alteraPll ::
215243
forall t domIn name .
216-
( Clocks t
217-
, KnownDomain domIn
244+
( HasAsynchronousReset domIn
245+
, Clocks t
218246
, ClocksCxt t
219247
, NumOutClocks t <= 18
220248
) =>

clash-prelude/src/Clash/Xilinx/ClockGen.hs

Lines changed: 33 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,13 +11,32 @@ PLL and other clock-related components for Xilinx FPGAs
1111
{-# LANGUAGE FlexibleContexts #-}
1212
{-# LANGUAGE GADTs #-}
1313

14-
module Clash.Xilinx.ClockGen where
14+
module Clash.Xilinx.ClockGen
15+
( clockWizard
16+
, clockWizardDifferential
17+
, unsafeClockWizard
18+
, unsafeClockWizardDifferential
19+
) where
1520

1621
import GHC.TypeLits (type (<=))
1722

1823
import Clash.Annotations.Primitive (hasBlackBox)
19-
import Clash.Clocks (Clocks(..))
24+
import Clash.Clocks
25+
(Clocks(..), ClocksSync(..), ClocksSyncCxt, NumOutClocksSync)
2026
import Clash.Signal.Internal
27+
(Clock, DiffClock(..), Reset, KnownDomain, HasAsynchronousReset)
28+
29+
clockWizard ::
30+
forall t domIn .
31+
( HasAsynchronousReset domIn
32+
, ClocksSyncCxt t domIn
33+
, NumOutClocksSync t domIn <= 7
34+
) =>
35+
Clock domIn ->
36+
Reset domIn ->
37+
t
38+
clockWizard clkIn rstIn =
39+
clocksResetSynchronizer (unsafeClockWizard clkIn rstIn) clkIn
2140

2241
-- | A clock source that corresponds to the Xilinx MMCM component created
2342
-- with the \"Clock Wizard\" with settings to provide a stable 'Clock' from
@@ -50,6 +69,18 @@ unsafeClockWizard = clocks
5069
{-# CLASH_OPAQUE unsafeClockWizard #-}
5170
{-# ANN unsafeClockWizard hasBlackBox #-}
5271

72+
clockWizardDifferential ::
73+
forall t domIn .
74+
( HasAsynchronousReset domIn
75+
, ClocksSyncCxt t domIn
76+
, NumOutClocksSync t domIn <= 7
77+
) =>
78+
DiffClock domIn ->
79+
Reset domIn ->
80+
t
81+
clockWizardDifferential clkIn@(DiffClock clkInP _) rstIn =
82+
clocksResetSynchronizer (unsafeClockWizardDifferential clkIn rstIn) clkInP
83+
5384
-- | A clock source that corresponds to the Xilinx MMCM component created
5485
-- with the \"Clock Wizard\", with settings to provide a stable 'Clock'
5586
-- from a free-running differential clock input.

tests/shouldwork/Xilinx/ClockWizard.hs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ import Clash.Explicit.Prelude
1414
import Clash.Explicit.Testbench
1515
import Clash.Xilinx.ClockGen
1616

17-
createDomain vXilinxSystem{vName="DomIn", vPeriod=hzToPeriod 24_000_000}
17+
createDomain vSystem{vName="DomIn", vPeriod=hzToPeriod 24_000_000}
1818
createDomain vXilinxSystem{vName="DomOut", vPeriod=hzToPeriod 300_000_000}
1919

2020
topEntity ::
@@ -24,10 +24,8 @@ topEntity ::
2424
Signal DomOut (Index 10, Index 10)
2525
topEntity clkInSE clkInDiff rstIn =
2626
let f clk rst = register clk rst enableGen 0 . fmap (satSucc SatBound)
27-
(clkA, stableA) = unsafeClockWizard clkInSE rstIn
28-
rstA = unsafeFromActiveLow stableA
29-
(clkB, stableB) = unsafeClockWizardDifferential clkInDiff rstIn
30-
rstB = unsafeFromActiveLow stableB
27+
(clkA, rstA) = clockWizard clkInSE rstIn
28+
(clkB, rstB) = clockWizardDifferential clkInDiff rstIn
3129
o1 = f clkA rstA o1
3230
o2 = f clkB rstB o2
3331
in bundle (o1, o2)

0 commit comments

Comments
 (0)