42 lines
1.1 KiB
Haskell
42 lines
1.1 KiB
Haskell
{-# LANGUAGE DataKinds #-}
|
|
{-# LANGUAGE NumericUnderscores #-}
|
|
|
|
module Fetch(
|
|
fetchInstruction,
|
|
FetchResult(..)) where
|
|
|
|
import Clash.Prelude
|
|
( Eq((==)),
|
|
KnownNat,
|
|
Bool(False, True),
|
|
(!!),
|
|
Bits(shiftR, (.&.)) )
|
|
import Types(Mem, Addr, Insn)
|
|
import Util(endianSwapWord)
|
|
import Bus(ReadResponse, WriteResponse, read)
|
|
import Bus(Peripherals(..))
|
|
import BusTypes(ReadRequest(..), TransactionSize(..))
|
|
|
|
import GHC.IO (IO)
|
|
import GHC.Base (Applicative(pure))
|
|
|
|
data FetchResult = Instruction Insn
|
|
| Misaligned Addr
|
|
|
|
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 ReadResponse
|
|
fetchInstruction1 peripherals addr =
|
|
read (BusTypes.Request addr BusTypes.SizeFullWord) peripherals
|