Skip to content

Instantly share code, notes, and snippets.

@jvranish
Created December 31, 2011 20:50
Show Gist options
  • Save jvranish/1545297 to your computer and use it in GitHub Desktop.
Save jvranish/1545297 to your computer and use it in GitHub Desktop.
Preliminary AST
{-#Language GeneralizedNewtypeDeriving #-}
module Language.TheExperiment.AST where
import Text.Parsec.Pos
import Language.TheExperiment.Type
data Literal = StringLiteral String
| CharLiteral Char
| IntegerLiteral Integer
| HexLiteral Integer
| FloatLiteral Double
deriving (Show, Eq, Ord)
newtype NodeId = NodeId Int -- unique identifier for each node in the AST
deriving (Show, Eq, Ord, Enum, Bounded, Num, Integral, Real)
data ParsedType = ParsedType { typePos :: SourcePos
, parsedType :: Type ParsedType
}
deriving (Show, Eq, Ord)
data Expr = Call { exprPos :: SourcePos
, exprNodeId :: NodeId
, callFunc :: Expr
, callParams :: [Expr]
}
| Identifier { exprPos :: SourcePos
, exprNodeId :: NodeId
, idName :: String
}
| Literal { exprPos :: SourcePos
, exprNodeId :: NodeId
, literal :: Literal
}
| Cast { exprPos :: SourcePos
, exprNodeId :: NodeId
, castType :: ParsedType
, castExpr :: Expr
}
| Member { exprPos :: SourcePos
, exprNodeId :: NodeId
, memberExpr :: Expr
, memberName :: String
}
deriving (Show, Eq, Ord)
data Statement = Assign { stmtPos :: SourcePos
, stmtNodeId :: NodeId
, assignName :: String
, assignExpr :: Expr
}
| VarDef { stmtPos :: SourcePos
, stmtNodeId :: NodeId
, varName :: String
}
| If { stmtPos :: SourcePos
, stmtNodeId :: NodeId
, ifCond :: Expr
, ifThen :: Statement
, ifElse :: Maybe Statement
}
| While { stmtPos :: SourcePos
, stmtNodeId :: NodeId
, whileCond :: Expr
, whileBody :: Statement
}
| FuncDef { stmtPos :: SourcePos
, stmtNodeId :: NodeId
, funcName :: String
, funcParams :: [String]
, funcExpr :: Expr
}
| ExprStmt { stmtPos :: SourcePos
, stmtNodeId :: NodeId
, stmtExpr :: Expr
}
| Block { stmtPos :: SourcePos
, stmtNodeId :: NodeId
, blockBody :: [Statement]
}
deriving (Show, Eq, Ord)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment