Skip to content

Commit e03d309

Browse files
committed
Port to Clash 1.4.2
1 parent 4d35a50 commit e03d309

File tree

25 files changed

+134
-130
lines changed

25 files changed

+134
-130
lines changed

Makefile

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,7 @@ ICO_BF_SOURCES=\
7171
build/ico_soc_clash.v: $(ICO_RTL_SOURCES) build/stack
7272
rtl/clash -irtl/src -iarch/src -outputdir build/clash \
7373
-fclash-inline-limit=50 --verilog rtl/src/RTL/IcoTop.hs
74-
cat build/clash/verilog/RTL/ico_soc/*.v > $@
74+
cat build/clash/RTL.IcoTop.topEntity/*.v > $@
7575

7676
build/ico.blif: build/ico_soc_clash.v rtl/syn/ico-top.v
7777
cd rtl/syn && yosys -q \
@@ -143,7 +143,7 @@ ICE_BF_SOURCES=\
143143
build/icestick_soc_clash.v: $(ICE_RTL_SOURCES) build/stack
144144
rtl/clash -irtl/src -iarch/src -outputdir build/clash \
145145
-fclash-inline-limit=50 --verilog rtl/src/RTL/IcestickTop.hs
146-
cat build/clash/verilog/RTL/icestick_soc/*.v > $@
146+
cat build/clash/RTL.IcestickTop.topEntity/*.v > $@
147147

148148
build/icestick.blif: build/icestick_soc_clash.v rtl/syn/icestick-top.v
149149
cd rtl/syn && yosys -q \

arch/src/CFM/Inst.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@ module CFM.Inst
1515
) where
1616

1717
import Clash.Prelude
18-
import GHC.Generics
1918
import Control.DeepSeq (NFData)
2019
import Test.QuickCheck
2120

@@ -69,7 +68,7 @@ data TMux = T -- ^ 0: Same value as this cycle.
6968
deriving (Eq, Enum, Bounded, Show)
7069

7170
data Space = MSpace | ISpace
72-
deriving (Eq, Show, Enum, Bounded, Generic, ShowX, NFData)
71+
deriving (Eq, Show, Enum, Bounded, Generic, ShowX, NFData, NFDataX)
7372

7473
instance BitPack Space where
7574
type BitSize Space = 1

rtl/src/RTL/Beh.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ executeNormally = do
6868
msRPtr += 1 -- push return stack
6969
fetch
7070
<&> osROp . _2 .~ 1
71-
<&> osROp . _3 .~ Just (zeroExtend $ pc' ++# low)
71+
<&> osROp . _3 .~ Just (zeroExtend $ pc' ++# pack low)
7272

7373
NotLit (ALU rpc t' tn tr nm space rd dd) -> do
7474
n <- view isDData

rtl/src/RTL/BootROM.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ import CFM.Types
3131
-- monitors the CPU fetch bus, and on the *second* such jump (the first having
3232
-- activated the boot program at reset), the interposer disables itself and
3333
-- normal RAM is exposed.
34-
bootROM :: (HasClockReset d g s, KnownNat a)
34+
bootROM :: (HiddenClockResetEnable d, KnownNat a)
3535
=> SNat n
3636
-- ^ Size of the ROM.
3737
-> FilePath

rtl/src/RTL/Core.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -13,14 +13,14 @@ import RTL.Str
1313
import RTL.CoreInterface
1414

1515
-- | Registered version of the core datapath.
16-
core :: HasClockReset dom gated synchronous
16+
core :: HiddenClockResetEnable dom
1717
=> Signal dom IS -> Signal dom OS
1818
core = mealy datapath def
1919

2020
-- | Combines 'core' with the selected implementation of stacks, and exposes
2121
-- the local bus interface.
2222
coreWithStacks
23-
:: (HasClockReset dom gated synchronous)
23+
:: (HiddenClockResetEnable dom)
2424
=> Signal dom Cell -- ^ read response from memory
2525
-> Signal dom Cell -- ^ read response from I/O
2626
-> ( Signal dom BusReq
@@ -38,7 +38,7 @@ coreWithStacks mresp ioresp = (mreq, ireq, fetch)
3838
n = stack "D" $ coreOuts <&> (^. osDOp)
3939
r = stack "R" $ coreOuts <&> (^. osROp)
4040

41-
stack :: (HasClockReset d g s)
41+
stack :: (HiddenClockResetEnable d)
4242
=> String -> Signal d (SP, SDelta, Maybe Cell) -> Signal d Cell
4343
stack name op = readNew (blockRamPow2 (repeat $ errorX name))
4444
(op <&> (^. _1) <&> unpack)
@@ -50,7 +50,7 @@ stack name op = readNew (blockRamPow2 (repeat $ errorX name))
5050
-- | Combines 'coreWithStacks' with a RAM built from the given constructor, and
5151
-- an I/O bridge, exposing the I/O bus.
5252
coreWithRAM
53-
:: (HasClockReset dom gated synchronous)
53+
:: (HiddenClockResetEnable dom)
5454
=> (Signal dom (Maybe (CellAddr, Maybe Cell)) -> Signal dom Cell)
5555
-- ^ RAM constructor
5656
-> Signal dom Cell -- ^ I/O read response, valid when addressed.

rtl/src/RTL/CoreInterface.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@
88
module RTL.CoreInterface where
99

1010
import Clash.Prelude hiding (cycle)
11-
import GHC.Generics
1211

1312
import Control.DeepSeq (NFData)
1413
import Control.Lens hiding ((:>))
@@ -24,7 +23,7 @@ data BusState = BusFetch
2423
| BusData Bool
2524
-- ^ The bus was used for something else. The bool flag
2625
-- indicates that the bus response should be written to T.
27-
deriving (Eq, Show, Generic, ShowX, NFData)
26+
deriving (Eq, Show, Generic, ShowX, NFData, NFDataX)
2827

2928
instance Arbitrary BusState where
3029
arbitrary = oneof [ pure BusFetch
@@ -46,7 +45,7 @@ data MS = MS
4645
, _msT :: Cell
4746
, _msBusState :: BusState
4847
, _msLastSpace :: Space
49-
} deriving (Show, Generic, ShowX, NFData)
48+
} deriving (Show, Generic, ShowX, NFData, NFDataX)
5049
makeLenses ''MS
5150

5251
-- At reset, pretend we're in the second phase of a store. We'll ignore the

rtl/src/RTL/GPIO.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
{-# LANGUAGE NoImplicitPrelude #-}
22
{-# LANGUAGE DataKinds #-}
3+
{-# LANGUAGE DeriveAnyClass #-}
4+
{-# LANGUAGE DeriveGeneric #-}
35
{-# LANGUAGE ScopedTypeVariables #-}
46
{-# LANGUAGE TypeOperators #-}
57
{-# LANGUAGE TypeFamilies #-}
@@ -17,7 +19,7 @@ import CFM.Types
1719
-- - +4: NAND output pins. 1 bits will clear pins, 0 bits have no effect.
1820
--
1921
-- Reading from any address gets the current pin status.
20-
outport :: (HasClockReset d g s)
22+
outport :: (HiddenClockResetEnable d)
2123
=> Signal d (Maybe (BitVector 2, Maybe Cell))
2224
-> ( Signal d Cell
2325
, Signal d Cell
@@ -41,7 +43,7 @@ outport = moorep outportT repeat id (pure ())
4143
--
4244
-- It also produces an interrupt on negative edges of bit 0. The interrupt
4345
-- condition can be cleared by any write to the port's address space.
44-
inport :: (KnownNat a, HasClockReset d g s)
46+
inport :: (KnownNat a, HiddenClockResetEnable d)
4547
=> Signal d Cell
4648
-> Signal d (Maybe (BitVector a, Maybe Cell))
4749
-> ( Signal d Cell
@@ -56,7 +58,7 @@ inport = moorep inportT (repeat . \(InportS x _) -> x) (\(InportS _ x) -> x)
5658
Just (_, Just _) -> False
5759
-- Otherwise, OR in the negative edge detector.
5860
_ -> irq || negedge
59-
negedge = unpack (lsb reg .&. complement (lsb port))
61+
negedge = bitCoerce (lsb reg .&. complement (lsb port))
6062

61-
data InportS = InportS Cell Bool deriving (Show)
63+
data InportS = InportS Cell Bool deriving (Show, Generic, NFDataX)
6264
instance Default InportS where def = InportS def False

rtl/src/RTL/IOBus.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@ topBits = fst . split
7575
-- Each cycle, the 'ioDecoder' sends its muxing decision as a @BitVector m@
7676
-- (when an I/O device is selected at all. On the next cycle, the 'responseMux'
7777
-- selects the corresponding channel out of @2 ^ m@ device response channels.
78-
responseMux :: forall m t d g s. (KnownNat m, HasClockReset d g s)
78+
responseMux :: forall m t d. (KnownNat m, HiddenClockResetEnable d)
7979
=> Vec (2 ^ m) (Signal d t) -- ^ response from each device
8080
-> Signal d (Maybe (BitVector m)) -- ^ decoder output
8181
-> Signal d t -- ^ response to core
@@ -98,7 +98,7 @@ partialDecode = fmap truncateAddr
9898
--
9999
-- The reset state of the machine is given by 'def' for the state type, for
100100
-- convenience.
101-
moorep :: (KnownNat a, HasClockReset dom gated synchronous, Default s)
101+
moorep :: (KnownNat a, HiddenClockResetEnable dom, Default s, NFDataX s)
102102
=> (s -> (Maybe (BitVector a, Maybe Cell), i) -> s)
103103
-- ^ State transition function.
104104
-> (s -> Vec (2^a) Cell)
@@ -129,7 +129,7 @@ moorep ft fr fo = \inp ioreq ->
129129
--
130130
-- The reset state of the machine is given by 'def' for the state type, for
131131
-- convenience.
132-
mealyp :: (KnownNat a, HasClockReset dom gated synchronous, Default s)
132+
mealyp :: (KnownNat a, HiddenClockResetEnable dom, Default s, NFDataX s)
133133
=> (s -> (Maybe (BitVector a, Maybe Cell), i) -> (s, o))
134134
-- ^ State transition and outputs function.
135135
-> (s -> Vec (2^a) Cell)

rtl/src/RTL/IRQ.hs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
{-# LANGUAGE NoImplicitPrelude #-}
22
{-# LANGUAGE DataKinds #-}
3+
{-# LANGUAGE DeriveAnyClass #-}
4+
{-# LANGUAGE DeriveGeneric #-}
35
{-# LANGUAGE ScopedTypeVariables #-}
46
{-# LANGUAGE TypeOperators #-}
57
{-# LANGUAGE ViewPatterns #-}
@@ -28,7 +30,7 @@ vectorMux vf = mux (fromStrobe <$> vf) (pure $ pack $ NotLit $ Call 1)
2830
-- space. They are disabled when an interrupt occurs. Currently, there is no
2931
-- way to disable interrupts programatically.
3032
singleIrqController
31-
:: (HasClockReset d g s)
33+
:: (HiddenClockResetEnable d)
3234
=> Signal d Bool -- ^ Interrupt input, active high, level-sensitive.
3335
-> Signal d Bool -- ^ CPU fetch signal, active high.
3436
-> Signal d (Maybe (BitVector 1, Maybe Cell)) -- ^ I/O bus request.
@@ -67,7 +69,7 @@ data SIS = SIS
6769
, sisEnter :: Bool
6870
-- ^ Interrupt entry event strobe. Goes high on the cycle when a fetch
6971
-- is being replaced by a vector.
70-
} deriving (Show)
72+
} deriving (Show, Generic, NFDataX)
7173

7274
instance Default SIS where def = SIS False False
7375

@@ -96,7 +98,7 @@ instance Default SIS where def = SIS False False
9698
-- interrupt. On writes, zero bits are ignored. Reads as the interrupt
9799
-- enable mask (the same as IRQSE).
98100
multiIrqController
99-
:: (HasClockReset d g s)
101+
:: (HiddenClockResetEnable d)
100102
=> Vec Width (Signal d Bool)
101103
-- ^ Interrupt inputs, active high, level-sensitive.
102104
-> Signal d Bool -- ^ CPU fetch signal, active high.
@@ -123,7 +125,7 @@ multiIrqController irqS fetchS reqS = (vfaS, vfdS, eiS, respS)
123125
-- Any write to the enable-trigger register enables.
124126
Just (0, Just _) -> True
125127
-- The bottom bit of writes @ 1 gets copied into the enable bit.
126-
Just (1, Just v) -> unpack $ lsb v
128+
Just (1, Just v) -> bitCoerce $ lsb v
127129
-- Anything else leaves matters unchanged.
128130
_ -> misEn s
129131

@@ -154,7 +156,7 @@ data MIS = MIS
154156
-- ^ Individual interrupt enable flags.
155157
, misEnter :: Bool
156158
-- ^ Vector fetch flag. Set during the cycle where we intercede in fetch.
157-
} deriving (Show)
159+
} deriving (Show, Generic, NFDataX)
158160

159161
instance Default MIS where
160162
def = MIS False (repeat False) (repeat False) False

rtl/src/RTL/IcestickTop.hs

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ import RTL.GPIO
1414
import RTL.Core
1515
import RTL.UART
1616

17-
system :: (HasClockReset dom gated synchronous)
17+
system :: (HiddenClockResetEnable dom)
1818
=> FilePath
1919
-> Signal dom Cell
2020
-> Signal dom Bit -- UART RX
@@ -36,20 +36,20 @@ system raminit ins urx = (outs, utx)
3636
partialDecode ioreq3
3737
irqs = irq0 :> urxne :> repeat (pure False)
3838

39-
{-# ANN topEntity (defTop { t_name = "icestick_soc"
40-
, t_inputs = [ PortName "clk_core"
41-
, PortName "reset"
42-
, PortName "inport"
43-
, PortName "uart_rx"
44-
]
45-
, t_output = PortField ""
46-
[ PortName "out1"
47-
, PortName "uart_tx"
48-
]
49-
}) #-}
50-
topEntity :: Clock System 'Source
51-
-> Reset System 'Asynchronous
39+
{-# ANN topEntity (Synthesize { t_name = "icestick_soc"
40+
, t_inputs = [ PortName "clk_core"
41+
, PortName "reset"
42+
, PortName "inport"
43+
, PortName "uart_rx"
44+
]
45+
, t_output = PortProduct ""
46+
[ PortName "out1"
47+
, PortName "uart_tx"
48+
]
49+
}) #-}
50+
topEntity :: Clock System
51+
-> Reset System
5252
-> Signal System Cell
5353
-> Signal System Bit
5454
-> (Signal System Cell, Signal System Bit)
55-
topEntity c r = withClockReset c r $ system "random-3k5.readmemb"
55+
topEntity c r = withClockResetEnable c r enableGen $ system "rtl/syn/random-3k5.readmemb"

0 commit comments

Comments
 (0)