aboutsummaryrefslogtreecommitdiff
path: root/src/Micro/Compiler.hs
diff options
context:
space:
mode:
authorJuan J. Martinez <jjm@usebox.net>2023-12-20 19:53:05 +0000
committerJuan J. Martinez <jjm@usebox.net>2023-12-20 19:53:05 +0000
commitc7cc8467ca1835c8f96ccb5be7c976a26d262433 (patch)
tree007845bfd68c97ce88056912942617424c2f93a8 /src/Micro/Compiler.hs
parent9ebeada35c00160b19161928be74e44093686985 (diff)
downloadmicro-lang-hs-c7cc8467ca1835c8f96ccb5be7c976a26d262433.tar.gz
micro-lang-hs-c7cc8467ca1835c8f96ccb5be7c976a26d262433.zip
Updated to use GHC 9.4.x and floating dependencies
Diffstat (limited to 'src/Micro/Compiler.hs')
-rw-r--r--src/Micro/Compiler.hs16
1 files changed, 8 insertions, 8 deletions
diff --git a/src/Micro/Compiler.hs b/src/Micro/Compiler.hs
index 70ce82c..81d403d 100644
--- a/src/Micro/Compiler.hs
+++ b/src/Micro/Compiler.hs
@@ -10,7 +10,7 @@ import Control.Monad.State
import Data.Foldable (traverse_)
import Data.Maybe (isNothing, mapMaybe)
import Micro.Asm.Sdcc (generate)
-import qualified Micro.Ast as A
+import Micro.Ast qualified as A
import Micro.Env
import Micro.Error
import Text.Parsec (SourcePos)
@@ -42,7 +42,7 @@ foldlEither fn =
-- the compilation to continue.
addError :: Error -> State CompState (Maybe A.Type)
addError e = do
- modify $ \st -> st {stErr = e : stErr st}
+ modify $ \st -> st {stErr = e : st.stErr}
pure Nothing
-- | @typecheckCall args params@ resolves @args@ and compares it with @params@,
@@ -118,7 +118,7 @@ compileOne x = do
-- current env
st <- get
-- check for undefined types
- (ev, errs) <- return (stEnv st, verifyFuncType ident params ret pos ++ stErr st)
+ (ev, errs) <- return (st.stEnv, verifyFuncType ident params ret pos ++ st.stErr)
-- updated with the function
(ev, errs) <-
return $ case addSymUniq ev (Sym ident ftype priv False pos) of
@@ -148,7 +148,7 @@ compileOne x = do
_ -> addError $ Error NonCallable "non callable value in function call" pos
(A.Var ident typ val priv local pos) -> do
st <- get
- (ev, errs) <- return $ foldlEither addSymUniq (stEnv st, stErr st) [Sym ident typ priv local pos]
+ (ev, errs) <- return $ foldlEither addSymUniq (st.stEnv, st.stErr) [Sym ident typ priv local pos]
errs <-
return $
if not (definedType typ)
@@ -159,7 +159,7 @@ compileOne x = do
typecheck (Just typ) t pos
(A.Return value pos) -> do
st <- get
- case getSyml (stEnv st) "$fn$" of
+ case getSyml st.stEnv "$fn$" of
Just Sym {symType = A.FuncType _ rtyp} -> do
case value of
Nothing ->
@@ -172,7 +172,7 @@ compileOne x = do
_ -> addError $ Error UnexpectedReturn "return without function call" pos
(A.Variable ident pos) -> do
st <- get
- case getSym (stEnv st) ident of
+ case getSym st.stEnv ident of
Just Sym {symType = t} -> pure $ Just t
Nothing -> addError $ Error Undefined ("undefined \"" ++ ident ++ "\"") pos
@@ -211,8 +211,8 @@ compileAll :: [A.Expr] -> State CompState (Either [Error] SymMap)
compileAll ast = do
traverse_ compileOne ast
st <- get
- let (Env sym _) = stEnv st
- let errs = stErr st
+ let (Env sym _) = st.stEnv
+ let errs = st.stErr
case errs of
[] -> pure $ Right sym
_ -> return $ Left errs