Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
hydrolarus committed Mar 1, 2024
1 parent 03c7e5e commit f0d1150
Show file tree
Hide file tree
Showing 9 changed files with 159 additions and 33 deletions.
4 changes: 2 additions & 2 deletions clash-vexriscv-sim/app/VexRiscvSimulation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import System.IO (putChar, hFlush, stdout)
import Text.Printf (printf)


import Utils.ProgramLoad (loadProgram)
import Utils.ProgramLoad (loadProgram, loadProgramDmem)
import Utils.Cpu (cpu)
import System.Exit (exitFailure)
import System.Directory.Internal.Prelude (exitFailure)
Expand Down Expand Up @@ -79,7 +79,7 @@ main = do

(iMem, dMem) <-
withClockResetEnable @System clockGen resetGen enableGen $
loadProgram @System elfFile
loadProgramDmem @System elfFile

let cpuOut@(unbundle -> (_circuit, writes, _iBus, _dBus)) =
withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $
Expand Down
39 changes: 24 additions & 15 deletions clash-vexriscv-sim/src/Utils/Cpu.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ import VexRiscv.JtagTcpBridge as JTag

import GHC.Stack (HasCallStack)

import Utils.ProgramLoad (Memory)
import Utils.ProgramLoad (Memory, DMemory)
import Utils.Interconnect (interconnectTwo)
import System.IO.Unsafe (unsafePerformIO)
import Text.Printf (printf)
Expand Down Expand Up @@ -45,8 +45,8 @@ Address space
cpu ::
(HasCallStack, HiddenClockResetEnable dom) =>
Maybe Integer ->
Memory dom ->
Memory dom ->
DMemory dom ->
DMemory dom ->
( Signal dom Output,
-- writes
Signal dom (Maybe (BitVector 32, BitVector 32)),
Expand All @@ -64,23 +64,32 @@ cpu jtagPort bootIMem bootDMem = (output, writes, iS2M, dS2M)
Nothing -> pure JTag.defaultIn
-- (unbundle -> (jtagIn', _debugReset)) = unsafePerformIO $ jtagTcpBridge' 7894 hasReset (jtagOut <$> output)

dM2S = dBusWbM2S <$> output
{-
00000000 - dummy area
20000000 - instruction memory
40000000 - data memory
-}

(iS2M, unbundle -> (iMemIM2S :> dMemIM2S :> Nil)) = interconnectTwo
(unBusAddr . iBusWbM2S <$> output)
((0x0000_0000, iMemIS2M) :> (0x4000_0000, dMemIS2M) :> Nil)

iM2S = unBusAddr . iBusWbM2S <$> output
(iMemIS2M, iMemDS2M) = bootIMem (mapAddr (\x -> complement 0x2000_0000 .&. x) <$> iMemIM2S) iMemDM2S

-- needed for 'writes' below
dM2S = dBusWbM2S <$> output

iS2M = bootIMem (mapAddr (\x -> -- trace (printf "I-addr = % 8X (% 8X)\n" (toInteger $ x - 0x2000_0000) (toInteger x))
x - 0x2000_0000) <$> iM2S)
(dS2M, unbundle -> (dLowerRegionM2S :> dUpperRegionM2S :> Nil)) = interconnectTwo
(unBusAddr <$> dM2S)
((0x0000_0000, dLowerRegionS2M) :> (0x4000_0000, dUpperRegionS2M) :> Nil)

dummy = dummyWb
(dLowerRegionS2M, unbundle -> (dDummyM2S :> iMemDM2S :> Nil)) = interconnectTwo
dLowerRegionM2S
((0x0000_0000, dDummyS2M) :> (0x2000_0000, iMemDS2M) :> Nil)

dummyS2M = dummy dummyM2S
bootDS2M = bootDMem bootDM2S
(dUpperRegionS2M, dMemIS2M) = bootDMem dUpperRegionM2S dMemIM2S

(dS2M, unbundle -> (dummyM2S :> bootDM2S :> Nil)) = interconnectTwo
((\x ->
-- trace (printf "DBUS %08X" (toInteger (addr x)))
x) <$> (unBusAddr <$> dM2S))
((0x0000_0000, dummyS2M) :> (0x4000_0000, bootDS2M) :> Nil)
dDummyS2M = dummyWb dDummyM2S

input =
( \iBus dBus ->
Expand Down
40 changes: 40 additions & 0 deletions clash-vexriscv-sim/src/Utils/ProgramLoad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,46 @@ type Memory dom =
Signal dom (WishboneS2M (BitVector 32))
)

type DMemory dom =
Signal dom (WishboneM2S 32 4 (BitVector 32)) ->
Signal dom (WishboneM2S 32 4 (BitVector 32)) ->
(Signal dom (WishboneS2M (BitVector 32)), Signal dom (WishboneS2M (BitVector 32)))

loadProgramDmem :: (HiddenClockResetEnable dom) => FilePath -> IO (DMemory dom, DMemory dom)
loadProgramDmem path = do
elfBytes <- BS.readFile path
let (entry, iMem, dMem) = readElfFromMemory elfBytes

assert (entry == 0x2000_0000) (pure ())

let
endianSwap dat =
L.concatMap (\[a, b, c, d] -> [d, c, b, a]) $
chunkFill 4 0 dat

-- endian swap instructions
iMemContents = endianSwap $
content iMem <> [0, 0, 0, 0, 0, 0, 0, 0]
dMemContents = endianSwap $
content dMem <> [0, 0, 0, 0, 0, 0, 0, 0]


let instrMem = dualPortStorage iMemContents
dataMem = dualPortStorage dMemContents

pure (instrMem, dataMem)
where
content :: BinaryData -> [BitVector 8]
content bin = L.map snd $ I.toAscList bin

chunkFill :: Int -> a -> [a] -> [[a]]
chunkFill _ _ [] = []
chunkFill n fill xs =
let (first0, rest) = L.splitAt n xs
first1 = first0 <> L.replicate (n - L.length first0) fill
in first1 : chunkFill n fill rest


loadProgram :: (HiddenClockResetEnable dom) => FilePath -> IO (Memory dom, Memory dom)
loadProgram path = do
elfBytes <- BS.readFile path
Expand Down
79 changes: 76 additions & 3 deletions clash-vexriscv-sim/src/Utils/Storage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,79 @@ import Protocols.Wishbone
import Debug.Trace (trace)
import Text.Printf (printf)

dualPortStorage ::
forall dom.
( KnownDomain dom,
HiddenClockResetEnable dom
) =>
[BitVector 8] ->
-- ^ contents
Signal dom (WishboneM2S 32 4 (BitVector 32)) ->
-- ^ in A
Signal dom (WishboneM2S 32 4 (BitVector 32)) ->
-- ^ in B
( Signal dom (WishboneS2M (BitVector 32))
-- ^ out A
, Signal dom (WishboneS2M (BitVector 32))
-- ^ out B
)
dualPortStorage contents portA portB = (aReply, bReply)
where
actualResult = storage contents inSignal

(port, inSignal, aReply, bReply) = go A portA portB actualResult

go currentPort (a :- inA) (b :- inB) ~(res :- actualResult)
-- neither active, just say A is current, do nothing
| not aActive && not bActive =
( A :- restPorts
, a :- restInSignal
, res :- aReplies
, emptyWishboneS2M :- bReplies
)
-- A current, A active -> do A
| currentPort == A && aActive =
( A :- restPorts
, a :- restInSignal
, res :- aReplies
, emptyWishboneS2M :- bReplies
)
-- current A, A not active but B is, do B and switch to B
| currentPort == A && not aActive && bActive =
( B :- restPorts
, b :- restInSignal
, emptyWishboneS2M :- aReplies
, res :- bReplies
)
-- current B, B active -> do B
| currentPort == B && bActive =
( B :- restPorts
, b :- restInSignal
, emptyWishboneS2M :- aReplies
, res :- bReplies
)
-- current B, B not active, but A is, do A and switch to A
| currentPort == B && not bActive && aActive =
( A :- restPorts
, a :- restInSignal
, res :- aReplies
, emptyWishboneS2M :- bReplies
)
where
aActive = strobe a && busCycle a
bActive = strobe b && busCycle b

nextPort = case (currentPort, aActive, bActive) of
(_, False, False) -> A
(A, False, True) -> B
(A, True, _) -> A
(B, _, True) -> B
(B, True, False) -> A

~(restPorts, restInSignal, aReplies, bReplies) = go nextPort inA inB actualResult

data AorB = A | B deriving (Generic, NFDataX, Eq)

storage ::
forall dom.
( KnownDomain dom,
Expand All @@ -31,7 +104,7 @@ storage contents = mealy' go (I.fromAscList $ L.zip [0..] contents)

-- Version of mealy that doesn't require NFDataX for the state.
-- This is needed because IntMap (Word8) does not implement NFDataX
mealy' fn st0 (i :- is) = o :- mealy' fn st1 is
mealy' fn st0 (i :- is) = o :- mealy' fn st1 is
where (!st1, o) = fn st0 i

go mem WishboneM2S{..}
Expand All @@ -58,7 +131,7 @@ readDataSel mem addr sel =
0b1100 -> readWord (addr + 2)
0b1111 -> readDWord addr
_ -> Nothing

where
readByte addr' = resize @_ @8 @32 <$> I.lookup (fromIntegral addr') mem
readWord addr' = do
Expand Down Expand Up @@ -93,6 +166,6 @@ writeDataSel mem addr sel val =
I.insert (fromIntegral $ addr + 1) hl $
I.insert (fromIntegral $ addr + 0) hh mem
_ -> mem

where
(hh :: BitVector 8, hl :: BitVector 8, lh :: BitVector 8, ll :: BitVector 8) = unpack val
4 changes: 2 additions & 2 deletions clash-vexriscv-sim/tests/tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import System.IO.Temp (withSystemTempFile)
import Test.Tasty
import Test.Tasty.HUnit (Assertion, testCase, (@?=))

import Utils.ProgramLoad (loadProgram)
import Utils.ProgramLoad (loadProgram, loadProgramDmem)
import Utils.Cpu (cpu)


Expand All @@ -35,7 +35,7 @@ runProgramExpect ::
Assertion
runProgramExpect act n expected = withSystemTempFile "ELF" $ \fp _ -> do
act fp
(iMem, dMem) <- withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $ loadProgram fp
(iMem, dMem) <- withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $ loadProgramDmem fp

let _all@(unbundle -> (_circuit, writes, _iBus, _dBus)) =
withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $
Expand Down
2 changes: 1 addition & 1 deletion clash-vexriscv/example-cpu/VexRiscvWithDebug.yaml
Original file line number Diff line number Diff line change
@@ -1 +1 @@
debug: !!vexriscv.DebugReport {hardwareBreakpointCount: 0}
debug: !!vexriscv.DebugReport {hardwareBreakpointCount: 5}
8 changes: 4 additions & 4 deletions clash-vexriscv/example-cpu/VexRiscvWrapped.v
Original file line number Diff line number Diff line change
Expand Up @@ -34,13 +34,13 @@ module VexRiscv (
input clk,
input reset
);
initial begin
// initial begin
// Specify the dump file name
$dumpfile("simulation_dump.vcd");
// $dumpfile("simulation_dump.vcd");

// Dump all signals to the VCD file
$dumpvars(1, VexRiscv);
end
// $dumpvars(1, VexRiscv);
// end

reg reset_cpu;
wire reqCpuReset;
Expand Down
2 changes: 1 addition & 1 deletion clash-vexriscv/src/ffi/impl.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -251,7 +251,7 @@ void vexr_jtag_bridge_step(vexr_jtag_bridge_data *d, const JTAG_OUTPUT *output,
}
}
}
d->timer = 27; // 3; value used by VexRiscv regression test
d->timer = 3; // 3; value used by VexRiscv regression test
}

void vexr_jtag_bridge_shutdown(vexr_jtag_bridge_data *bridge_data)
Expand Down
14 changes: 9 additions & 5 deletions debug-test/src/main.rs
Original file line number Diff line number Diff line change
Expand Up @@ -37,11 +37,15 @@ fn main() -> ! {
print(&s);
}

print("wheeeey!\n");

unsafe {
//riscv::asm::ebreak();
}
print("aaaaa!\n");
print("bbbbb!\n");
print("ccccc!\n");
print("ddddd!\n");
print("eeeee!\n");

// unsafe {
// riscv::asm::ebreak();
// }
}
}

Expand Down

0 comments on commit f0d1150

Please sign in to comment.