diff options
author | Juan J. Martinez <jjm@usebox.net> | 2022-08-14 13:46:45 +0100 |
---|---|---|
committer | Juan J. Martinez <jjm@usebox.net> | 2022-08-14 13:46:45 +0100 |
commit | f999609dade8eee277806c24f1981c66e5d48c15 (patch) | |
tree | ced79f527566bb06359edc96bc92fdf61aebc8bd | |
parent | 79d4e3e42cd4a9e668790f8a2e7a243523a14c88 (diff) | |
download | micro-lang-hs-f999609dade8eee277806c24f1981c66e5d48c15.tar.gz micro-lang-hs-f999609dade8eee277806c24f1981c66e5d48c15.zip |
Typecheck function calls
-rw-r--r-- | src/Compiler.hs | 41 |
1 files changed, 33 insertions, 8 deletions
diff --git a/src/Compiler.hs b/src/Compiler.hs index e694d71..0adc4ad 100644 --- a/src/Compiler.hs +++ b/src/Compiler.hs @@ -2,6 +2,7 @@ module Compiler where import qualified Ast as A import Control.Monad.State +import Data.Either (rights) import Env import Error import System.Environment (getEnv, getEnvironment) @@ -36,11 +37,37 @@ addError e = do put (ev, e : errs) return $ Right Nothing +-- | @typecheckCall args params@ resolves @args@ and compares it with @params@, +-- returning a a string describing an error or Nothing in case of type match. +typecheckCall :: [A.Expr] -> [A.Type] -> State CompState (Maybe String) +typecheckCall args params + | length args /= length params = return $ Just "invalid number of arguments in function call" + | length params == 0 = return $ Nothing + | otherwise = do + -- resolve all args types + targs <- fmap rights $ traverse compile args + case sequence targs of + Just t -> + if length t /= length params + then -- there was an error in one argument + return $ Nothing + else + if all (\(a, b) -> a == b) $ zip t params -- compare types + then return $ Nothing -- all good! + else return $ Just "type mismatch in function call" -- TODO: type description + Nothing -> + -- there was an error in on argument + return $ Nothing + compile :: A.Expr -> State CompState CompResult compile x = do case x of (A.Module name pos) -> return $ Right Nothing - (A.BinOp _ a b) -> compileAll [a, b] -- XXX + (A.Num _ _) -> return $ Right $ Just $ A.Type "u8" -- TODO: placeholder + (A.BinOp _ a b) -> do + l <- compile a + r <- compile b + return $ l -- TODO: placeholder (A.Func ident params ret body priv pos) -> do -- current env (ev, errs) <- get @@ -62,12 +89,11 @@ compile x = do (A.Call ident args pos) -> do r <- compile ident case r of - p@(Right (Just (A.FuncType params _))) -> - if length args /= length params - then addError $ Error ("invalid number of arguments in function call") pos - else return $ p - Right _ -> addError $ Error ("non callable value in function call") pos - Left r -> return $ Right Nothing + p@(Right (Just (A.FuncType params rtyp))) -> do + r <- typecheckCall args params + case r of + Just err -> addError $ Error err pos + Nothing -> return $ Right rtyp (A.Return value pos) -> case value of Just v -> compile v Nothing -> return $ Right Nothing @@ -76,7 +102,6 @@ compile x = do case getSym ev ident of Just (_, t, _) -> return $ Right $ Just t Nothing -> addError $ Error ("undefined variable \"" ++ ident ++ "\"") pos - _ -> return $ Right Nothing compileAll :: [A.Expr] -> State CompState CompResult compileAll (x : xs) = do |