module Language.GLSL.Syntax where
data TranslationUnit = TranslationUnit [ExternalDeclaration]
deriving (Show, Eq)
data ExternalDeclaration =
FunctionDeclaration FunctionPrototype
| FunctionDefinition FunctionPrototype Compound
| Declaration Declaration
deriving (Show, Eq)
data Declaration =
InitDeclaration InvariantOrType [InitDeclarator]
| Precision PrecisionQualifier TypeSpecifierNoPrecision
| Block TypeQualifier String [Field] (Maybe (String, Maybe (Maybe Expr)))
| TQ TypeQualifier
deriving (Show, Eq)
data InitDeclarator = InitDecl String (Maybe (Maybe Expr)) (Maybe Expr)
deriving (Show, Eq)
data InvariantOrType = InvariantDeclarator | TypeDeclarator FullType
deriving (Show, Eq)
data FunctionPrototype = FuncProt FullType String [ParameterDeclaration]
deriving (Show, Eq)
data ParameterDeclaration =
ParameterDeclaration (Maybe ParameterTypeQualifier)
(Maybe ParameterQualifier)
TypeSpecifier
(Maybe (String, Maybe Expr))
deriving (Show, Eq)
data FullType = FullType (Maybe TypeQualifier) TypeSpecifier
deriving (Show, Eq)
data TypeQualifier =
TypeQualSto StorageQualifier
| TypeQualLay LayoutQualifier (Maybe StorageQualifier)
| TypeQualInt InterpolationQualifier (Maybe StorageQualifier)
| TypeQualInv InvariantQualifier (Maybe StorageQualifier)
| TypeQualInv3 InvariantQualifier InterpolationQualifier StorageQualifier
deriving (Show, Eq)
data TypeSpecifier = TypeSpec (Maybe PrecisionQualifier) TypeSpecifierNoPrecision
deriving (Show, Eq)
data InvariantQualifier = Invariant
deriving (Show, Eq)
data InterpolationQualifier =
Smooth
| Flat
| NoPerspective
deriving (Show, Eq)
data LayoutQualifier = Layout [LayoutQualifierId]
deriving (Show, Eq)
data LayoutQualifierId = LayoutQualId String (Maybe Expr)
deriving (Show, Eq)
data Statement =
DeclarationStatement Declaration
| Continue
| Break
| Return (Maybe Expr)
| Discard
| CompoundStatement Compound
| ExpressionStatement (Maybe Expr)
| SelectionStatement Expr Statement (Maybe Statement)
| SwitchStatement Expr [Statement]
| CaseLabel CaseLabel
| While Condition Statement
| DoWhile Statement Expr
| For (Either (Maybe Expr) Declaration) (Maybe Condition) (Maybe Expr) Statement
deriving (Show, Eq)
data Compound = Compound [Statement]
deriving (Show, Eq)
data Condition =
Condition Expr
| InitializedCondition FullType String Expr
deriving (Show, Eq)
data CaseLabel = Case Expr | Default
deriving (Show, Eq)
data StorageQualifier =
Const
| Attribute
| Varying
| CentroidVarying
| In
| Out
| CentroidIn
| CentroidOut
| Uniform
deriving (Show, Eq)
data TypeSpecifierNoPrecision = TypeSpecNoPrecision TypeSpecifierNonArray (Maybe (Maybe Expr))
deriving (Show, Eq)
data TypeSpecifierNonArray =
Void
| Float
| Int
| UInt
| Bool
| Vec2
| Vec3
| Vec4
| BVec2
| BVec3
| BVec4
| IVec2
| IVec3
| IVec4
| UVec2
| UVec3
| UVec4
| Mat2
| Mat3
| Mat4
| Mat2x2
| Mat2x3
| Mat2x4
| Mat3x2
| Mat3x3
| Mat3x4
| Mat4x2
| Mat4x3
| Mat4x4
| Sampler1D
| Sampler2D
| Sampler3D
| SamplerCube
| Sampler1DShadow
| Sampler2DShadow
| SamplerCubeShadow
| Sampler1DArray
| Sampler2DArray
| Sampler1DArrayShadow
| Sampler2DArrayShadow
| ISampler1D
| ISampler2D
| ISampler3D
| ISamplerCube
| ISampler1DArray
| ISampler2DArray
| USampler1D
| USampler2D
| USampler3D
| USamplerCube
| USampler1DArray
| USampler2DArray
| Sampler2DRect
| Sampler2DRectShadow
| ISampler2DRect
| USampler2DRect
| SamplerBuffer
| ISamplerBuffer
| USamplerBuffer
| Sampler2DMS
| ISampler2DMS
| USampler2DMS
| Sampler2DMSArray
| ISampler2DMSArray
| USampler2DMSArray
| StructSpecifier (Maybe String) [Field]
| TypeName String
deriving (Show, Eq)
data PrecisionQualifier = HighP | MediumP | LowP
deriving (Show, Eq)
data Field = Field (Maybe TypeQualifier) TypeSpecifier [StructDeclarator]
deriving (Show, Eq)
data StructDeclarator = StructDeclarator String (Maybe (Maybe Expr))
deriving (Show, Eq)
data Expr =
Variable String
| IntConstant IntConstantKind Integer
| FloatConstant Float
| BoolConstant Bool
| Bracket Expr Expr
| FieldSelection Expr String
| MethodCall Expr FunctionIdentifier Parameters
| FunctionCall FunctionIdentifier Parameters
| PostInc Expr
| PostDec Expr
| PreInc Expr
| PreDec Expr
| UnaryPlus Expr
| UnaryNegate Expr
| UnaryNot Expr
| UnaryOneComplement Expr
| Mul Expr Expr
| Div Expr Expr
| Mod Expr Expr
| Add Expr Expr
| Sub Expr Expr
| LeftShift Expr Expr
| RightShift Expr Expr
| Lt Expr Expr
| Gt Expr Expr
| Lte Expr Expr
| Gte Expr Expr
| Equ Expr Expr
| Neq Expr Expr
| BitAnd Expr Expr
| BitXor Expr Expr
| BitOr Expr Expr
| And Expr Expr
| Or Expr Expr
| Selection Expr Expr Expr
| Equal Expr Expr
| MulAssign Expr Expr
| DivAssign Expr Expr
| ModAssign Expr Expr
| AddAssign Expr Expr
| SubAssign Expr Expr
| LeftAssign Expr Expr
| RightAssign Expr Expr
| AndAssign Expr Expr
| XorAssign Expr Expr
| OrAssign Expr Expr
| Sequence Expr Expr
deriving (Show, Eq)
data IntConstantKind = Hexadecimal | Octal | Decimal
deriving (Show, Eq)
data Parameters = ParamVoid | Params [Expr]
deriving (Show, Eq)
data ParameterQualifier = InParameter | OutParameter | InOutParameter
deriving (Show, Eq)
data ParameterTypeQualifier = ConstParameter
deriving (Show, Eq)
data FunctionIdentifier =
FuncIdTypeSpec TypeSpecifier
| FuncId String
deriving (Show, Eq)