Skip to content

Commit

Permalink
Change to be hidden clock, reset, and enable.
Browse files Browse the repository at this point in the history
  • Loading branch information
rslawson committed Dec 16, 2024
1 parent cd1f2ae commit 36d2a25
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 36 deletions.
8 changes: 3 additions & 5 deletions bittide-instances/src/Bittide/Instances/Hitl/IlaPlot.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,7 @@ import Clash.Cores.Xilinx.Xpm.Cdc.Gray (xpmCdcGray)
import Clash.Cores.Xilinx.Xpm.Cdc.Single (xpmCdcSingle)
import Clash.Explicit.Reset.Extra

import Clash.Signal (HiddenClockResetEnable, withClockResetEnable)
import Control.Arrow (second, (***))
import Data.Bool (bool)
import Data.Constraint.Nat.Extra (
Expand Down Expand Up @@ -455,10 +456,7 @@ data DiffResult a
deriving (Generic, BitPack, NFDataX, Functor, Eq, Ord, Show)

type CallistoCc n m sys cfg =
(KnownDomain sys, HasSynchronousReset sys) =>
Clock sys ->
Reset sys ->
Enable sys ->
(HiddenClockResetEnable sys, HasSynchronousReset sys) =>
cfg ->
Signal sys (BitVector n) ->
Vec n (Signal sys (RelDataCount m)) ->
Expand Down Expand Up @@ -502,7 +500,7 @@ callistoClockControlWithIla ::
callistoClockControlWithIla dynClk clk rst callistoCfg callistoCc IlaControl{..} mask ebs =
hwSeqX ilaInstance (muteDuringCalibration <$> calibrating <*> output)
where
output = callistoCc clk rst enableGen callistoCfg mask ebs
output = withClockResetEnable clk rst enableGen $ callistoCc callistoCfg mask ebs

-- Condense multicycle speedchange outputs into a single cycle for the ILA
mscChanging = isRising clk rst enableGen False (isJust . maybeSpeedChange <$> output)
Expand Down
44 changes: 13 additions & 31 deletions bittide/src/Bittide/ClockControl/CallistoSw.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,7 @@ module Bittide.ClockControl.CallistoSw (
SwControlConfig (..),
) where

import Clash.Explicit.Prelude hiding (PeriodToCycles)
import Clash.Prelude (withClockResetEnable)
import Clash.Prelude hiding (PeriodToCycles)

import Clash.Cores.Xilinx.Ila (Depth (..), IlaConfig (..), ila, ilaConfig)
import Data.Maybe (fromMaybe, isJust)
Expand All @@ -22,7 +21,6 @@ import Project.FilePath
import Protocols
import Protocols.Idle
import System.FilePath
import VexRiscv

import Bittide.CircuitUtils
import Bittide.ClockControl (RelDataCount)
Expand Down Expand Up @@ -64,7 +62,7 @@ The CPU is instantiated with 64KB of IMEM containing the 'clock-control' binary
-}
callistoSwClockControl ::
forall nLinks eBufBits dom margin framesize.
( KnownDomain dom
( HiddenClockResetEnable dom
, KnownNat nLinks
, KnownNat eBufBits
, 1 <= nLinks
Expand All @@ -73,20 +71,14 @@ callistoSwClockControl ::
, 1 <= framesize
, 1 <= DomainPeriod dom
) =>
-- | CPU clock
Clock dom ->
-- | CPU reset
Reset dom ->
-- | CPU enable
Enable dom ->
-- | Clock control config
SwControlConfig dom margin framesize ->
-- | Availability mask
Signal dom (BitVector nLinks) ->
-- | Diff counters
Vec nLinks (Signal dom (RelDataCount eBufBits)) ->
Signal dom (CallistoResult nLinks)
callistoSwClockControl clk rst ena (SwControlConfig (reframe :: Signal dom Bool) mgn fsz) mask ebs =
callistoSwClockControl (SwControlConfig (reframe :: Signal dom Bool) mgn fsz) mask ebs =
hwSeqX callistoSwIla callistoResult
where
callistoResult =
Expand All @@ -113,39 +105,29 @@ callistoSwClockControl clk rst ena (SwControlConfig (reframe :: Signal dom Bool)
)
{ depth = D16384
}
clk
(unsafeToActiveLow rst)
hasClock
(unsafeToActiveLow hasReset)
capture
debugData.updatePeriod
debugData.updatePeriodMin
debugData.updatePeriodMax

debugRegisterCfg = DebugRegisterCfg <$> reframe

capture = isRising clk rst ena False (isJust <$> ccData.clockMod)
capture = isRising False (isJust <$> ccData.clockMod)

(_, (ccData, debugData)) =
toSignals
( circuit $ \jtag -> do
[wbClockControl, wbDebug, wbDummy] <-
withClockResetEnable clk rst ena $ processingElement peConfig -< jtag
toSignals @()
( circuit $ \_unit -> do
jtag <- idleSource -< ()
[wbClockControl, wbDebug, wbDummy] <- processingElement peConfig -< jtag
idleSink -< wbDummy
[ccd0, ccd1] <-
cSignalDupe
<| withClockResetEnable
clk
rst
ena
(clockControlWb mgn fsz mask ebs)
-< wbClockControl
[ccd0, ccd1] <- cSignalDupe <| clockControlWb mgn fsz mask ebs -< wbClockControl
cm <- cSignalMap clockMod -< ccd0
dbg <-
withClockResetEnable clk rst enableGen
$ debugRegisterWb debugRegisterCfg
-< (wbDebug, cm)
dbg <- debugRegisterWb debugRegisterCfg -< (wbDebug, cm)
idC -< (ccd1, dbg)
)
(pure $ JtagIn low low low, (pure (), pure ()))
((), (pure (), pure ()))
(iMem, dMem) =
$( do
root <- runIO $ findParentContaining "cabal.project"
Expand Down

0 comments on commit 36d2a25

Please sign in to comment.