diff options
author | Josh Rahm <joshuarahm@gmail.com> | 2024-10-03 18:23:50 -0600 |
---|---|---|
committer | Josh Rahm <joshuarahm@gmail.com> | 2024-10-03 18:23:50 -0600 |
commit | 407e41489cc22fbf0518fd370530f8857b8c3ed0 (patch) | |
tree | 8c5f3fceb7c9e083033e06c818556eba1dcf9a06 /src/Language/Fiddle/Compiler/ConsistencyCheck.hs | |
parent | 72eeba5fd6178409b4aab5eb8dbfaf4460f6841c (diff) | |
download | fiddle-407e41489cc22fbf0518fd370530f8857b8c3ed0.tar.gz fiddle-407e41489cc22fbf0518fd370530f8857b8c3ed0.tar.bz2 fiddle-407e41489cc22fbf0518fd370530f8857b8c3ed0.zip |
Clean up warnings and remove unused files.
Diffstat (limited to 'src/Language/Fiddle/Compiler/ConsistencyCheck.hs')
-rw-r--r-- | src/Language/Fiddle/Compiler/ConsistencyCheck.hs | 42 |
1 files changed, 18 insertions, 24 deletions
diff --git a/src/Language/Fiddle/Compiler/ConsistencyCheck.hs b/src/Language/Fiddle/Compiler/ConsistencyCheck.hs index 79ac9e7..3bdae4a 100644 --- a/src/Language/Fiddle/Compiler/ConsistencyCheck.hs +++ b/src/Language/Fiddle/Compiler/ConsistencyCheck.hs @@ -11,36 +11,29 @@ module Language.Fiddle.Compiler.ConsistencyCheck ) where -import Control.Monad (forM, forM_, unless, when) -import Control.Monad.Identity (Identity (Identity)) +import Control.Monad (forM_, unless, when) import Control.Monad.RWS (MonadState (get, put), MonadWriter (tell), gets, modify') -import Data.Foldable (Foldable (toList), foldlM) +import Data.Foldable (foldlM) import Data.Functor.Identity -import qualified Data.IntMap as IntMap -import Data.Kind (Type) -import Data.List (inits, intercalate) -import Data.List.NonEmpty (NonEmpty (..)) -import qualified Data.List.NonEmpty as NonEmpty -import Data.Map (Map) -import qualified Data.Map as Map -import Data.Maybe (fromMaybe, mapMaybe) -import qualified Data.Set as Set -import qualified Data.Text as Text -import Data.Void +import Data.List (intercalate) +import Data.Maybe (mapMaybe) import Data.Word (Word32) import GHC.TypeError as TypeError -import GHC.TypeLits import Language.Fiddle.Ast import Language.Fiddle.Compiler import Language.Fiddle.Internal.Scopes import Language.Fiddle.Internal.UnitInterface as UnitInterface import Language.Fiddle.Types (Comment (DocComment), Commented (Commented, unCommented), SourceSpan) -import Text.Printf (printf) import Prelude hiding (unzip) +import Text.Printf (printf) + +import qualified Data.IntMap as IntMap +import qualified Data.List.NonEmpty as NonEmpty +import qualified Data.Text as Text data GlobalState = GlobalState { globalScope :: Scope String (Either SizeBits SizeBytes), - fileDependencies :: [FilePath], + _fileDependencies :: [FilePath], unitInterface :: UnitInterface } @@ -158,7 +151,7 @@ instance AdvanceStage CurrentStage ObjTypeBody where deriving instance AdvanceStage CurrentStage FiddleDecl instance AdvanceStage CurrentStage (Directed FiddleDecl) where - modifyState (Directed directives t _) s = case t of + modifyState (Directed _ t _) s = case t of (BitsDecl _ id typ annotation) -> do typeSize <- getTypeSize typ insertTypeSize annotation s id typeSize @@ -345,9 +338,6 @@ objTypeBodyToStage3 st (ObjTypeBody bodyType decls a) startOff = do ) _ -> return () fUnzip xs = (fst <$> xs, snd <$> xs) - pushApply :: Maybe (a, b) -> (Maybe a, Maybe b) - pushApply (Just (a, b)) = (Just a, Just b) - pushApply Nothing = (Nothing, Nothing) registerBodyToStage3 :: LocalState -> @@ -531,6 +521,7 @@ lookupTypeSize (LocalState scopePath) (Name idents a) = do (unCommented a) ] compilationFailure + _ -> compilationFailure getTypeSize :: BitType CurrentStage I Annot -> Compile s SizeBits getTypeSize (RawBits expr _) = fromIntegral <$> exprToSize expr @@ -581,9 +572,12 @@ getTypeSize (EnumBitType expr (Identity (EnumBody constants _)) ann) = do diagnosticError :: String -> Annot -> Compile a () diagnosticError str a = tell [Diagnostic Error str (unCommented a)] -diagnosticInfo :: String -> Annot -> Compile a () -diagnosticInfo str a = tell [Diagnostic Info str (unCommented a)] - +insertIntoUnitInterface :: + NonEmpty.NonEmpty String -> + UnitInterface -> + Commented SourceSpan -> + ExportedValue -> + UnitInterface insertIntoUnitInterface path ui (Commented comments srcspan) val = let docComments = mconcat |