Skip to content

Commit

Permalink
Fix testsuite
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Jun 25, 2019
1 parent 897520b commit 699b277
Show file tree
Hide file tree
Showing 92 changed files with 1,008 additions and 772 deletions.
2 changes: 1 addition & 1 deletion benchmark/tests/PipelinesViaFolds.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module PipelinesViaFolds where
import Clash.Prelude
import Data.Word

topEntity :: SystemClockReset => Signal System Word32 -> Signal System Word32
topEntity :: SystemClockResetEnable => Signal System Word32 -> Signal System Word32
topEntity = pipeline
where
pipeline :: Signal System Word32 -> Signal System Word32
Expand Down
84 changes: 70 additions & 14 deletions examples/Blinker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,18 @@ module Blinker where
import Clash.Prelude
import Clash.Intel.ClockGen

type DomInput = Dom "Input" 20000
type Dom50 = Dom "System" 20000
data LedMode
= Rotate
-- ^ After some period, rotate active led to the left
| Complement
-- ^ After some period, turn on all disable LEDs, and vice versa
deriving (Generic, Undefined)

-- Define a synthesis domain with a clock with a period of 20000 /ps/.
createDomain vSystem{vTag="Input", vPeriod=20000}

-- Define a synthesis domain with a clock with a period of 50000 /ps/.
createDomain vSystem{vTag="Dom50", vPeriod=50000}

{-# ANN topEntity
(Synthesize
Expand All @@ -16,28 +26,74 @@ type Dom50 = Dom "System" 20000
, t_output = PortName "LED"
}) #-}
topEntity
:: Clock DomInput Source
-> Signal DomInput Bool
:: Clock Input
-- ^ Incoming clock
-> Signal Input Bool
-- ^ Reset signal, straight from KEY0
-> Signal Dom50 Bit
-- ^ Mode choice, straight from KEY1. See 'LedMode'.
-> Signal Dom50 (BitVector 8)
topEntity clk rst =
exposeClockReset (mealy blinkerT (1,False,0) . isRising 1) pllOut rstSync
where
(pllOut,pllStable) = altpll @Dom50 (SSymbol @"altpll50") clk (unsafeToAsyncReset (not <$> rst))
rstSync = resetSynchronizer pllOut (unsafeToAsyncReset (not <$> pllStable))
-- ^ Output containing 8 bits, corresponding to 8 LEDs
topEntity clk20 rstBtn modeBtn =
exposeClockResetEnable
(mealy blinkerT initialStateBlinkerT . isRising 1)
clk50
rstSync
en
modeBtn
where
-- | Enable line for subcomponents: we'll keep it always running
en = enableGen

-- Start with the first LED turned on, in rotate mode, with the counter on zero
initialStateBlinkerT = (1, Rotate, 0)

-- 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
-- 'unsafeFromActiveLow'.
rst = unsafeFromLowPolarity 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
-- clock signal running at 20 MHz to a clock signal running at 50 MHz.
(clk50, pllStable) =
altpll
@Dom50
(SSymbol @"altpll50")
clk20
rst

-- 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
-- 'unsafeFromActiveLow'
rstSync =
resetSynchronizer
clk50
(unsafeFromLowPolarity pllStable)
en

flipMode :: LedMode -> LedMode
flipMode Rotate = Complement
flipMode Complement = Rotate

blinkerT (leds,mode,cntr) key1R = ((leds',mode',cntr'),leds)
blinkerT
:: (BitVector 8, LedMode, Index 16650001)
-> Bool
-> ((BitVector 8, LedMode, Index 16650001), BitVector 8)
blinkerT (leds, mode, cntr) key1R = ((leds', mode', cntr'), leds)
where
-- clock frequency = 50e6 (50 MHz)
-- led update rate = 333e-3 (every 333ms)
cnt_max = 16650000 :: (Index 16650001) -- 50e6 * 333e-3
cnt_max = 16650000 :: Index 16650001 -- 50e6 * 333e-3

cntr' | cntr == cnt_max = 0
| otherwise = cntr + 1

mode' | key1R = not mode
mode' | key1R = flipMode mode
| otherwise = mode

leds' | cntr == 0 = if mode then complement leds
else rotateL leds 1
leds' | cntr == 0 =
case mode of
Rotate -> rotateL leds 1
Complement -> complement leds
| otherwise = leds
5 changes: 3 additions & 2 deletions examples/BlockRamTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,9 @@ module BlockRamTest where
import Clash.Prelude

topEntity
:: Clock System Source
:: Clock System
-> Enable System
-> Signal System (Unsigned 7)
-> Signal System (Maybe (Unsigned 7,Unsigned 4))
-> Signal System (Unsigned 4)
topEntity = exposeClock (blockRamPow2 (repeat 0))
topEntity clk en = exposeEnable (exposeClock (blockRamPow2 (repeat 0)) clk) en
11 changes: 6 additions & 5 deletions examples/CHIP8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,22 +13,23 @@ import Data.Monoid

{-# NOINLINE topEntity #-}
topEntity
:: Clock System Source
-> Reset System Asynchronous
:: Clock System
-> Reset System
-> Enable System
-> ( Signal System Bit
)
topEntity = exposeClockReset output
topEntity = exposeClockResetEnable output
where
cpuIn = pure CPUIn{ cpuInMem = 0x00 }
cpuOut = mealyState (runCPU defaultOut cpu) initState cpuIn
output = boolToBit . (== 0x00) . cpuOutMemAddr <$> cpuOut

mealyState
:: ( HiddenClockReset domain gated synchronous
:: ( HiddenClockResetEnable tag dom
, Undefined s )
=> (i -> State s o)
-> s
-> (Signal domain i -> Signal domain o)
-> (Signal tag i -> Signal tag o)
mealyState f = mealy $ \s x -> let (y, s') = runState (f x) s in (s', y)

data Phase
Expand Down
9 changes: 5 additions & 4 deletions examples/Calculator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,11 +34,12 @@ datamem mem (addr,Nothing) = (mem ,mem !! addr)
datamem mem (addr,Just val) = (replace addr val mem,mem !! addr)

topEntity
:: Clock System Source
-> Reset System Asynchronous
:: Clock System
-> Reset System
-> Enable System
-> Signal System (OPC Word)
-> Signal System (Maybe Word)
topEntity = exposeClockReset go where
topEntity = exposeClockResetEnable go where
go i = val where
(addr,val) = (pu alu <^> (0,0,0 :: Unsigned 3)) (mem,i)
mem = (datamem <^> initMem) (addr,val)
Expand All @@ -50,6 +51,6 @@ testBench = done
where
testInput = stimuliGenerator clk rst $(listToVecTH [Imm 1::OPC Word,Push,Imm 2,Push,Pop,Pop,Pop,ADD])
expectedOutput = outputVerifier clk rst $(listToVecTH [Just 1 :: Maybe Word,Nothing,Just 2,Nothing,Nothing,Nothing,Nothing,Just 3])
done = expectedOutput (topEntity clk rst testInput)
done = expectedOutput (topEntity clk rst (enableGen) testInput)
clk = tbSystemClockGen (not <$> done)
rst = systemResetGen
Loading

0 comments on commit 699b277

Please sign in to comment.