Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
martijnbastiaan committed Mar 4, 2024
1 parent 03c7e5e commit e54a68a
Show file tree
Hide file tree
Showing 27 changed files with 2,098,160 additions and 512 deletions.
74 changes: 74 additions & 0 deletions clash-vexriscv-sim/app/ElfToHex.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,74 @@
-- | Convert an ELF file to a set of @.mem@ files, suitable for use with
-- Verilog simulators. Use in combination with @readmemh@ in Verilog.
module Main where

import Prelude

import Control.Concurrent.Async (mapConcurrently_)
import Control.Monad (forM_)
import Data.IntMap (IntMap, findWithDefault)
import Data.Tuple.Extra (uncurry3)
import System.Environment (getArgs)
import System.IO (withFile, IOMode(WriteMode), hPutStrLn)
import Text.Printf (printf)
import Text.Read (readMaybe)
import Utils.ReadElf (readElfFromMemory)

import qualified Data.ByteString as BS
import qualified Clash.Prelude as C

-- | Like 'zipWithM_', but execute concurrently
zipWithConcurrently_ :: (a -> b -> IO ()) -> [a] -> [b] -> IO ()
zipWithConcurrently_ f xs ys = mapConcurrently_ (uncurry f) (zip xs ys)

-- | Like 'zipWith3M_', but execute concurrently
zipWith3Concurrently_ :: (a -> b -> c -> IO ()) -> [a] -> [b] -> [c] -> IO ()
zipWith3Concurrently_ f xs ys zs = mapConcurrently_ (uncurry3 f) (zip3 xs ys zs)

-- | Convenience function to get data from a memory map. If a memory address is
-- not found, return 0.
getData :: Num a => IntMap a -> Int -> a
getData mem addr = findWithDefault 0 addr mem

-- | Generate the addresses for the four memory banks, given the total size in
-- bytes, and the start address.
getAddrs :: Int -> Int -> ([Int], [Int], [Int], [Int])
getAddrs size start =
( [start + 0, start + 4 .. start + size - 1]
, [start + 1, start + 5 .. start + size - 1]
, [start + 2, start + 6 .. start + size - 1]
, [start + 3, start + 7 .. start + size - 1] )

-- | Write a single @.mem@ file
writeByteMem :: IntMap (C.BitVector 8) -> FilePath -> [Int] -> IO ()
writeByteMem mem path addrs = do
putStrLn $ "Writing " <> path
withFile path WriteMode $ \h ->
forM_ addrs $ \addr -> do
hPutStrLn h (toHex (getData mem addr))

-- | Write four @.mem@ files
writeMem :: Int -> IntMap (C.BitVector 8) -> FilePath -> Int -> IO ()
writeMem size mem prefix start = do
let (addrs0, addrs1, addrs2, addrs3) = getAddrs size start

zipWithConcurrently_
(writeByteMem mem)
[prefix <> show n <> ".mem" | n <- [(0::Int)..]]
[addrs0, addrs1, addrs2, addrs3]

-- | Print a byte as a hex string of the form 0x00.
toHex :: C.BitVector 8 -> String
toHex = printf "0x%02x" . toInteger

main :: IO ()
main = do
[sizeStr, elfFile] <- getArgs
let Just size = readMaybe @Int sizeStr
(_addr, iMem, dMem) <- readElfFromMemory <$> BS.readFile elfFile

zipWith3Concurrently_
(writeMem size)
[iMem, dMem]
["imem", "dmem"]
[0x20000000, 0x40000000]
4 changes: 2 additions & 2 deletions clash-vexriscv-sim/app/HdlTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,10 +10,10 @@ import VexRiscv
circuit ::
"CLK" ::: Clock System ->
"RST" ::: Reset System ->
"INPUT" ::: Signal System Input ->
"CPU_COMB_INPUT" ::: Signal System CpuIn ->
"JTAG_IN_" ::: Signal System JtagIn ->
"" :::
( "OUTPUT" ::: Signal System Output
( "CPU_OUTPUT" ::: Signal System CpuOut
, "JTAG_OUT_" ::: Signal System JtagOut)
circuit clk rst input jtagIn =
vexRiscv clk rst input jtagIn
Expand Down
29 changes: 18 additions & 11 deletions clash-vexriscv-sim/app/VexRiscvSimulation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,13 +10,13 @@
import Clash.Prelude

import Protocols.Wishbone
import VexRiscv (Output(iBusWbM2S, dBusWbM2S))
import VexRiscv (CpuOut(iBusWbM2S, dBusWbM2S))

import qualified Data.List as L

import Control.Monad (forM_, when)
import Data.Char (chr)
import Data.Maybe (catMaybes)
import Data.Maybe (catMaybes, fromMaybe)
import System.Environment (getArgs)
import System.IO (putChar, hFlush, stdout)
import Text.Printf (printf)
Expand All @@ -25,7 +25,6 @@ import Text.Printf (printf)
import Utils.ProgramLoad (loadProgram)
import Utils.Cpu (cpu)
import System.Exit (exitFailure)
import System.Directory.Internal.Prelude (exitFailure)

--------------------------------------
--
Expand Down Expand Up @@ -84,25 +83,29 @@ main = do
let cpuOut@(unbundle -> (_circuit, writes, _iBus, _dBus)) =
withClockResetEnable @System clockGen (resetGenN (SNat @2)) enableGen $
let (circ, writes1, iBus, dBus) = cpu (Just 7894) iMem dMem
dBus' = register emptyWishboneS2M dBus
dBus' = register Nothing dBus
in bundle (circ, writes1, iBus, dBus')

case debugConfig of
RunCharacterDevice ->
forM_ (sample_lazy @System (bundle (register @System (unpack 0) cpuOut, cpuOut))) $
\((out, write, dS2M, iS2M), (out1, _write, _dS2M, _iS2M)) -> do
\((_out, write, dS2M0, iS2M0), (out1, _write, _dS2M, _iS2M)) -> do
let
iS2M = fromMaybe emptyWishboneS2M iS2M0
dS2M = fromMaybe emptyWishboneS2M dS2M0

when (err dS2M) $ do
let dBusM2S = dBusWbM2S out1
let dAddr = toInteger (addr dBusM2S) -- `shiftL` 2
printf "D-bus ERR reply % 8X (% 8X)\n" (toInteger $ dAddr `shiftL` 2) (toInteger dAddr)
-- exitFailure
exitFailure

when (err iS2M) $ do
let iBusM2S = iBusWbM2S out1
let iAddr = toInteger (addr iBusM2S) -- `shiftL` 2
printf "I-bus ERR reply % 8X (% 8X)\n" (toInteger $ iAddr `shiftL` 2) (toInteger iAddr)
printf "%s\n" (showX iBusM2S)
-- exitFailure
exitFailure

case write of
Just (address, value) | address == 0x0000_1000 -> do
Expand All @@ -119,10 +122,14 @@ main = do
let sampled = case interesting of
Nothing -> L.zip [0 ..] $ sample_lazy @System cpuOut
Just nInteresting ->
let total = initCycles + uninteresting + nInteresting in L.zip [0 ..] $ L.take total $ sample_lazy @System cpuOut

forM_ sampled $ \(i, (out, _, iBusS2M, dBusS2M)) -> do
let doPrint = i >= skipTotal
let total = initCycles + uninteresting + nInteresting in
L.zip [0 ..] $ L.take total $ sample_lazy @System cpuOut

forM_ sampled $ \(i, (out, _, iBusS2M0, dBusS2M0)) -> do
let
iBusS2M = fromMaybe emptyWishboneS2M iBusS2M0
dBusS2M = fromMaybe emptyWishboneS2M dBusS2M0
doPrint = i >= skipTotal

-- I-bus interactions

Expand Down
13 changes: 13 additions & 0 deletions clash-vexriscv-sim/clash-vexriscv-sim.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,19 @@ executable hdl-test
clash-vexriscv,
clash-vexriscv-sim,

executable elf-to-hex
import: common-options
main-is: ElfToHex.hs
hs-source-dirs: app
default-language: Haskell2010
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
async,
base,
bytestring,
clash-vexriscv-sim,
extra,

executable clash-vexriscv-bin
import: common-options
main-is: VexRiscvSimulation.hs
Expand Down
36 changes: 16 additions & 20 deletions clash-vexriscv-sim/src/Utils/Cpu.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,9 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE RecordWildCards #-}

{-# OPTIONS_GHC -Wno-orphans #-}

module Utils.Cpu where

import Clash.Prelude
Expand All @@ -18,20 +21,6 @@ import GHC.Stack (HasCallStack)

import Utils.ProgramLoad (Memory)
import Utils.Interconnect (interconnectTwo)
import System.IO.Unsafe (unsafePerformIO)
import Text.Printf (printf)
import Debug.Trace (trace)

emptyInput :: Input
emptyInput =
Input
{ timerInterrupt = low,
externalInterrupt = low,
softwareInterrupt = low,
iBusWbS2M = (emptyWishboneS2M @(BitVector 32)) {readData = 0},
dBusWbS2M = (emptyWishboneS2M @(BitVector 32)) {readData = 0}
}


createDomain vXilinxSystem{vName="Basic50", vPeriod= hzToPeriod 50_000_000}

Expand All @@ -47,26 +36,33 @@ cpu ::
Maybe Integer ->
Memory dom ->
Memory dom ->
( Signal dom Output,
( Signal dom CpuOut,
-- writes
Signal dom (Maybe (BitVector 32, BitVector 32)),
-- iBus responses
Signal dom (WishboneS2M (BitVector 32)),
Signal dom (Maybe (WishboneS2M (BitVector 32))),
-- dBus responses
Signal dom (WishboneS2M (BitVector 32))
Signal dom (Maybe (WishboneS2M (BitVector 32)))
)
cpu jtagPort bootIMem bootDMem =
( output
, writes
, mux validI (Just <$> iS2M) (pure Nothing)
, mux validD (Just <$> dS2M) (pure Nothing)
)
cpu jtagPort bootIMem bootDMem = (output, writes, iS2M, dS2M)
where
(output, jtagOut) = vexRiscv hasClock hasReset input (JTag.defaultIn :- jtagIn)
(output, jtagOut) = vexRiscv hasClock hasReset input jtagIn

jtagIn = case jtagPort of
Just port -> vexrJtagBridge (fromInteger port) jtagOut
Nothing -> pure JTag.defaultIn
-- (unbundle -> (jtagIn', _debugReset)) = unsafePerformIO $ jtagTcpBridge' 7894 hasReset (jtagOut <$> output)

dM2S = dBusWbM2S <$> output
validD = fmap busCycle dM2S .&&. fmap strobe dM2S

iM2S = unBusAddr . iBusWbM2S <$> output
validI = fmap busCycle iM2S .&&. fmap strobe iM2S

iS2M = bootIMem (mapAddr (\x -> -- trace (printf "I-addr = % 8X (% 8X)\n" (toInteger $ x - 0x2000_0000) (toInteger x))
x - 0x2000_0000) <$> iM2S)
Expand All @@ -84,7 +80,7 @@ cpu jtagPort bootIMem bootDMem = (output, writes, iS2M, dS2M)

input =
( \iBus dBus ->
Input
CpuIn
{ timerInterrupt = low,
externalInterrupt = low,
softwareInterrupt = low,
Expand Down
Loading

0 comments on commit e54a68a

Please sign in to comment.