aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorEinhard Leichtfuß <alguien@respiranto.de>2025-05-16 14:16:29 +0200
committerEinhard Leichtfuß <alguien@respiranto.de>2025-05-16 14:16:29 +0200
commitfccc64702fb0b110e404dd827bdb4400a6bc9360 (patch)
tree21fcebb71da0594f187ec807f0cc0bf4ae771719
parentc5e3637c37805b2167e21158cc889a48f8c221b2 (diff)
Add initial AST
-rw-r--r--src/Language/SimpleShell/AST.hs62
1 files changed, 62 insertions, 0 deletions
diff --git a/src/Language/SimpleShell/AST.hs b/src/Language/SimpleShell/AST.hs
new file mode 100644
index 0000000..7549626
--- /dev/null
+++ b/src/Language/SimpleShell/AST.hs
@@ -0,0 +1,62 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+
+module Language.SimpleShell.AST
+where
+
+class SimpleType a
+instance SimpleType Integer
+instance SimpleType String
+instance SimpleType Bool
+
+class Castable a b
+instance Castable Integer String
+instance Castable String Integer
+
+data Expr a where
+ Literal :: (SimpleType a) => a -> Expr a
+ VarE :: Var a -> Expr a
+ FunctionCall :: Function a args -> ExprList args -> Expr a
+ And :: Expr Bool -> Expr Bool -> Expr Bool
+ Or :: Expr Bool -> Expr Bool -> Expr Bool
+ Not :: Expr Bool -> Expr Bool
+ Eq :: Expr a -> Expr a -> Expr Bool
+ Neq :: Expr a -> Expr a -> Expr Bool
+ Gt :: Expr Integer -> Expr Integer -> Expr Bool
+ Ge :: Expr Integer -> Expr Integer -> Expr Bool
+ Lt :: Expr Integer -> Expr Integer -> Expr Bool
+ Le :: Expr Integer -> Expr Integer -> Expr Bool
+ Ternary :: (SimpleType a) => Expr Bool -> Expr a -> Expr a -> Expr a
+ Cast :: (Castable a b) => Expr a -> Expr b
+
+data ExprList a where
+ NilE :: ExprList ()
+ ConsE :: Expr a -> ExprList as -> ExprList (a, as)
+
+data Var a where
+ Var :: (SimpleType a) => String -> Var a
+
+data Args args where
+ NilArgs :: Args ()
+ ConsArgs :: (SimpleType a) => Var a -> Args as -> Args (a, as)
+
+data Statement a where
+ Declare :: Var a -> Statement b
+ Assign :: Var a -> Expr a -> Statement b
+ Print :: Expr String -> Statement b
+ Command
+ :: (Maybe (Var Integer)) -- shell return value
+ -> (Maybe (Var String)) -- stdout
+ -> (Maybe (Var String)) -- stderr
+ -> Command a
+ -> Statement a
+ Return :: Expr a -> Statement a
+
+data Command a where
+ ExtCmd :: Expr String -> [Expr String] -> Command b
+ CompundCmd :: [Statement a] -> Command a
+
+data Function a args where
+ Function :: (SimpleType a) => Args args -> Command a -> Function a args