From d0e002d92d6db9318b683a361f08af8e7d6ead8d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?S=C3=B6ren=20Tempel?= Date: Tue, 16 Apr 2024 06:20:37 +0200 Subject: [PATCH] Add some documentation for LibRISCV.Effects.Decoding --- .../Effects/Decoding/Default/Interpreter.hs | 14 ++++++++++++-- lib/LibRISCV/Effects/Decoding/Language.hs | 16 +++++++++++++--- 2 files changed, 25 insertions(+), 5 deletions(-) diff --git a/lib/LibRISCV/Effects/Decoding/Default/Interpreter.hs b/lib/LibRISCV/Effects/Decoding/Default/Interpreter.hs index 4cc0391..b9a59df 100644 --- a/lib/LibRISCV/Effects/Decoding/Default/Interpreter.hs +++ b/lib/LibRISCV/Effects/Decoding/Default/Interpreter.hs @@ -2,7 +2,13 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} + +-- | Provides the default (concrete) interpretation for the decoding effect. This +-- implementation assumes that the 'Decodable' type class can be implemented for +-- the underlying type parameter, that is, it must be possible to convert the +-- type to a fixed-width concrete integer. module LibRISCV.Effects.Decoding.Default.Interpreter where + import LibRISCV.Effects.Decoding.Language ( Decoding(..) ) import Data.Data (Proxy(..)) import Control.Monad.IO.Class (MonadIO (liftIO)) @@ -13,19 +19,23 @@ import Control.Monad.Freer ( type (~>) ) import LibRISCV.Internal.Decoder.Opcodes (decode) import LibRISCV.Internal.Decoder.Instruction (mkRd, mkRs1, mkRs2, immI, immS, immB, immU, immJ, mkShamt) - +-- | Decoder state used to implement the stateful 'SetInstr' constructor of the 'Decoding' effect. type DecoderState = IORef Word32 +-- | Type class used to perform conversion from/to a fixed-with concrete integer. class Decodable a where fromWord :: Word32 -> a + -- ^ Convert from a fixed-with integer to the underlying value type of the interpreter. toWord :: a -> Word32 + -- ^ Convert from the underlying value type to a fixed-with integer. instance Decodable BV where fromWord = bitVec 32 toWord = fromIntegral +-- | Concrete implementation of the decoding effect. defaultDecoding :: forall v m. (Decodable v, MonadIO m) => DecoderState -> Decoding v ~> m -defaultDecoding instRef = +defaultDecoding instRef = let decodeAndConvert f = fmap (fromWord . f) . readIORef in liftIO . \case diff --git a/lib/LibRISCV/Effects/Decoding/Language.hs b/lib/LibRISCV/Effects/Decoding/Language.hs index 55a420e..fcd96ec 100644 --- a/lib/LibRISCV/Effects/Decoding/Language.hs +++ b/lib/LibRISCV/Effects/Decoding/Language.hs @@ -1,13 +1,20 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE FlexibleContexts #-} + +-- | Implements an effect for instruction decoding. Specifically, the effect +-- is only used to describe obtaining of instruction operands. The instruction +-- opcode is determined seperatly using code generated from the existing +-- tool. The decoding +-- effect is stateful and operates on a current instruction word specified via +-- 'setInstr', thereby avoiding the need to pass the current instruction word +-- to every decoding function. module LibRISCV.Effects.Decoding.Language where import Data.Data (Proxy) import LibRISCV.Internal.Decoder.Opcodes (InstructionType) import Control.Monad.Freer.TH (makeEffect) - data Decoding v r where DecodeRS1 :: Decoding v v DecodeRS2 :: Decoding v v @@ -19,7 +26,10 @@ data Decoding v r where DecodeImmJ :: Decoding v v DecodeShamt :: Decoding v v - SetInstr :: v -> Decoding v () + SetInstr :: v -> Decoding v () + -- TODO: WithInstrType is only used to determine which Haskell module + -- provides the semantics for a given instruction. Can we eliminate + -- the need to do this somehow? WithInstrType :: Proxy v -> (InstructionType -> b) -> Decoding v b -makeEffect ''Decoding \ No newline at end of file +makeEffect ''Decoding