Skip to content

Commit 9b7e5f1

Browse files
committed
Generalize XLEN.
It's not RV64I yet, for it has no `*w` instructions (`addw` and such).
1 parent 264e781 commit 9b7e5f1

File tree

10 files changed

+275
-223
lines changed

10 files changed

+275
-223
lines changed

lion-formal/src/LionFV.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,9 @@ License : BSD-3-Clause
66
Maintainer : [email protected]
77
-}
88

9+
{-# LANGUAGE FlexibleContexts #-}
10+
{-# LANGUAGE GADTs #-}
11+
912
module LionFV where
1013

1114
import Clash.Prelude
@@ -17,13 +20,14 @@ import Lion.Rvfi ( Rvfi )
1720

1821
lionFV
1922
:: HiddenClockResetEnable dom
20-
=> Signal dom (BitVector 32) -- ^ mem_rdata
23+
=> (KnownNat xl, KnownNat (Log2 xl), 1 <= Div xl 8)
24+
=> Signal dom (BitVector xl) -- ^ mem_rdata
2125
-> ( Signal dom Bool -- mem_valid
2226
, Signal dom Bool -- mem_instr
23-
, Signal dom (BitVector 32) -- mem_addr
24-
, Signal dom (BitVector 32) -- mem_wdata
25-
, Signal dom (BitVector 4) -- mem_wstrb
26-
, Signal dom Rvfi -- rvfi
27+
, Signal dom (BitVector xl) -- mem_addr
28+
, Signal dom (BitVector xl) -- mem_wdata
29+
, Signal dom (BitVector (Div xl 8)) -- mem_wstrb
30+
, Signal dom (Rvfi xl) -- rvfi
2731
)
2832
lionFV memRData =
2933
( memValid
@@ -41,7 +45,7 @@ lionFV memRData =
4145
memWData = fromMaybe 0 . (memWrite =<<) <$> toMem fromCore
4246
memWStrb = maybe 0 memByteMask <$> toMem fromCore
4347

44-
isInstr :: ToMem -> Bool
48+
isInstr :: ToMem xl -> Bool
4549
isInstr = (== InstrMem) . memAccess
4650

4751
{-# NOINLINE topEntity #-}
@@ -54,7 +58,7 @@ topEntity
5458
, "mem_addr" ::: Signal System (BitVector 32)
5559
, "mem_wdata" ::: Signal System (BitVector 32)
5660
, "mem_wstrb" ::: Signal System (BitVector 4)
57-
, "rvfi" ::: Signal System Rvfi
61+
, "rvfi" ::: Signal System (Rvfi 32)
5862
)
5963
topEntity clk rst = exposeClockResetEnable lionFV clk rst enableGen
6064
makeTopEntityWithName 'topEntity "LionFV"

lion-metric/src/Metric.hs

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,9 @@ Maintainer : [email protected]
88
Core top entity to observe yosys metrics when synthesized for iCE40
99
-}
1010

11+
{-# LANGUAGE FlexibleContexts #-}
12+
{-# LANGUAGE GADTs #-}
13+
1114
module Metric where
1215

1316
import Clash.Prelude
@@ -16,15 +19,16 @@ import Lion.Core
1619

1720
metric
1821
:: HiddenClockResetEnable dom
19-
=> Signal dom (BitVector 32)
20-
-> Signal dom (Maybe ToMem)
22+
=> (KnownNat xl, KnownNat (Log2 xl), 1 <= Div xl 8)
23+
=> Signal dom (BitVector xl)
24+
-> Signal dom (Maybe (ToMem xl))
2125
metric = toMem . core defaultCoreConfig
2226

2327
{-# NOINLINE topEntity #-}
2428
topEntity
2529
:: "clk" ::: Clock System
2630
-> "rst" ::: Reset System
2731
-> "fromMem" ::: Signal System (BitVector 32)
28-
-> "toMem" ::: Signal System (Maybe ToMem)
32+
-> "toMem" ::: Signal System (Maybe (ToMem 32))
2933
topEntity clk rst = withClockResetEnable clk rst enableGen metric
3034
makeTopEntityWithName 'topEntity "Metric"

lion-soc/src/Bus.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -50,21 +50,21 @@ data BusOut (p :: Peripheral) where
5050
FromSpram :: BitVector 32 -> BusOut 'Spram
5151
FromSpi :: BitVector 32 -> BusOut 'Spi
5252

53-
romMap :: Maybe ToMem -> BusIn 'Rom
53+
romMap :: Maybe (ToMem 32) -> BusIn 'Rom
5454
romMap = ToRom . wordAddr . maybe 0 memAddress
5555
where
5656
wordAddr :: BitVector 32 -> Unsigned 8
5757
wordAddr a = unpack $ slice d7 d0 $ a `shiftR` 2
5858

59-
uartMap :: Peripheral -> Maybe ToMem -> BusIn 'Uart
59+
uartMap :: Peripheral -> Maybe (ToMem 32) -> BusIn 'Uart
6060
uartMap Uart (Just (ToMem DataMem _ msk wrM)) = ToUart (slice d2 d0 msk) $ slice d7 d0 <$> wrM
6161
uartMap _ _ = ToUart 0 Nothing
6262

63-
ledMap :: Peripheral -> Maybe ToMem -> BusIn 'Led
63+
ledMap :: Peripheral -> Maybe (ToMem 32) -> BusIn 'Led
6464
ledMap Led (Just (ToMem _ _ $(bitPattern "..11") (Just d))) = ToLed (slice d11 d8 d) (slice d7 d0 d) True
6565
ledMap _ _ = ToLed 0 0 False
6666

67-
spramMap :: Peripheral -> Maybe ToMem -> BusIn 'Spram
67+
spramMap :: Peripheral -> Maybe (ToMem 32) -> BusIn 'Spram
6868
spramMap _ Nothing = ToSpram 0 0 0 0
6969
spramMap periph (Just mem) = case (periph, memWrite mem) of
7070
(Spram, Just wr) -> ToSpram wordAddr wr nybMask 1
@@ -78,11 +78,11 @@ spramMap periph (Just mem) = case (periph, memWrite mem) of
7878
| b == high = 0b11
7979
| otherwise = 0b00
8080

81-
spiMap :: Peripheral -> Maybe ToMem -> BusIn 'Spi
81+
spiMap :: Peripheral -> Maybe (ToMem 32) -> BusIn 'Spi
8282
spiMap Spi (Just (ToMem DataMem _ mask wrM)) = ToSpi mask wrM
8383
spiMap _ _ = ToSpi 0 Nothing
8484

85-
selectPeripheral :: Maybe ToMem -> Peripheral
85+
selectPeripheral :: Maybe (ToMem 32) -> Peripheral
8686
selectPeripheral Nothing = Rom
8787
selectPeripheral (Just toMem)
8888
| checkRegion 17 = Spram

lion.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ library
2424
other-modules: Lion.Alu
2525
, Lion.Instruction
2626
, Lion.Pipe
27+
, Lion.Util.Clash
2728
hs-source-dirs: src
2829
default-language: Haskell2010
2930
build-depends:

src/Lion/Alu.hs

Lines changed: 22 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -11,44 +11,46 @@ Configurable alu, choose between soft and hard adders/subtractors
1111
module Lion.Alu where
1212

1313
import Clash.Prelude
14+
import Data.Bool ( bool )
1415
import Data.Function ( on )
1516
import Data.Proxy
1617
import Ice40.Mac
1718
import Lion.Instruction
19+
import Lion.Util.Clash
1820

1921
-- | ALU configuration
2022
data AluConfig = Hard -- ^ use hard adder and subtractor from iCE40 SB_MAC16
2123
| Soft -- ^ use generic adder and subtractor: (+) and (-)
2224
deriving stock (Generic, Show, Eq)
2325

24-
class Alu (config :: AluConfig) where
25-
alu :: HiddenClockResetEnable dom
26+
class Alu (xl :: Nat) (config :: AluConfig) where
27+
alu :: (KnownNat xl, KnownNat (Log2 xl))
28+
=> HiddenClockResetEnable dom
2629
=> Proxy (config :: AluConfig)
2730
-> Signal dom Op
28-
-> Signal dom (BitVector 32)
29-
-> Signal dom (BitVector 32)
30-
-> Signal dom (BitVector 32)
31+
-> Signal dom (BitVector xl)
32+
-> Signal dom (BitVector xl)
33+
-> Signal dom (BitVector xl)
3134

32-
instance Alu 'Soft where
35+
instance Alu xl 'Soft where
3336
alu _ op in1 = register 0 . liftA3 aluFunc op in1
3437
where
3538
aluFunc = \case
3639
Add -> (+)
3740
Sub -> (-)
3841
Sll -> \x y -> x `shiftL` shamt y
39-
Slt -> boolToBV ... (<) `on` sign
40-
Sltu -> boolToBV ... (<)
42+
Slt -> bool 0 1 ... (<) `on` sign
43+
Sltu -> bool 0 1 ... (<)
4144
Xor -> xor
4245
Srl -> \x y -> x `shiftR` shamt y
4346
Sra -> \x y -> pack $ sign x `shiftR` shamt y
4447
Or -> (.|.)
4548
And -> (.&.)
4649
where
47-
shamt = unpack . resize . slice d4 d0
48-
sign = unpack :: BitVector 32 -> Signed 32
50+
shamt = fromEnum . resizeTo (SNat :: SNat (Log2 xl))
4951
(...) = (.).(.)
5052

51-
instance Alu 'Hard where
53+
instance Alu 32 'Hard where
5254
alu _ op in1 in2 = mux isAddSub adderSubtractor $ register 0 $ baseAlu op in1 in2
5355
where
5456
isAdd = (Add == ) <$> op
@@ -57,24 +59,25 @@ instance Alu 'Hard where
5759
adderSubtractor = hardAddSub (boolToBit <$> isSub) in1 in2
5860

5961
baseAlu
60-
:: Signal dom Op
61-
-> Signal dom (BitVector 32)
62-
-> Signal dom (BitVector 32)
63-
-> Signal dom (BitVector 32)
62+
:: forall dom xl
63+
. (KnownNat xl, KnownNat (Log2 xl))
64+
=> Signal dom Op
65+
-> Signal dom (BitVector xl)
66+
-> Signal dom (BitVector xl)
67+
-> Signal dom (BitVector xl)
6468
baseAlu = liftA3 $ \case
6569
Add -> \_ _ -> 0
6670
Sub -> \_ _ -> 0
6771
Sll -> \x y -> x `shiftL` shamt y
68-
Slt -> boolToBV ... (<) `on` sign
69-
Sltu -> boolToBV ... (<)
72+
Slt -> bool 0 1 ... (<) `on` sign
73+
Sltu -> bool 0 1 ... (<)
7074
Xor -> xor
7175
Srl -> \x y -> x `shiftR` shamt y
7276
Sra -> \x y -> pack $ sign x `shiftR` shamt y
7377
Or -> (.|.)
7478
And -> (.&.)
7579
where
76-
shamt = unpack . resize . slice d4 d0
77-
sign = unpack :: BitVector 32 -> Signed 32
80+
shamt = fromEnum . resizeTo (SNat :: SNat (Log2 xl))
7881
(...) = (.).(.)
7982

8083
-- | addSub32PipelinedUnsigned

src/Lion/Core.hs

Lines changed: 16 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ Copyright : (c) David Cox, 2021
55
License : BSD-3-Clause
66
Maintainer : [email protected]
77
8-
The Lion core is a 32-bit [RISC-V](https://riscv.org/about/) processor written in Haskell using [Clash](https://clash-lang.org). Note, all peripherals and memory must have single cycle latency. See [lion-soc](https://github.com/standardsemiconductor/lion/tree/main/lion-soc) for an example of using the Lion core in a system.
8+
The Lion core is a xl-bit [RISC-V](https://riscv.org/about/) processor written in Haskell using [Clash](https://clash-lang.org). Note, all peripherals and memory must have single cycle latency. See [lion-soc](https://github.com/standardsemiconductor/lion/tree/main/lion-soc) for an example of using the Lion core in a system.
99
-}
1010

1111
module Lion.Core
@@ -49,20 +49,21 @@ defaultCoreConfig = CoreConfig
4949
}
5050

5151
-- | Core outputs
52-
data FromCore dom = FromCore
53-
{ toMem :: Signal dom (Maybe P.ToMem) -- ^ shared memory and instruction bus, output from core to memory and peripherals
54-
, toRvfi :: Signal dom Rvfi -- ^ formal verification interface output, see [lion-formal](https://github.com/standardsemiconductor/lion/tree/main/lion-formal) for usage
52+
data FromCore dom xl = FromCore
53+
{ toMem :: Signal dom (Maybe (P.ToMem xl)) -- ^ shared memory and instruction bus, output from core to memory and peripherals
54+
, toRvfi :: Signal dom (Rvfi xl) -- ^ formal verification interface output, see [lion-formal](https://github.com/standardsemiconductor/lion/tree/main/lion-formal) for usage
5555
}
5656

57-
-- | RISC-V Core: RV32I
57+
-- | RISC-V Core: RV(32, 64)I
5858
core
59-
:: forall a startPC dom
60-
. HiddenClockResetEnable dom
61-
=> Alu a
62-
=> (KnownNat startPC, startPC <= 0xFFFFFFFF)
59+
:: forall a startPC dom xl
60+
. (KnownNat xl, KnownNat (Log2 xl), 1 <= Div xl 8)
61+
=> HiddenClockResetEnable dom
62+
=> Alu xl a
63+
=> (KnownNat startPC, startPC + 1 <= 2^xl)
6364
=> CoreConfig (startPC :: Nat) (a :: AluConfig) -- ^ core configuration
64-
-> Signal dom (BitVector 32) -- ^ core input, from memory/peripherals
65-
-> FromCore dom -- ^ core output
65+
-> Signal dom (BitVector xl) -- ^ core input, from memory/peripherals
66+
-> FromCore dom xl -- ^ core output
6667
core config toCore = FromCore
6768
{ toMem = getFirst . P._toMem <$> fromPipe
6869
, toRvfi = fromMaybe mkRvfi . getFirst . P._toRvfi <$> fromPipe
@@ -87,11 +88,12 @@ core config toCore = FromCore
8788

8889
-- | Register bank
8990
regBank
90-
:: HiddenClockResetEnable dom
91+
:: KnownNat xl
92+
=> HiddenClockResetEnable dom
9193
=> Signal dom (Unsigned 5) -- ^ Rs1 Addr
9294
-> Signal dom (Unsigned 5) -- ^ Rs2 Addr
93-
-> Signal dom (Maybe (Unsigned 5, BitVector 32)) -- ^ Rd Write
94-
-> Unbundled dom (BitVector 32, BitVector 32) -- ^ (Rs1Data, Rs2Data)
95+
-> Signal dom (Maybe (Unsigned 5, BitVector xl)) -- ^ Rd Write
96+
-> Unbundled dom (BitVector xl, BitVector xl) -- ^ (Rs1Data, Rs2Data)
9597
regBank rs1Addr rs2Addr rdWrM = (regFile rs1Addr, regFile rs2Addr)
9698
where
9799
regFile = flip (readNew (blockRamPow2 (repeat 0))) rdWrM

0 commit comments

Comments
 (0)