How to obtain the clock period/frequency from the domain?

Hi, can the clock period/frequency be obtained from the domain?

I am creating a slower clock with a desired frequency by counting the difference from the system clock, as shown below.
My understanding is that the domain configuration will be provided from outside during synthesis according to the underlying hardware.
Is there a way to obtain the period from the provided domain to dynamically adjust the number to count?

counter :: (HiddenClockResetEnable dom, KnownNat a) => Unsigned a -> Signal dom (Unsigned a)
counter toCount = register 0 (mux (prevVal .<. pure (toCount - 1)) (prevVal + 1) 0)
  where prevVal = counter toCount

generateClock :: HiddenClockResetEnable dom => Unsigned 64 -> Unsigned 64 -> Signal dom Bool
generateClock systemClockFreq desiredFreq = register False (mux (countSignal .==. maxVal) (pure True) (pure False))
  where
    countSignal = counter toCount
    toCount = systemClockFreq `div` desiredFreq
    maxVal = pure (toCount - 1)
-- Test:
-- clashi> sampleN @System 20 (generateClock 3 1)

There’s risePeriod and riseRate in RetroClash.Clock, and their implementation can show you how to reify the clock rate in the term level in general.

Also clash-prelude now has clockPeriod, which gives you an SNat which you can then convert with snatToIntegral etc.

1 Like

Periods in Clash
Periods in Clash are stored on the type level in picoseconds. You can use the DomainPeriod type to extract that information from your domain!

A couple of examples:

{-# LANGUAGE FlexibleContexts #-}
import Clash.Prelude
import Data.Proxy

-- Make some example domain with a frequency of 25 MHz.
createDomain vSystem{vPeriod = hzToPeriod 25e6, vName = "MyDomain"}

-- | A function that when given a domain, returns the period in picoseconds
domPeriod :: forall dom . KnownDomain dom =>  Proxy dom -> Int
domPeriod _ = natToNum @(DomainPeriod dom)

-- | A function that when given a domain, returns the period in picoseconds as a singleton
domPeriodSingleton :: forall dom . (KnownDomain dom) => Proxy dom -> SNat (DomainPeriod dom)
domPeriodSingleton _ = SNat

Now we can do:

ghci> domPeriod (Proxy @System)
10000
ghci> domPeriod (Proxy @MyDomain)
40000

The next release of clash-prelude will also contain more type level definitions to reason about time. These were introduced in Add utilities to represent time by lmbollen · Pull Request #2734 · clash-lang/clash-compiler · GitHub.

So now we can also write:

domFrequency :: forall dom . (KnownDomain dom, 1 <= DomainPeriod dom) => Proxy dom -> Int
domFrequency _ = natToNum @(DomainToHz dom)

to extract the frequency of our domain.

ghci> domFrequency (Proxy @System)
100000000
ghci> domFrequency (Proxy @MyDomain)
25000000

Reducing the number of pulses
It seems like you are trying to implement some logic to provide a True periodically at a certain period which is a multiple of your clock frequency.

To do that you can use the a free running counter whose maxBound is derived from your desired period and your clock period:

-- | A pulse that goes high every @desiredPeriod@ picoseconds
periodicPulse :: 
  forall dom desiredPeriod . -- Bring the type variables into the scope of the function
  ( HiddenClockResetEnable dom -- The domain needs to have a hidden clock, reset, and enable signal
  , 1 <= DomainPeriod dom -- The domain needs to have a period greater than 1 ps
  , 1 <= PeriodToCycles dom desiredPeriod -- The number of cycles in the resulting period needs to be greater than 1
  ) => 
  -- | The desired period of the pulse in picoseconds
  SNat desiredPeriod -> 
  -- | The pulse signal
  Signal dom Bool
periodicPulse SNat = pulse
 where
  pulse = counter .==. pure maxBound
  initialCount = 0 :: Index (PeriodToCycles dom desiredPeriod)
  counter = register initialCount $ satSucc SatWrap <$> counter

-- Simulate 20 samples (including once cycel of reset) of a 100ns periodic pulse
-- in the 25 MHz "MyDomain" domain
simPeriodicPulse = sampleN 20 $ periodicPulse @MyDomain (SNat @(Nanoseconds 100))

When we simulate the circuit, we see that after one cycle of reset, we get a pulse every third cycle. Remember that the period of MyDomain was 40000 picoseconds, or 40 nanoseconds. So every three cycles means every 120 nanoseconds.

ghci> simPeriodicPulse 
[False,False,False,True,False,False,True,False,False,True,False,False,True,False,False,True,False,False,True,False]
3 Likes

Thank you very much for such a detailed and instructive reply. Much appreciated :pray: