aboutsummaryrefslogtreecommitdiff
path: root/src/Micro/Ast.hs
diff options
context:
space:
mode:
authorJuan J. Martinez <jjm@usebox.net>2022-09-07 16:26:50 +0100
committerJuan J. Martinez <jjm@usebox.net>2022-09-07 16:26:50 +0100
commit65c8beecb14f6d09c49504d74beedd58cc7ddd17 (patch)
tree0a39cc6fc3f78153272c6528300936c039351d3e /src/Micro/Ast.hs
parent48896c56c39344fa429260d3969eccc93ef8035c (diff)
downloadmicro-lang-hs-65c8beecb14f6d09c49504d74beedd58cc7ddd17.tar.gz
micro-lang-hs-65c8beecb14f6d09c49504d74beedd58cc7ddd17.zip
Better project layout, removed warnings
Diffstat (limited to 'src/Micro/Ast.hs')
-rw-r--r--src/Micro/Ast.hs46
1 files changed, 46 insertions, 0 deletions
diff --git a/src/Micro/Ast.hs b/src/Micro/Ast.hs
new file mode 100644
index 0000000..45697de
--- /dev/null
+++ b/src/Micro/Ast.hs
@@ -0,0 +1,46 @@
+module Micro.Ast where
+
+import Data.List (intercalate)
+import Text.Parsec (SourcePos)
+
+type Ident = String
+
+data Type = Type String | FuncType [Type] (Maybe Type) deriving (Eq, Ord)
+
+instance Show Type where
+ show (Type t) = t
+ show (FuncType params rtyp) =
+ "(" ++ (intercalate ", " (fmap show params)) ++ ") -> " ++ case rtyp of
+ Just t -> show t
+ Nothing -> "()"
+
+showList :: [Type] -> String
+showList xs = intercalate ", " $ fmap show xs
+
+type FuncParam = (Ident, Type, Bool, SourcePos)
+
+data Expr
+ = Num Integer SourcePos
+ | Bool' Bool SourcePos
+ | BinOp Op SourcePos Expr Expr
+ | Variable Ident 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
+ | Return (Maybe Expr) SourcePos
+ | Module String SourcePos
+ deriving (Eq, Ord, Show)
+
+data Op
+ = Assign
+ | Plus
+ | Minus
+ | Mul
+ | Div
+ deriving (Eq, Ord, Show)
+
+toFuncType :: [FuncParam] -> Maybe Type -> Type
+toFuncType params rtyp =
+ FuncType (map (\(_, t, _, _) -> t) params) rtyp