{-# LANGUAGE DataKinds #-} {-# LANGUAGE NumericUnderscores #-} module Fetch( fetchInstruction, debugInsn, FetchResult(..), ) where import Clash.Prelude import qualified Prelude as P import Types(Addr, Insn) import Bus(read) import Bus(Peripherals(..)) import BusTypes( ReadRequest(..), TransactionSize(..), BusVal(..), BusError(..)) import Exceptions(Exception(..)) data FetchResult = Instruction Insn | InstructionException Exception deriving (Generic, Show, Eq, NFDataX) fetchInstruction :: Peripherals -> Addr -> IO FetchResult fetchInstruction peripherals addr = do readReasponse <-Bus.read (BusTypes.Request addr BusTypes.SizeFullWord) peripherals case readReasponse of Right (BusFullWord insn) -> pure $ Instruction insn Left UnAligned -> pure $ InstructionException (InstructionAddressMisaligned addr) Left UnMapped -> pure $ InstructionException (InstructionAccessFault addr) Right _ -> pure $ InstructionException (InstructionAccessFault addr) debugInsn :: FetchResult -> String debugInsn fetchResult = case fetchResult of Instruction insn -> "Instruction raw binary | " P.++ binaryInsn P.++ " (" P.++ show insn P.++ ")" where binaryInsn = show (bitCoerce insn :: BitVector 32) InstructionException e -> show e