Skip to content

Commit

Permalink
Add unsafeFromActiveLow and unsafeFromActiveHigh
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Jul 13, 2023
1 parent fadedce commit de192fe
Show file tree
Hide file tree
Showing 34 changed files with 119 additions and 70 deletions.
1 change: 1 addition & 0 deletions changelog/2023-07-13T14_49_23+02_00_rename_from_polarity
@@ -0,0 +1 @@
DEPRECATED: `unsafeFromLowPolarity` and `unsafeFromHighPolarity` have been replaced by `unsafeFromActiveLow` and `unsafeFromActiveHigh`. While former ones will continue to exist, a deprecation warning has been added pointing to the latter ones.
6 changes: 3 additions & 3 deletions clash-cores/test/Test/Cores/Xilinx/DcFifo.hs
Expand Up @@ -260,7 +260,7 @@ testOverflow = testCase "Overflows appropriately" $ do

fifo = dcFifo @4 defConfig{dcOverflow = True} clk noRst clk noRst
clk = clockGen @D3
noRst = unsafeFromHighPolarity $ pure False
noRst = unsafeFromActiveHigh $ pure False
drive15 = mealy clk noRst enableGen go 15 (pure ())
go 0 _ = (0 :: Int, Nothing)
go n _ = (n-1, Just (1 :: Int))
Expand Down Expand Up @@ -361,11 +361,11 @@ throughFifo d _ _ feed drain wrDataList rdStalls = rdDataList
where

wrClk = clockGen @write
noWrRst = unsafeFromHighPolarity $ pure False
noWrRst = unsafeFromActiveHigh $ pure False
wrEna = enableGen @write

rdClk = clockGen @read
noRdRst = unsafeFromHighPolarity $ pure False
noRdRst = unsafeFromActiveHigh $ pure False
rdEna = enableGen @read

wrData =
Expand Down
8 changes: 4 additions & 4 deletions clash-prelude/src/Clash/Annotations/TopEntity.hs
Expand Up @@ -84,8 +84,8 @@ topEntity clk20 rstBtn enaBtn modeBtn =
-- Signal coming from the reset button is low when pressed, and high when
-- not pressed. We convert this signal to the polarity of our domain with
-- /unsafeFromLowPolarity/.
rst = 'Clash.Signal.unsafeFromLowPolarity' ('Clash.Signal.unsafeFromReset' rstBtn)
-- /unsafeFromActiveLow/.
rst = 'Clash.Signal.unsafeFromActiveLow' ('Clash.Signal.unsafeFromReset' rstBtn)
-- Instantiate a PLL: this stabilizes the incoming clock signal and indicates
-- when the signal is stable. We're also using it to transform an incoming
Expand All @@ -99,11 +99,11 @@ topEntity clk20 rstBtn enaBtn modeBtn =
-- Synchronize reset to clock signal coming from PLL. We want the reset to
-- remain active while the PLL is NOT stable, hence the conversion with
-- /unsafeFromLowPolarity/
-- /unsafeFromActiveLow/
rstSync =
'Clash.Prelude.resetSynchronizer'
clk50
('Clash.Signal.unsafeFromLowPolarity' pllStable)
('Clash.Signal.unsafeFromActiveLow' pllStable)
blinkerT
:: (BitVector 8, Bool, Index 16650001)
Expand Down
10 changes: 7 additions & 3 deletions clash-prelude/src/Clash/Explicit/Reset.hs
Expand Up @@ -32,6 +32,10 @@ module Clash.Explicit.Reset
, unsafeFromReset
, unsafeToHighPolarity
, unsafeToLowPolarity
, unsafeFromActiveHigh
, unsafeFromActiveLow

-- * Deprecated
, unsafeFromHighPolarity
, unsafeFromLowPolarity
) where
Expand Down Expand Up @@ -185,7 +189,7 @@ resetSynchronizer clk rst = rstOut
--
-- === __Example 1__
-- >>> let sampleResetN n = sampleN n . unsafeToHighPolarity
-- >>> let resetFromList = unsafeFromHighPolarity . fromList
-- >>> let resetFromList = unsafeFromActiveHigh . fromList
-- >>> let rst = resetFromList [True, True, False, False, True, False, False, True, True, False, True, True]
-- >>> sampleResetN 12 (resetGlitchFilter d2 systemClockGen rst)
-- [True,True,True,True,False,False,False,False,False,True,True,True]
Expand Down Expand Up @@ -239,7 +243,7 @@ resetGlitchFilter SNat clk rst =
-- intermediate assertions of the reset signal:
--
-- >>> let rst = fromList [True, False, False, False, True, False, False, False]
-- >>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (unsafeFromHighPolarity rst))
-- >>> sampleWithReset (holdReset @System clockGen enableGen (SNat @2) (unsafeFromActiveHigh rst))
-- [True,True,True,False,True,True,True,False]
--
holdReset
Expand All @@ -255,7 +259,7 @@ holdReset
-- ^ Reset to extend
-> Reset dom
holdReset clk en SNat rst =
unsafeFromHighPolarity ((/=maxBound) <$> counter)
unsafeFromActiveHigh ((/=maxBound) <$> counter)
where
counter :: Signal dom (Index (n+1))
counter = register clk rst en 0 (satSucc SatBound <$> counter)
Expand Down
10 changes: 7 additions & 3 deletions clash-prelude/src/Clash/Explicit/Signal.hs
Expand Up @@ -208,8 +208,8 @@ module Clash.Explicit.Signal
, unsafeFromReset
, unsafeToHighPolarity
, unsafeToLowPolarity
, unsafeFromHighPolarity
, unsafeFromLowPolarity
, unsafeFromActiveHigh
, unsafeFromActiveLow
-- * Basic circuit functions
, andEnable
, enable -- DEPRECATED
Expand Down Expand Up @@ -267,6 +267,10 @@ module Clash.Explicit.Signal
, readFromBiSignal
, writeToBiSignal
, mergeBiSignalOuts

-- * Deprecated
, unsafeFromHighPolarity
, unsafeFromLowPolarity
)
where

Expand Down Expand Up @@ -813,7 +817,7 @@ simulateB_lazy f = simulate_lazy (bundle . f . unbundle)

-- | Like 'fromList', but resets on reset and has a defined reset value.
--
-- >>> let rst = unsafeFromHighPolarity (fromList [True, True, False, False, True, False])
-- >>> let rst = unsafeFromActiveHigh (fromList [True, True, False, False, True, False])
-- >>> let res = fromListWithReset @System rst Nothing [Just 'a', Just 'b', Just 'c']
-- >>> sampleN 6 res
-- [Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']
Expand Down
12 changes: 6 additions & 6 deletions clash-prelude/src/Clash/Intel/ClockGen.hs
Expand Up @@ -77,13 +77,13 @@ import Clash.Signal.Internal
-- where
-- (clk, pllStable) =
-- 'altpll' \@'Clash.Signal.System' ('SSymbol' \@\"altpll50to100\") clkInp
-- ('Clash.Signal.unsafeFromLowPolarity' rstInp)
-- rst = 'Clash.Signal.resetSynchronizer' clk ('Clash.Signal.unsafeFromLowPolarity' pllStable)
-- ('Clash.Signal.unsafeFromActiveLow' rstInp)
-- rst = 'Clash.Signal.resetSynchronizer' clk ('Clash.Signal.unsafeFromActiveLow' pllStable)
-- @
--
-- 'Clash.Signal.resetSynchronizer' will keep the reset asserted when
-- @pllStable@ is 'False', hence the use of
-- @'Clash.Signal.unsafeFromLowPolarity' pllStable@. Your circuit will have
-- @'Clash.Signal.unsafeFromActiveLow' pllStable@. Your circuit will have
-- signals of type @'Signal' 'Clash.Signal.System'@ and all the clocks and
-- resets of your components will be the @clk@ and @rst@ signals generated here
-- (modulo local resets, which will be based on @rst@ or never asserted at all
Expand Down Expand Up @@ -179,13 +179,13 @@ altpll !_ = knownDomain @domIn `seq` knownDomain @domOut `seq` clocks
-- where
-- (clk :: 'Clock' 'Clash.Signal.System', pllStable :: 'Signal' 'Clash.Signal.System' 'Bool')
-- 'alteraPll' ('SSymbol' \@\"alterapll50to100\") clkInp
-- ('Clash.Signal.unsafeFromLowPolarity' rstInp)
-- rst = 'Clash.Signal.resetSynchronizer' clk ('Clash.Signal.unsafeFromLowPolarity' pllStable)
-- ('Clash.Signal.unsafeFromActiveLow' rstInp)
-- rst = 'Clash.Signal.resetSynchronizer' clk ('Clash.Signal.unsafeFromActiveLow' pllStable)
-- @
--
-- 'Clash.Signal.resetSynchronizer' will keep the reset asserted when
-- @pllStable@ is 'False', hence the use of
-- @'Clash.Signal.unsafeFromLowPolarity' pllStable@. Your circuit will have
-- @'Clash.Signal.unsafeFromActiveLow' pllStable@. Your circuit will have
-- signals of type @'Signal' 'Clash.Signal.System'@ and all the clocks and
-- resets of your components will be the @clk@ and @rst@ signals generated here
-- (modulo local resets, which will be based on @rst@ or never asserted at all
Expand Down
10 changes: 7 additions & 3 deletions clash-prelude/src/Clash/Signal.hs
Expand Up @@ -138,8 +138,8 @@ module Clash.Signal
, unsafeFromReset
, unsafeToHighPolarity
, unsafeToLowPolarity
, unsafeFromHighPolarity
, unsafeFromLowPolarity
, unsafeFromActiveHigh
, unsafeFromActiveLow
#ifdef CLASH_MULTIPLE_HIDDEN
, convertReset
#endif
Expand Down Expand Up @@ -262,6 +262,10 @@ module Clash.Signal
, HiddenClockName
, HiddenResetName
, HiddenEnableName

-- * Deprecated
, unsafeFromHighPolarity
, unsafeFromLowPolarity
)
where

Expand Down Expand Up @@ -2252,7 +2256,7 @@ holdReset m =

-- | Like 'fromList', but resets on reset and has a defined reset value.
--
-- >>> let rst = unsafeFromHighPolarity (fromList [True, True, False, False, True, False])
-- >>> let rst = unsafeFromActiveHigh (fromList [True, True, False, False, True, False])
-- >>> let res = withReset rst (fromListWithReset Nothing [Just 'a', Just 'b', Just 'c'])
-- >>> sampleN @System 6 res
-- [Nothing,Nothing,Just 'a',Just 'b',Nothing,Just 'a']
Expand Down
50 changes: 43 additions & 7 deletions clash-prelude/src/Clash/Signal/Internal.hs
Expand Up @@ -97,8 +97,8 @@ module Clash.Signal.Internal
, unsafeFromReset
, unsafeToHighPolarity
, unsafeToLowPolarity
, unsafeFromHighPolarity
, unsafeFromLowPolarity
, unsafeFromActiveHigh
, unsafeFromActiveLow
, invertReset
-- * Basic circuits
, delay#
Expand Down Expand Up @@ -153,6 +153,10 @@ module Clash.Signal.Internal
, traverse#
-- * EXTREMELY EXPERIMENTAL
, joinSignal#

-- * Deprecated
, unsafeFromHighPolarity
, unsafeFromLowPolarity
)
where

Expand Down Expand Up @@ -1097,7 +1101,7 @@ resetGenN
-> Reset dom
resetGenN n =
let asserted = replicate (snatToNum n) True in
unsafeFromHighPolarity (fromList (asserted ++ repeat False))
unsafeFromActiveHigh (fromList (asserted ++ repeat False))
{-# ANN resetGenN hasBlackBox #-}
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE resetGenN #-}
Expand Down Expand Up @@ -1183,8 +1187,8 @@ unsafeFromReset (Reset r) = r
-- it can lead to <Clash-Explicit-Signal.html#metastability meta-stability>
-- issues in the presence of asynchronous resets.
--
-- __NB__: You probably want to use 'unsafeFromLowPolarity' or
-- 'unsafeFromHighPolarity'.
-- __NB__: You probably want to use 'unsafeFromActiveLow' or
-- 'unsafeFromActiveHigh'.
unsafeToReset
:: Signal dom Bool
-> Reset dom
Expand All @@ -1206,7 +1210,23 @@ unsafeFromHighPolarity
=> Signal dom Bool
-- ^ Reset signal that's 'True' when active, and 'False' when inactive.
-> Reset dom
unsafeFromHighPolarity r =
unsafeFromHighPolarity = unsafeFromActiveHigh
{-# DEPRECATED unsafeFromHighPolarity "Use 'unsafeFromActiveHigh' instead" #-}

-- | Interpret a signal of bools as an active high reset and convert it to
-- a reset signal corresponding to the domain's setting.
--
-- For asynchronous resets it is unsafe because it can cause combinatorial
-- loops. In case of synchronous resets it can lead to
-- <Clash-Explicit-Signal.html#metastability meta-stability> in the presence of
-- asynchronous resets.
unsafeFromActiveHigh
:: forall dom
. KnownDomain dom
=> Signal dom Bool
-- ^ Reset signal that's 'True' when active, and 'False' when inactive.
-> Reset dom
unsafeFromActiveHigh r =
unsafeToReset $
case resetPolarityProxy (Proxy @dom) of
SActiveHigh -> r
Expand All @@ -1225,7 +1245,23 @@ unsafeFromLowPolarity
=> Signal dom Bool
-- ^ Reset signal that's 'False' when active, and 'True' when inactive.
-> Reset dom
unsafeFromLowPolarity r =
unsafeFromLowPolarity = unsafeFromActiveLow
{-# DEPRECATED unsafeFromLowPolarity "Use 'unsafeFromActiveLow' instead" #-}

-- | Interpret a signal of bools as an active low reset and convert it to
-- a reset signal corresponding to the domain's setting.
--
-- For asynchronous resets it is unsafe because it can cause combinatorial
-- loops. In case of synchronous resets it can lead to
-- <Clash-Explicit-Signal.html#metastability meta-stability> in the presence of
-- asynchronous resets.
unsafeFromActiveLow
:: forall dom
. KnownDomain dom
=> Signal dom Bool
-- ^ Reset signal that's 'False' when active, and 'True' when inactive.
-> Reset dom
unsafeFromActiveLow r =
unsafeToReset $
case resetPolarityProxy (Proxy @dom) of
SActiveHigh -> not <$> r
Expand Down
8 changes: 4 additions & 4 deletions clash-prelude/src/Clash/Tutorial.hs
Expand Up @@ -924,8 +924,8 @@ topEntity
topEntity clk rst =
'exposeClockResetEnable' ('mealy' blinkerT (1,False,0) . Clash.Prelude.isRising 1) pllOut rstSync 'enableGen'
where
(pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' \@Dom100 (SSymbol \@\"altpll100\") clk ('Clash.Signal.unsafeFromLowPolarity' rst)
rstSync = 'Clash.Signal.resetSynchronizer' pllOut ('Clash.Signal.unsafeFromLowPolarity' pllStable)
(pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' \@Dom100 (SSymbol \@\"altpll100\") clk ('Clash.Signal.unsafeFromActiveLow' rst)
rstSync = 'Clash.Signal.resetSynchronizer' pllOut ('Clash.Signal.unsafeFromActiveLow' pllStable)
blinkerT (leds,mode,cntr) key1R = ((leds',mode',cntr'),leds)
where
Expand Down Expand Up @@ -2505,8 +2505,8 @@ topEntity
topEntity clk rst =
'exposeClockResetEnable' ('mealy' blinkerT (1,False,0) . Clash.Prelude.isRising 1) pllOut rstSync 'enableGen'
where
(pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' \@Dom100 (SSymbol \@\"altpll100\") clk ('Clash.Signal.unsafeFromLowPolarity' rst)
rstSync = 'Clash.Signal.resetSynchronizer' pllOut ('Clash.Signal.unsafeFromLowPolarity' pllStable)
(pllOut,pllStable) = 'Clash.Intel.ClockGen.altpll' \@Dom100 (SSymbol \@\"altpll100\") clk ('Clash.Signal.unsafeFromActiveLow' rst)
rstSync = 'Clash.Signal.resetSynchronizer' pllOut ('Clash.Signal.unsafeFromActiveLow' pllStable)
blinkerT (leds,mode,cntr) key1R = ((leds',mode',cntr'),leds)
where
Expand Down
4 changes: 2 additions & 2 deletions clash-prelude/tests/Clash/Tests/AsyncFIFOSynchronizer.hs
Expand Up @@ -1053,8 +1053,8 @@ fifoOperations racts wacts = (bundle (rAllDone, rel), bundle (wAllDone, wel))
wclk = clockGen @wdom
-- Not resetting makes the test easier to interpret and actual proper testing
-- of reset behaviour is a lot more involved.
noRRst = unsafeFromHighPolarity @rdom (pure False)
noWRst = unsafeFromHighPolarity @wdom (pure False)
noRRst = unsafeFromActiveHigh @rdom (pure False)
noWRst = unsafeFromActiveHigh @wdom (pure False)
(wdone, wact) =
unbundle $ fromList $ P.zip (P.repeat False) wacts <> P.repeat (True, WNoOp)
(rdone, ract) =
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/tests/Clash/Tests/Reset.hs
Expand Up @@ -23,7 +23,7 @@ sampleResetN :: KnownDomain dom => Int -> Reset dom -> [Bool]
sampleResetN n = sampleN n . unsafeToHighPolarity

resetFromList :: KnownDomain dom => [Bool] -> Reset dom
resetFromList = unsafeFromHighPolarity . fromList
resetFromList = unsafeFromActiveHigh . fromList

onePeriodGlitchReset :: KnownDomain dom => Reset dom
onePeriodGlitchReset =
Expand Down
2 changes: 1 addition & 1 deletion clash-prelude/tests/Clash/Tests/Signal.hs
Expand Up @@ -113,7 +113,7 @@ tests =
"Implicit"
[ -- See: https://github.com/clash-lang/clash-compiler/pull/655
let rst0 = fromList [True, True, False, False, True, True]
rst1 = unsafeFromHighPolarity rst0
rst1 = unsafeFromActiveHigh rst0
reg = register 'a' (pure 'b')
#ifdef CLASH_MULTIPLE_HIDDEN
sig = withReset rst1 reg
Expand Down
8 changes: 4 additions & 4 deletions examples/Blinker.hs
Expand Up @@ -65,8 +65,8 @@ topEntity clk20 rstBtn modeBtn =

-- Signal coming from the reset button is low when pressed, and high when
-- not pressed. We convert this signal to the polarity of our domain with
-- 'unsafeFromLowPolarity'.
rst = unsafeFromLowPolarity rstBtn
-- 'unsafeFromActiveLow'.
rst = unsafeFromActiveLow rstBtn

-- Instantiate a PLL: this stabilizes the incoming clock signal and indicates
-- when the signal is stable. We're also using it to transform an incoming
Expand All @@ -80,11 +80,11 @@ topEntity clk20 rstBtn modeBtn =

-- Synchronize reset to clock signal coming from PLL. We want the reset to
-- remain active while the PLL is NOT stable, hence the conversion with
-- 'unsafeFromLowPolarity'
-- 'unsafeFromActiveLow'
rstSync =
resetSynchronizer
clk50
(unsafeFromLowPolarity pllStable)
(unsafeFromActiveLow pllStable)

flipMode :: LedMode -> LedMode
flipMode Rotate = Complement
Expand Down
2 changes: 1 addition & 1 deletion tests/shouldwork/Cores/Xilinx/DcFifo/Basic.hs
Expand Up @@ -81,7 +81,7 @@ testBench = done
(pack <$> fifoData maxOut) (fExpectedData <$> fsmOut)
(fDone <$> fsmOut)
clk = tbClockGen (not <$> done)
noRst = unsafeFromHighPolarity $ pure False
noRst = unsafeFromActiveHigh $ pure False
en = enableGen
-- See: https://github.com/clash-lang/clash-compiler/pull/2511
{-# CLASH_OPAQUE testBench #-}
Expand Down
4 changes: 2 additions & 2 deletions tests/shouldwork/Cores/Xilinx/DcFifo/Lfsr.hs
Expand Up @@ -120,8 +120,8 @@ mkTestBench cFifo = done
where
(rClk, wClk) = biTbClockGen (not <$> done)

noRRst = unsafeFromHighPolarity $ pure False
noWRst = unsafeFromHighPolarity $ pure False
noRRst = unsafeFromActiveHigh $ pure False
noWRst = unsafeFromActiveHigh $ pure False

rEna = enableGen
wEna = enableGen
Expand Down
4 changes: 2 additions & 2 deletions tests/shouldwork/Cores/Xilinx/TdpBlockRam.hs
Expand Up @@ -31,10 +31,10 @@ topEntity
{-# CLASH_OPAQUE topEntity #-}

noRstA :: Reset A
noRstA = unsafeFromHighPolarity (pure False)
noRstA = unsafeFromActiveHigh (pure False)

noRstB :: Reset B
noRstB = unsafeFromHighPolarity (pure False)
noRstB = unsafeFromActiveHigh (pure False)

tb ::
( KnownNat n0, KnownNat n1, KnownNat n2, KnownNat n3
Expand Down
2 changes: 1 addition & 1 deletion tests/shouldwork/Cores/Xilinx/XpmCdcArraySingleTypes.hs
Expand Up @@ -14,7 +14,7 @@ createDomain vXilinxSystem{vName="D10", vPeriod=hzToPeriod 100e6}
createDomain vXilinxSystem{vName="D11", vPeriod=hzToPeriod 110e6}

noRst :: KnownDomain dom => Reset dom
noRst = unsafeFromHighPolarity (pure False)
noRst = unsafeFromActiveHigh (pure False)

tb ::
forall a b stages width n .
Expand Down

0 comments on commit de192fe

Please sign in to comment.