more progress on UART read
This commit is contained in:
parent
7265728932
commit
8d5cd862ab
|
@ -6,6 +6,7 @@
|
||||||
#include <stdbool.h>
|
#include <stdbool.h>
|
||||||
|
|
||||||
static volatile bool ctrl_c_received = false;
|
static volatile bool ctrl_c_received = false;
|
||||||
|
static char last_char = '\0';
|
||||||
|
|
||||||
void sigint_handler(int sig_num) {
|
void sigint_handler(int sig_num) {
|
||||||
ctrl_c_received = true;
|
ctrl_c_received = true;
|
||||||
|
@ -37,8 +38,10 @@ void restore_terminal() {
|
||||||
}
|
}
|
||||||
|
|
||||||
char get_char_from_terminal() {
|
char get_char_from_terminal() {
|
||||||
char c = getchar();
|
if (is_char_available()) {
|
||||||
return c;
|
last_char = getchar(); // Update last_char if new character is available
|
||||||
|
}
|
||||||
|
return last_char; // Return the last available character (or '\0' initially)
|
||||||
}
|
}
|
||||||
|
|
||||||
void write_char_to_terminal(char chr) {
|
void write_char_to_terminal(char chr) {
|
||||||
|
|
14
hs/Bus.hs
14
hs/Bus.hs
|
@ -30,6 +30,8 @@ alignCheck addr SizeQuadWord = addr `mod` 16 == 0
|
||||||
(ramStart, ramEnd) = (0x80000000 :: Addr, ramStart + (bytesInRam - 1))
|
(ramStart, ramEnd) = (0x80000000 :: Addr, ramStart + (bytesInRam - 1))
|
||||||
(uartStart, uartEnd) = (0x10000000 :: Addr, uartStart + 7)
|
(uartStart, uartEnd) = (0x10000000 :: Addr, uartStart + 7)
|
||||||
|
|
||||||
|
-- reading/writing from/to UART is implemented as reading/writing
|
||||||
|
-- from/to STDIO, so we need IO.
|
||||||
read :: Request -> Peripherals -> IO ReadResponse
|
read :: Request -> Peripherals -> IO ReadResponse
|
||||||
read (Request addr size) peripherals
|
read (Request addr size) peripherals
|
||||||
| not (alignCheck addr size) = return $ ReadResponse $ Error UnAligned
|
| not (alignCheck addr size) = return $ ReadResponse $ Error UnAligned
|
||||||
|
@ -40,15 +42,3 @@ read (Request addr size) peripherals
|
||||||
ramAddrNoOffset = addr - ramStart
|
ramAddrNoOffset = addr - ramStart
|
||||||
ramAddr :: RamAddr
|
ramAddr :: RamAddr
|
||||||
ramAddr = resize ramAddrNoOffset
|
ramAddr = resize ramAddrNoOffset
|
||||||
|
|
||||||
-- | (addr > ramStart) && (addr < ramEnd) = return $ ReadResponse $ Peripherals.Ram.read addr size (ram peripherals)
|
|
||||||
-- | addr >= numBytesInRam = ReadError UnMapped
|
|
||||||
-- case size of
|
|
||||||
-- SizeByte -> BusByte $ fromIntegral $ extractByte (ramRead 0)
|
|
||||||
-- SizeHalfWord -> BusHalfWord $ fromIntegral $ (ramRead 0 `shiftL` 8) .|. ramRead 1
|
|
||||||
-- SizeWord -> BusWord $ fromIntegral $ concatReads [0..3]
|
|
||||||
-- SizeDoubleWord -> BusDoubleWord $ fromIntegral $ concatReads [0..7]
|
|
||||||
-- SizeQuadWord -> BusQuadWord $ fromIntegral $ concatReads [0..15]
|
|
||||||
-- where
|
|
||||||
-- ramRead offset = Peripherals.Ram.read (ram peripherals) (fromIntegral (addr + offset))
|
|
||||||
-- concatReads offsets = foldl (\acc o -> (acc `shiftL` 8) .|. ramRead o) 0 offsets
|
|
||||||
|
|
|
@ -6,6 +6,11 @@ module Fetch(
|
||||||
FetchResult(..)) where
|
FetchResult(..)) where
|
||||||
|
|
||||||
import Clash.Prelude
|
import Clash.Prelude
|
||||||
|
( Eq((==)),
|
||||||
|
KnownNat,
|
||||||
|
Bool(False, True),
|
||||||
|
(!!),
|
||||||
|
Bits(shiftR, (.&.)) )
|
||||||
import Types(Mem, Addr, Insn)
|
import Types(Mem, Addr, Insn)
|
||||||
import Util(endianSwapWord)
|
import Util(endianSwapWord)
|
||||||
|
|
||||||
|
|
|
@ -21,10 +21,7 @@ import qualified Clash.Sized.Vector as Vec
|
||||||
import Types(Addr,
|
import Types(Addr,
|
||||||
Byte, HalfWord, FullWord, DoubleWord, QuadWord)
|
Byte, HalfWord, FullWord, DoubleWord, QuadWord)
|
||||||
import BusTypes(
|
import BusTypes(
|
||||||
BusError(..),
|
|
||||||
TransactionSize(..),
|
TransactionSize(..),
|
||||||
Request(..),
|
|
||||||
BusResponse(..),
|
|
||||||
BusVal(..),
|
BusVal(..),
|
||||||
ReadResponse(..),
|
ReadResponse(..),
|
||||||
WriteResponse(..)
|
WriteResponse(..)
|
||||||
|
@ -129,6 +126,3 @@ populateVectorFromInt32 ls v = Vec.fromList adjustedLs
|
||||||
adjustedLs = fromIntegral <$> adjustLength vecLen ls
|
adjustedLs = fromIntegral <$> adjustLength vecLen ls
|
||||||
adjustLength :: Int -> [Int32] -> [Int32]
|
adjustLength :: Int -> [Int32] -> [Int32]
|
||||||
adjustLength n xs = P.take n (xs P.++ P.repeat 0)
|
adjustLength n xs = P.take n (xs P.++ P.repeat 0)
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -3,7 +3,7 @@ module Peripherals.Setup (
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
import Peripherals.UartCFFI(initTerminal, restoreTerminal)
|
import Peripherals.UartCFFI(initTerminal)
|
||||||
import Peripherals.Ram (initRamFromFile, Ram)
|
import Peripherals.Ram (initRamFromFile, Ram)
|
||||||
import Control.Exception (try)
|
import Control.Exception (try)
|
||||||
import System.IO.Error (ioeGetErrorString)
|
import System.IO.Error (ioeGetErrorString)
|
||||||
|
|
61
hs/Peripherals/Uart.hs
Normal file
61
hs/Peripherals/Uart.hs
Normal file
|
@ -0,0 +1,61 @@
|
||||||
|
module Peripherals.Uart (read) where
|
||||||
|
|
||||||
|
import Clash.Prelude hiding (read)
|
||||||
|
import Types (Byte)
|
||||||
|
import Data.Char (ord)
|
||||||
|
|
||||||
|
import Peripherals.UartCFFI (
|
||||||
|
initTerminal,
|
||||||
|
restoreTerminal,
|
||||||
|
getCharFromTerminal,
|
||||||
|
writeCharToTerminal,
|
||||||
|
isCharAvailable,
|
||||||
|
setupSigintHandler,
|
||||||
|
wasCtrlCReceived
|
||||||
|
)
|
||||||
|
|
||||||
|
import BusTypes (
|
||||||
|
TransactionSize(..),
|
||||||
|
BusVal(..),
|
||||||
|
ReadResponse(..),
|
||||||
|
WriteResponse(..)
|
||||||
|
)
|
||||||
|
|
||||||
|
-- based on a 16550 UART which has an address space of 8 bytes
|
||||||
|
type UartAddr = Unsigned 3
|
||||||
|
|
||||||
|
-- Receiver Buffer Register address (commonly 0x0 for 16550 UART)
|
||||||
|
rbrAddr :: UartAddr
|
||||||
|
rbrAddr = 0x0
|
||||||
|
|
||||||
|
-- Line Status Register address
|
||||||
|
lsrAddr :: UartAddr
|
||||||
|
lsrAddr = 0x5
|
||||||
|
|
||||||
|
-- Helper function to convert Byte to BusVal based on TransactionSize
|
||||||
|
busValFromByte :: TransactionSize -> Byte -> BusVal
|
||||||
|
busValFromByte size val = case size of
|
||||||
|
SizeByte -> BusByte val
|
||||||
|
SizeHalfWord -> BusHalfWord (resize val)
|
||||||
|
SizeFullWord -> BusFullWord (resize val)
|
||||||
|
SizeDoubleWord -> BusDoubleWord (resize val)
|
||||||
|
SizeQuadWord -> BusQuadWord (resize val)
|
||||||
|
|
||||||
|
-- Reads a character from the terminal (RBR equivalent)
|
||||||
|
buildRBR :: IO Byte
|
||||||
|
buildRBR = do
|
||||||
|
c <- getCharFromTerminal
|
||||||
|
return $ fromIntegral (ord c) -- Convert Char to Byte
|
||||||
|
|
||||||
|
-- Reads the Line Status Register (LSR) to check character availability
|
||||||
|
buildLSR :: IO Byte
|
||||||
|
buildLSR = do
|
||||||
|
char_available <- isCharAvailable
|
||||||
|
return $ fromIntegral char_available
|
||||||
|
|
||||||
|
-- Updated 'read' function to handle RBR and LSR reads
|
||||||
|
read :: TransactionSize -> UartAddr -> IO BusVal
|
||||||
|
read size addr
|
||||||
|
| addr == rbrAddr = busValFromByte size <$> buildRBR
|
||||||
|
| addr == lsrAddr = busValFromByte size <$> buildLSR
|
||||||
|
| otherwise = return $ busValFromByte size 0x00
|
|
@ -8,7 +8,6 @@ module Simulation(Args(..), simulation, Simulation(..)) where
|
||||||
import qualified Prelude as P
|
import qualified Prelude as P
|
||||||
import Peripherals.Setup(setupPeripherals, InitializedPeripherals(..))
|
import Peripherals.Setup(setupPeripherals, InitializedPeripherals(..))
|
||||||
import Peripherals.Teardown(teardownPeripherals)
|
import Peripherals.Teardown(teardownPeripherals)
|
||||||
import Text.Printf (printf)
|
|
||||||
import Clash.Prelude
|
import Clash.Prelude
|
||||||
import Machine(
|
import Machine(
|
||||||
Machine(..),
|
Machine(..),
|
||||||
|
@ -17,12 +16,8 @@ import Machine(
|
||||||
machineInit, RISCVCPU (RISCVCPU))
|
machineInit, RISCVCPU (RISCVCPU))
|
||||||
import Fetch(fetchInstruction, FetchResult (Instruction, Misaligned))
|
import Fetch(fetchInstruction, FetchResult (Instruction, Misaligned))
|
||||||
import Isa.Decode(decode)
|
import Isa.Decode(decode)
|
||||||
import Isa.Forms(Opcode(..))
|
|
||||||
import Peripherals.UartCFFI(writeCharToTerminal)
|
|
||||||
import Control.Concurrent (threadDelay)
|
|
||||||
|
|
||||||
import Debug.Trace
|
import Debug.Trace
|
||||||
import Types (Mem, Addr)
|
|
||||||
|
|
||||||
data Args = Args {
|
data Args = Args {
|
||||||
firmware :: FilePath
|
firmware :: FilePath
|
||||||
|
@ -64,9 +59,6 @@ simulationLoop :: Int -> Machine -> IO [Machine]
|
||||||
simulationLoop 0 state = return [state]
|
simulationLoop 0 state = return [state]
|
||||||
simulationLoop n state = do
|
simulationLoop n state = do
|
||||||
let newState = machine' state
|
let newState = machine' state
|
||||||
-- later use this to display writes from machine to its
|
|
||||||
-- uart peripheral
|
|
||||||
-- writeCharToTerminal 'a'
|
|
||||||
rest <- simulationLoop (n - 1) newState
|
rest <- simulationLoop (n - 1) newState
|
||||||
return (state : rest)
|
return (state : rest)
|
||||||
|
|
||||||
|
|
|
@ -90,6 +90,7 @@ library
|
||||||
Isa.Decode,
|
Isa.Decode,
|
||||||
Isa.Forms,
|
Isa.Forms,
|
||||||
Peripherals.Ram,
|
Peripherals.Ram,
|
||||||
|
Peripherals.Uart,
|
||||||
Peripherals.UartCFFI,
|
Peripherals.UartCFFI,
|
||||||
Peripherals.Setup,
|
Peripherals.Setup,
|
||||||
Peripherals.Teardown,
|
Peripherals.Teardown,
|
||||||
|
|
Loading…
Reference in a new issue