diff options
author | Juan J. Martinez <jjm@usebox.net> | 2022-09-02 12:57:29 +0100 |
---|---|---|
committer | Juan J. Martinez <jjm@usebox.net> | 2022-09-02 12:57:29 +0100 |
commit | f66874f1f5066e57ef5761cd7c87b5d498fd89b6 (patch) | |
tree | 0edef26cda608a79c92f9c64c847f214ba877f9c | |
parent | a5633563e9bb579ed10cb7d6d43676485c13b1fb (diff) | |
download | micro-lang-hs-f66874f1f5066e57ef5761cd7c87b5d498fd89b6.tar.gz micro-lang-hs-f66874f1f5066e57ef5761cd7c87b5d498fd89b6.zip |
Private variables
-rw-r--r-- | language.md | 5 | ||||
-rw-r--r-- | src/Ast.hs | 7 | ||||
-rw-r--r-- | src/Compiler.hs | 14 | ||||
-rw-r--r-- | src/Env.hs | 10 | ||||
-rw-r--r-- | src/Parser.hs | 11 | ||||
-rw-r--r-- | test/Language.hs | 21 |
6 files changed, 43 insertions, 25 deletions
diff --git a/language.md b/language.md index 9adb6f6..2440cc7 100644 --- a/language.md +++ b/language.md @@ -74,6 +74,11 @@ p; # whatever byte is in address 0x8000 (peek) p = 0; # byte at 0x8000 is now 0 (poke) ``` +Variables are exported by default, unless they are defined as private: +``` +private val local: u8 = 123; +``` + ### Constants Constant are immutable values and may not have memory allocated to them: @@ -17,14 +17,15 @@ instance Show Type where showList :: [Type] -> String showList xs = intercalate ", " $ fmap show xs -type FuncParam = (Ident, Type, SourcePos) +type FuncParam = (Ident, Type, Bool, SourcePos) data Expr = Num Integer SourcePos | Bool' Bool SourcePos | BinOp Op Expr Expr | Variable Ident SourcePos - | Var Ident Type Expr SourcePos + | -- v type value private pos + Var Ident Type Expr Bool SourcePos | -- fn [params] return body private anomyous pos Func Ident [FuncParam] (Maybe Type) [Expr] Bool Bool SourcePos | Call Expr [Expr] SourcePos @@ -41,4 +42,4 @@ data Op toFuncType :: [FuncParam] -> Maybe Type -> Type toFuncType params rtyp = - FuncType (map (\(_, t, _) -> t) params) rtyp + FuncType (map (\(_, t, _, _) -> t) params) rtyp diff --git a/src/Compiler.hs b/src/Compiler.hs index a708f96..f36083c 100644 --- a/src/Compiler.hs +++ b/src/Compiler.hs @@ -90,7 +90,7 @@ verifyFuncType :: String -> [A.FuncParam] -> Maybe A.Type -> SourcePos -> [Error verifyFuncType ident params ret pos = do ( catMaybes $ map - ( \(id, t, pos) -> + ( \(id, t, _, pos) -> if not (definedType t) then Just $ Error UndefinedType ("undefined type in function declaration \"" ++ id ++ "\"") pos else Nothing @@ -118,7 +118,7 @@ compile x = do (ev, errs) <- return $ (ev, (verifyFuncType ident params ret pos) ++ errs) -- updated with the function (ev, errs) <- - return $ case addSymUniq ev (ident, ftype, pos) of + return $ case addSymUniq ev (ident, ftype, priv, pos) of Left err -> (ev, err : errs) Right ev -> (ev, errs) -- lambdas can only access local variables (closures aren't supported) @@ -126,7 +126,7 @@ compile x = do -- with parameters (nev, errs) <- return $ foldlEither addSymUniq (addEnv fev, errs) params -- helper for return - nev <- return $ addSym nev ("$fn$", ftype, pos) + nev <- return $ addSym nev ("$fn$", ftype, True, pos) put (nev, errs) r <- compileAll body (_, errs) <- get @@ -145,9 +145,9 @@ compile x = do Nothing -> return $ Right rtyp Right _ -> addError $ Error NonCallable "non callable value in function call" pos _ -> return $ Right Nothing - (A.Var ident typ val pos) -> do + (A.Var ident typ val priv pos) -> do (ev, errs) <- get - (ev, errs) <- return $ foldlEither addSymUniq (ev, errs) [(ident, typ, pos)] + (ev, errs) <- return $ foldlEither addSymUniq (ev, errs) [(ident, typ, priv, pos)] errs <- return $ if not (definedType typ) @@ -160,7 +160,7 @@ compile x = do (ev, errs) <- get case getSyml ev "$fn$" of Nothing -> addError $ Error UnexpectedReturn "return without function call" pos - Just (_, A.FuncType _ rtyp, _) -> do + Just (_, A.FuncType _ rtyp, _, _) -> do r <- typecheckReturn value rtyp case r of Just err -> addError $ Error TypeError err pos @@ -168,7 +168,7 @@ compile x = do (A.Variable ident pos) -> do (ev, errs) <- get case getSym ev ident of - Just (_, t, _) -> return $ Right $ Just t + Just (_, t, _, _) -> return $ Right $ Just t Nothing -> addError $ Error Undefined ("undefined variable \"" ++ ident ++ "\"") pos compileAll :: [A.Expr] -> State CompState CompResult @@ -6,7 +6,7 @@ import Data.Maybe (isJust) import Error import Text.Parsec (SourcePos) -type Sym = (A.Ident, A.Type, SourcePos) +type Sym = (A.Ident, A.Type, Bool, SourcePos) type SymMap = Map.Map A.Ident Sym @@ -44,7 +44,7 @@ existsSyml env sym = isJust $ getSyml env sym -- environment. It will create a new enviroment if the symbol already exists -- (shadowing). addSym :: Env -> Sym -> Env -addSym env@(Env m parent) sym@(id, typ, pos) = case getSym env id of +addSym env@(Env m parent) sym@(id, _, _, _) = case getSym env id of Nothing -> Env (Map.insert id sym m) parent Just s -> Env (Map.singleton id sym) $ Just env @@ -55,8 +55,8 @@ addEnv env = Env Map.empty $ Just env -- | @addSymUniq e s@ adds a local symbol @s@ to the enviroment @e@ if it -- doesn't exist. addSymUniq :: Env -> Sym -> Either Error Env -addSymUniq ev (id, typ, pos) = case getSyml ev id of +addSymUniq ev (id, typ, priv, pos) = case getSyml ev id of Nothing -> Right $ addSym ev sym - Just (_, _, p) -> Left $ Error AlreadyDefined ("symbol \"" ++ id ++ "\" already defined in " ++ show p) pos + Just (_, _, _, p) -> Left $ Error AlreadyDefined ("symbol \"" ++ id ++ "\" already defined in " ++ show p) pos where - sym = (id, typ, pos) + sym = (id, typ, priv, pos) diff --git a/src/Parser.hs b/src/Parser.hs index de8cce0..f3fd03b 100644 --- a/src/Parser.hs +++ b/src/Parser.hs @@ -63,13 +63,13 @@ type' = do try typFn <|> typ <?> "type" -arg :: Parser (String, Type, SourcePos) +arg :: Parser (String, Type, Bool, SourcePos) arg = do pos <- getPosition i <- identifier _ <- colonSep <?> "\":\" before type" t <- type' <?> "type" - return $ (i, t, pos) + return $ (i, t, True, pos) fdef :: Ident -> Bool -> Bool -> SourcePos -> Parser Expr fdef ident priv anon pos = do @@ -118,12 +118,13 @@ call = do var :: Parser Expr var = do + priv <- optionMaybe $ reserved "private" reserved "var" - (ident, typ, pos) <- arg + (ident, typ, _, pos) <- arg reservedOp "=" <?> "assignation" value <- expr reservedOp ";" - return $ Var ident typ value pos + return $ Var ident typ value (isJust priv) pos factor :: Parser Expr factor = @@ -158,7 +159,7 @@ program = do m <- module' n <- many $ do - function + try function <|> var <|> statement <?> "statement" return $ [m] ++ n diff --git a/test/Language.hs b/test/Language.hs index fbb9c3b..19ec5bf 100644 --- a/test/Language.hs +++ b/test/Language.hs @@ -64,7 +64,7 @@ testCase4 = "module main\n\ \def fn(a: u8) { }" [ A.Module "main" $ newPos "test" 1 1, - A.Func "fn" [("a", A.Type "u8", newPos "test" 2 8)] Nothing [] False False $ newPos "test" 2 1 + A.Func "fn" [("a", A.Type "u8", True, newPos "test" 2 8)] Nothing [] False False $ newPos "test" 2 1 ] testCase5 = @@ -101,7 +101,7 @@ testCase7 = \def fn(a: u8) { }\n\ \fn(10);" [ A.Module "main" $ newPos "test" 1 1, - A.Func "fn" [("a", A.Type "u8", newPos "test" 2 8)] Nothing [] False False $ newPos "test" 2 1, + A.Func "fn" [("a", A.Type "u8", True, newPos "test" 2 8)] Nothing [] False False $ newPos "test" 2 1, A.Call (A.Variable "fn" $ newPos "test" 3 1) [A.Num 10 $ newPos "test" 3 4] $ newPos "test" 3 1 ] @@ -143,7 +143,7 @@ testCase10 = A.Func "fn1" [] Nothing [] False False $ newPos "test" 2 1, A.Func "fn2" - [("f", A.FuncType [] Nothing, newPos "test" 3 9)] + [("f", A.FuncType [] Nothing, True, newPos "test" 3 9)] Nothing [ A.Call (A.Variable "f" $ newPos "test" 4 1) [] $ newPos "test" 4 1 ] @@ -165,7 +165,7 @@ testCase11 = [ A.Module "main" $ newPos "test" 1 1, A.Func "fn" - [("f", A.FuncType [] Nothing, newPos "test" 2 8)] + [("f", A.FuncType [] Nothing, True, newPos "test" 2 8)] Nothing [A.Call (A.Variable "f" $ newPos "test" 3 1) [] $ newPos "test" 3 1] False @@ -191,7 +191,17 @@ testCase13 = "module main\n\ \var a: u8 = 10;" [ A.Module "main" $ newPos "test" 1 1, - A.Var "a" (A.Type "u8") (A.Num 10 $ newPos "test" 2 13) $ newPos "test" 2 5 + A.Var "a" (A.Type "u8") (A.Num 10 $ newPos "test" 2 13) False $ newPos "test" 2 5 + ] + +testCase14 = + TestLabel "parse a private variable declaration" $ + TestCase $ + assertAst + "module main\n\ + \private var a: u8 = 10;" + [ A.Module "main" $ newPos "test" 1 1, + A.Var "a" (A.Type "u8") (A.Num 10 $ newPos "test" 2 21) True $ newPos "test" 2 13 ] -- test errors @@ -312,6 +322,7 @@ language = testCase11, testCase12, testCase13, + testCase14, testCaseE1, testCaseE2, testCaseE3, |