56 lines
1.6 KiB
Haskell
56 lines
1.6 KiB
Haskell
{-# LANGUAGE DataKinds #-}
|
|
{-# LANGUAGE NumericUnderscores #-}
|
|
|
|
module Fetch(
|
|
fetchInstruction,
|
|
fetchInstruction1,
|
|
FetchResult(..),
|
|
FetchResult1(..)) where
|
|
|
|
import Clash.Prelude
|
|
import Types(Mem, Addr, Insn)
|
|
import Bus(ReadResponse, WriteResponse, read)
|
|
import Bus(Peripherals(..))
|
|
import BusTypes(
|
|
ReadRequest(..),
|
|
TransactionSize(..),
|
|
BusVal(..),
|
|
BusError(..))
|
|
import Exceptions(Exception(..), exceptionCode, isSynchronousException)
|
|
|
|
import GHC.IO (IO)
|
|
import GHC.Base (Applicative(pure))
|
|
|
|
data FetchResult = Instruction Insn
|
|
| Misaligned Addr
|
|
|
|
data FetchResult1 = Instruction1 Insn
|
|
| InstructionException Exception
|
|
|
|
fetchInstruction :: KnownNat n => Mem n -> Addr -> FetchResult
|
|
fetchInstruction mem addr =
|
|
let
|
|
isWordAligned = addr .&. 3 == 0
|
|
addrWordAligned = addr `shiftR` 2
|
|
insn = mem !! addrWordAligned
|
|
-- TODO : check if instruction is word aligned and create type
|
|
-- to capture if its not.
|
|
in
|
|
case isWordAligned of
|
|
True -> Instruction insn
|
|
False -> Misaligned addr
|
|
|
|
fetchInstruction1 :: Peripherals -> Addr -> IO FetchResult1
|
|
fetchInstruction1 peripherals addr =
|
|
do
|
|
readReasponse <-Bus.read (BusTypes.Request addr BusTypes.SizeFullWord) peripherals
|
|
case readReasponse of
|
|
Right (BusFullWord insn) ->
|
|
pure $ Instruction1 insn
|
|
Left UnAligned ->
|
|
pure $ InstructionException InstructionAddressMisaligned
|
|
Left UnMapped ->
|
|
pure $ InstructionException InstructionAccessFault
|
|
Right _ ->
|
|
pure $ InstructionException InstructionAccessFault
|