glsl-0.0.1.1: Parser and optimizer for a small subset of GLSL
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.GLSL.AST

Documentation

data GLSL a Source #

Constructors

GLSL Version [TopDecl a] 

Instances

Instances details
Functor GLSL Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fmap :: (a -> b) -> GLSL a -> GLSL b #

(<$) :: a -> GLSL b -> GLSL a #

Foldable GLSL Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fold :: Monoid m => GLSL m -> m #

foldMap :: Monoid m => (a -> m) -> GLSL a -> m #

foldMap' :: Monoid m => (a -> m) -> GLSL a -> m #

foldr :: (a -> b -> b) -> b -> GLSL a -> b #

foldr' :: (a -> b -> b) -> b -> GLSL a -> b #

foldl :: (b -> a -> b) -> b -> GLSL a -> b #

foldl' :: (b -> a -> b) -> b -> GLSL a -> b #

foldr1 :: (a -> a -> a) -> GLSL a -> a #

foldl1 :: (a -> a -> a) -> GLSL a -> a #

toList :: GLSL a -> [a] #

null :: GLSL a -> Bool #

length :: GLSL a -> Int #

elem :: Eq a => a -> GLSL a -> Bool #

maximum :: Ord a => GLSL a -> a #

minimum :: Ord a => GLSL a -> a #

sum :: Num a => GLSL a -> a #

product :: Num a => GLSL a -> a #

Traversable GLSL Source # 
Instance details

Defined in Language.GLSL.AST

Methods

traverse :: Applicative f => (a -> f b) -> GLSL a -> f (GLSL b) #

sequenceA :: Applicative f => GLSL (f a) -> f (GLSL a) #

mapM :: Monad m => (a -> m b) -> GLSL a -> m (GLSL b) #

sequence :: Monad m => GLSL (m a) -> m (GLSL a) #

Eq a => Eq (GLSL a) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: GLSL a -> GLSL a -> Bool #

(/=) :: GLSL a -> GLSL a -> Bool #

Show a => Show (GLSL a) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> GLSL a -> ShowS #

show :: GLSL a -> String #

showList :: [GLSL a] -> ShowS #

Generic (GLSL a) Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep (GLSL a) :: Type -> Type #

Methods

from :: GLSL a -> Rep (GLSL a) x #

to :: Rep (GLSL a) x -> GLSL a #

type Rep (GLSL a) Source # 
Instance details

Defined in Language.GLSL.AST

newtype Version Source #

Constructors

Version Int 

Instances

Instances details
Eq Version Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Show Version Source # 
Instance details

Defined in Language.GLSL.AST

Generic Version Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

type Rep Version Source # 
Instance details

Defined in Language.GLSL.AST

type Rep Version = D1 ('MetaData "Version" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'True) (C1 ('MetaCons "Version" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data TopDecl a Source #

Instances

Instances details
Functor TopDecl Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fmap :: (a -> b) -> TopDecl a -> TopDecl b #

(<$) :: a -> TopDecl b -> TopDecl a #

Foldable TopDecl Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fold :: Monoid m => TopDecl m -> m #

foldMap :: Monoid m => (a -> m) -> TopDecl a -> m #

foldMap' :: Monoid m => (a -> m) -> TopDecl a -> m #

foldr :: (a -> b -> b) -> b -> TopDecl a -> b #

foldr' :: (a -> b -> b) -> b -> TopDecl a -> b #

foldl :: (b -> a -> b) -> b -> TopDecl a -> b #

foldl' :: (b -> a -> b) -> b -> TopDecl a -> b #

foldr1 :: (a -> a -> a) -> TopDecl a -> a #

foldl1 :: (a -> a -> a) -> TopDecl a -> a #

toList :: TopDecl a -> [a] #

null :: TopDecl a -> Bool #

length :: TopDecl a -> Int #

elem :: Eq a => a -> TopDecl a -> Bool #

maximum :: Ord a => TopDecl a -> a #

minimum :: Ord a => TopDecl a -> a #

sum :: Num a => TopDecl a -> a #

product :: Num a => TopDecl a -> a #

Traversable TopDecl Source # 
Instance details

Defined in Language.GLSL.AST

Methods

traverse :: Applicative f => (a -> f b) -> TopDecl a -> f (TopDecl b) #

sequenceA :: Applicative f => TopDecl (f a) -> f (TopDecl a) #

mapM :: Monad m => (a -> m b) -> TopDecl a -> m (TopDecl b) #

sequence :: Monad m => TopDecl (m a) -> m (TopDecl a) #

Eq a => Eq (TopDecl a) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: TopDecl a -> TopDecl a -> Bool #

(/=) :: TopDecl a -> TopDecl a -> Bool #

Show a => Show (TopDecl a) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> TopDecl a -> ShowS #

show :: TopDecl a -> String #

showList :: [TopDecl a] -> ShowS #

Generic (TopDecl a) Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep (TopDecl a) :: Type -> Type #

Methods

from :: TopDecl a -> Rep (TopDecl a) x #

to :: Rep (TopDecl a) x -> TopDecl a #

type Rep (TopDecl a) Source # 
Instance details

Defined in Language.GLSL.AST

data ProcName Source #

Constructors

ProcMain 
ProcName NameId 

Instances

Instances details
Eq ProcName Source # 
Instance details

Defined in Language.GLSL.AST

Show ProcName Source # 
Instance details

Defined in Language.GLSL.AST

Generic ProcName Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep ProcName :: Type -> Type #

Methods

from :: ProcName -> Rep ProcName x #

to :: Rep ProcName x -> ProcName #

type Rep ProcName Source # 
Instance details

Defined in Language.GLSL.AST

type Rep ProcName = D1 ('MetaData "ProcName" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "ProcMain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProcName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NameId)))

data LayoutSpec Source #

Instances

Instances details
Eq LayoutSpec Source # 
Instance details

Defined in Language.GLSL.AST

Show LayoutSpec Source # 
Instance details

Defined in Language.GLSL.AST

Generic LayoutSpec Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep LayoutSpec :: Type -> Type #

type Rep LayoutSpec Source # 
Instance details

Defined in Language.GLSL.AST

type Rep LayoutSpec = D1 ('MetaData "LayoutSpec" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "LayoutStd140" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LayoutLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))

data ParamDecl Source #

Constructors

Param ParamKind LocalDecl 

Instances

Instances details
Eq ParamDecl Source # 
Instance details

Defined in Language.GLSL.AST

Show ParamDecl Source # 
Instance details

Defined in Language.GLSL.AST

Generic ParamDecl Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep ParamDecl :: Type -> Type #

type Rep ParamDecl Source # 
Instance details

Defined in Language.GLSL.AST

data ParamKind Source #

Constructors

PkIn 
PkOut 
PkInout 

Instances

Instances details
Eq ParamKind Source # 
Instance details

Defined in Language.GLSL.AST

Show ParamKind Source # 
Instance details

Defined in Language.GLSL.AST

Generic ParamKind Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep ParamKind :: Type -> Type #

type Rep ParamKind Source # 
Instance details

Defined in Language.GLSL.AST

type Rep ParamKind = D1 ('MetaData "ParamKind" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "PkIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PkOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PkInout" 'PrefixI 'False) (U1 :: Type -> Type)))

data LocalDecl Source #

Constructors

LDecl Type NameId (Maybe Expr) 

Instances

Instances details
Eq LocalDecl Source # 
Instance details

Defined in Language.GLSL.AST

Show LocalDecl Source # 
Instance details

Defined in Language.GLSL.AST

Generic LocalDecl Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep LocalDecl :: Type -> Type #

type Rep LocalDecl Source # 
Instance details

Defined in Language.GLSL.AST

data GlobalDecl Source #

Constructors

GDecl GDeclKind Type Name 

Instances

Instances details
Eq GlobalDecl Source # 
Instance details

Defined in Language.GLSL.AST

Show GlobalDecl Source # 
Instance details

Defined in Language.GLSL.AST

Generic GlobalDecl Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep GlobalDecl :: Type -> Type #

type Rep GlobalDecl Source # 
Instance details

Defined in Language.GLSL.AST

data GDeclKind Source #

Constructors

GkIn 
GkOut 
GkUniform 

Instances

Instances details
Eq GDeclKind Source # 
Instance details

Defined in Language.GLSL.AST

Show GDeclKind Source # 
Instance details

Defined in Language.GLSL.AST

Generic GDeclKind Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep GDeclKind :: Type -> Type #

type Rep GDeclKind Source # 
Instance details

Defined in Language.GLSL.AST

type Rep GDeclKind = D1 ('MetaData "GDeclKind" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "GkIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GkOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GkUniform" 'PrefixI 'False) (U1 :: Type -> Type)))

data Type Source #

Instances

Instances details
Eq Type Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Show Type Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

type Rep Type Source # 
Instance details

Defined in Language.GLSL.AST

newtype NameId Source #

Constructors

NameId Int 

Instances

Instances details
Eq NameId Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: NameId -> NameId -> Bool #

(/=) :: NameId -> NameId -> Bool #

Show NameId Source # 
Instance details

Defined in Language.GLSL.AST

Generic NameId Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep NameId :: Type -> Type #

Methods

from :: NameId -> Rep NameId x #

to :: Rep NameId x -> NameId #

type Rep NameId Source # 
Instance details

Defined in Language.GLSL.AST

type Rep NameId = D1 ('MetaData "NameId" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'True) (C1 ('MetaCons "NameId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Name Source #

Constructors

Name Namespace NameId 

Instances

Instances details
Eq Name Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Show Name Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

type Rep Name Source # 
Instance details

Defined in Language.GLSL.AST

data Namespace Source #

Constructors

NsT 
NsS 
NsU 
NsVF 
NsIn 
NsOut 

Instances

Instances details
Eq Namespace Source # 
Instance details

Defined in Language.GLSL.AST

Show Namespace Source # 
Instance details

Defined in Language.GLSL.AST

Generic Namespace Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Namespace :: Type -> Type #

type Rep Namespace Source # 
Instance details

Defined in Language.GLSL.AST

type Rep Namespace = D1 ('MetaData "Namespace" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) ((C1 ('MetaCons "NsT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NsS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NsU" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NsVF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NsIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NsOut" 'PrefixI 'False) (U1 :: Type -> Type))))

data FunName Source #

Instances

Instances details
Eq FunName Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: FunName -> FunName -> Bool #

(/=) :: FunName -> FunName -> Bool #

Show FunName Source # 
Instance details

Defined in Language.GLSL.AST

Generic FunName Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep FunName :: Type -> Type #

Methods

from :: FunName -> Rep FunName x #

to :: Rep FunName x -> FunName #

type Rep FunName Source # 
Instance details

Defined in Language.GLSL.AST

type Rep FunName = D1 ('MetaData "FunName" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) ((((C1 ('MetaCons "PrimAbs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimAsin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimAtan" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimCos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimCross" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PrimDot" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimFloor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimFract" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PrimLength" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimMat3x3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimMat4x4" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PrimMod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimNormalize" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimPow" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimSin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimSmoothstep" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PrimSqrt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimStep" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimTan" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PrimVec2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimVec3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrimVec4" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Swizzle Source #

Constructors

X 
Y 
Z 
W 

Instances

Instances details
Eq Swizzle Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Swizzle -> Swizzle -> Bool #

(/=) :: Swizzle -> Swizzle -> Bool #

Show Swizzle Source # 
Instance details

Defined in Language.GLSL.AST

Generic Swizzle Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Swizzle :: Type -> Type #

Methods

from :: Swizzle -> Rep Swizzle x #

to :: Rep Swizzle x -> Swizzle #

type Rep Swizzle Source # 
Instance details

Defined in Language.GLSL.AST

type Rep Swizzle = D1 ('MetaData "Swizzle" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) ((C1 ('MetaCons "X" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Y" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Z" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "W" 'PrefixI 'False) (U1 :: Type -> Type)))

data NameExpr Source #

Instances

Instances details
Eq NameExpr Source # 
Instance details

Defined in Language.GLSL.AST

Show NameExpr Source # 
Instance details

Defined in Language.GLSL.AST

Generic NameExpr Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep NameExpr :: Type -> Type #

Methods

from :: NameExpr -> Rep NameExpr x #

to :: Rep NameExpr x -> NameExpr #

type Rep NameExpr Source # 
Instance details

Defined in Language.GLSL.AST

data Cast Source #

Constructors

Cast 
NoCast 

Instances

Instances details
Eq Cast Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Cast -> Cast -> Bool #

(/=) :: Cast -> Cast -> Bool #

Show Cast Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> Cast -> ShowS #

show :: Cast -> String #

showList :: [Cast] -> ShowS #

Generic Cast Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Cast :: Type -> Type #

Methods

from :: Cast -> Rep Cast x #

to :: Rep Cast x -> Cast #

type Rep Cast Source # 
Instance details

Defined in Language.GLSL.AST

type Rep Cast = D1 ('MetaData "Cast" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "Cast" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoCast" 'PrefixI 'False) (U1 :: Type -> Type))

data ExprAtom Source #

Instances

Instances details
Eq ExprAtom Source # 
Instance details

Defined in Language.GLSL.AST

Show ExprAtom Source # 
Instance details

Defined in Language.GLSL.AST

Generic ExprAtom Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep ExprAtom :: Type -> Type #

Methods

from :: ExprAtom -> Rep ExprAtom x #

to :: Rep ExprAtom x -> ExprAtom #

type Rep ExprAtom Source # 
Instance details

Defined in Language.GLSL.AST

type Rep ExprAtom = D1 ('MetaData "ExprAtom" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) ((C1 ('MetaCons "LitIntExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Cast) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "LitFloatExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Cast) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float)) :+: C1 ('MetaCons "IdentifierExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NameExpr)))) :+: (C1 ('MetaCons "SwizzleExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NameId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Swizzle)) :+: (C1 ('MetaCons "VecIndexExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NameExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Swizzle)) :+: C1 ('MetaCons "MatIndexExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NameExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Swizzle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Swizzle))))))

data Expr Source #

Instances

Instances details
Eq Expr Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

Show Expr Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Generic Expr Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Expr :: Type -> Type #

Methods

from :: Expr -> Rep Expr x #

to :: Rep Expr x -> Expr #

type Rep Expr Source # 
Instance details

Defined in Language.GLSL.AST

type Rep Expr = D1 ('MetaData "Expr" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) ((C1 ('MetaCons "UnaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UnaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExprAtom)) :+: C1 ('MetaCons "BinaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExprAtom) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BinaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExprAtom)))) :+: (C1 ('MetaCons "FunCallExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FunName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ExprAtom])) :+: (C1 ('MetaCons "TextureExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExprAtom) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExprAtom) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExprAtom))) :+: C1 ('MetaCons "AtomExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ExprAtom)))))

data BinaryOp Source #

Instances

Instances details
Eq BinaryOp Source # 
Instance details

Defined in Language.GLSL.AST

Show BinaryOp Source # 
Instance details

Defined in Language.GLSL.AST

Generic BinaryOp Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep BinaryOp :: Type -> Type #

Methods

from :: BinaryOp -> Rep BinaryOp x #

to :: Rep BinaryOp x -> BinaryOp #

type Rep BinaryOp Source # 
Instance details

Defined in Language.GLSL.AST

type Rep BinaryOp = D1 ('MetaData "BinaryOp" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (((C1 ('MetaCons "BOpPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BOpMinus" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BOpMul" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BOpDiv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BOpGE" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BOpGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BOpLE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BOpLT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BOpAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BOpOr" 'PrefixI 'False) (U1 :: Type -> Type)))))

data UnaryOp Source #

Constructors

UOpMinus 
UOpNot 

Instances

Instances details
Eq UnaryOp Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: UnaryOp -> UnaryOp -> Bool #

(/=) :: UnaryOp -> UnaryOp -> Bool #

Show UnaryOp Source # 
Instance details

Defined in Language.GLSL.AST

Generic UnaryOp Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep UnaryOp :: Type -> Type #

Methods

from :: UnaryOp -> Rep UnaryOp x #

to :: Rep UnaryOp x -> UnaryOp #

type Rep UnaryOp Source # 
Instance details

Defined in Language.GLSL.AST

type Rep UnaryOp = D1 ('MetaData "UnaryOp" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "UOpMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UOpNot" 'PrefixI 'False) (U1 :: Type -> Type))

data StmtAnnot a Source #

Constructors

SA 

Fields

Instances

Instances details
Functor StmtAnnot Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fmap :: (a -> b) -> StmtAnnot a -> StmtAnnot b #

(<$) :: a -> StmtAnnot b -> StmtAnnot a #

Applicative StmtAnnot Source # 
Instance details

Defined in Language.GLSL.AST

Methods

pure :: a -> StmtAnnot a #

(<*>) :: StmtAnnot (a -> b) -> StmtAnnot a -> StmtAnnot b #

liftA2 :: (a -> b -> c) -> StmtAnnot a -> StmtAnnot b -> StmtAnnot c #

(*>) :: StmtAnnot a -> StmtAnnot b -> StmtAnnot b #

(<*) :: StmtAnnot a -> StmtAnnot b -> StmtAnnot a #

Foldable StmtAnnot Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fold :: Monoid m => StmtAnnot m -> m #

foldMap :: Monoid m => (a -> m) -> StmtAnnot a -> m #

foldMap' :: Monoid m => (a -> m) -> StmtAnnot a -> m #

foldr :: (a -> b -> b) -> b -> StmtAnnot a -> b #

foldr' :: (a -> b -> b) -> b -> StmtAnnot a -> b #

foldl :: (b -> a -> b) -> b -> StmtAnnot a -> b #

foldl' :: (b -> a -> b) -> b -> StmtAnnot a -> b #

foldr1 :: (a -> a -> a) -> StmtAnnot a -> a #

foldl1 :: (a -> a -> a) -> StmtAnnot a -> a #

toList :: StmtAnnot a -> [a] #

null :: StmtAnnot a -> Bool #

length :: StmtAnnot a -> Int #

elem :: Eq a => a -> StmtAnnot a -> Bool #

maximum :: Ord a => StmtAnnot a -> a #

minimum :: Ord a => StmtAnnot a -> a #

sum :: Num a => StmtAnnot a -> a #

product :: Num a => StmtAnnot a -> a #

Traversable StmtAnnot Source # 
Instance details

Defined in Language.GLSL.AST

Methods

traverse :: Applicative f => (a -> f b) -> StmtAnnot a -> f (StmtAnnot b) #

sequenceA :: Applicative f => StmtAnnot (f a) -> f (StmtAnnot a) #

mapM :: Monad m => (a -> m b) -> StmtAnnot a -> m (StmtAnnot b) #

sequence :: Monad m => StmtAnnot (m a) -> m (StmtAnnot a) #

Eq a => Eq (StmtAnnot a) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: StmtAnnot a -> StmtAnnot a -> Bool #

(/=) :: StmtAnnot a -> StmtAnnot a -> Bool #

Show a => Show (StmtAnnot a) Source # 
Instance details

Defined in Language.GLSL.AST

Generic (StmtAnnot a) Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep (StmtAnnot a) :: Type -> Type #

Methods

from :: StmtAnnot a -> Rep (StmtAnnot a) x #

to :: Rep (StmtAnnot a) x -> StmtAnnot a #

type Rep (StmtAnnot a) Source # 
Instance details

Defined in Language.GLSL.AST

type Rep (StmtAnnot a) = D1 ('MetaData "StmtAnnot" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "SA" 'PrefixI 'True) (S1 ('MetaSel ('Just "annot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "unAnnot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Stmt a))))

data Stmt a Source #

Instances

Instances details
Functor Stmt Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fmap :: (a -> b) -> Stmt a -> Stmt b #

(<$) :: a -> Stmt b -> Stmt a #

Applicative Stmt Source # 
Instance details

Defined in Language.GLSL.AST

Methods

pure :: a -> Stmt a #

(<*>) :: Stmt (a -> b) -> Stmt a -> Stmt b #

liftA2 :: (a -> b -> c) -> Stmt a -> Stmt b -> Stmt c #

(*>) :: Stmt a -> Stmt b -> Stmt b #

(<*) :: Stmt a -> Stmt b -> Stmt a #

Foldable Stmt Source # 
Instance details

Defined in Language.GLSL.AST

Methods

fold :: Monoid m => Stmt m -> m #

foldMap :: Monoid m => (a -> m) -> Stmt a -> m #

foldMap' :: Monoid m => (a -> m) -> Stmt a -> m #

foldr :: (a -> b -> b) -> b -> Stmt a -> b #

foldr' :: (a -> b -> b) -> b -> Stmt a -> b #

foldl :: (b -> a -> b) -> b -> Stmt a -> b #

foldl' :: (b -> a -> b) -> b -> Stmt a -> b #

foldr1 :: (a -> a -> a) -> Stmt a -> a #

foldl1 :: (a -> a -> a) -> Stmt a -> a #

toList :: Stmt a -> [a] #

null :: Stmt a -> Bool #

length :: Stmt a -> Int #

elem :: Eq a => a -> Stmt a -> Bool #

maximum :: Ord a => Stmt a -> a #

minimum :: Ord a => Stmt a -> a #

sum :: Num a => Stmt a -> a #

product :: Num a => Stmt a -> a #

Traversable Stmt Source # 
Instance details

Defined in Language.GLSL.AST

Methods

traverse :: Applicative f => (a -> f b) -> Stmt a -> f (Stmt b) #

sequenceA :: Applicative f => Stmt (f a) -> f (Stmt a) #

mapM :: Monad m => (a -> m b) -> Stmt a -> m (Stmt b) #

sequence :: Monad m => Stmt (m a) -> m (Stmt a) #

Eq a => Eq (Stmt a) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Stmt a -> Stmt a -> Bool #

(/=) :: Stmt a -> Stmt a -> Bool #

Show a => Show (Stmt a) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> Stmt a -> ShowS #

show :: Stmt a -> String #

showList :: [Stmt a] -> ShowS #

Generic (Stmt a) Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep (Stmt a) :: Type -> Type #

Methods

from :: Stmt a -> Rep (Stmt a) x #

to :: Rep (Stmt a) x -> Stmt a #

type Rep (Stmt a) Source # 
Instance details

Defined in Language.GLSL.AST

data Emit Source #

Instances

Instances details
Eq Emit Source # 
Instance details

Defined in Language.GLSL.AST

Methods

(==) :: Emit -> Emit -> Bool #

(/=) :: Emit -> Emit -> Bool #

Show Emit Source # 
Instance details

Defined in Language.GLSL.AST

Methods

showsPrec :: Int -> Emit -> ShowS #

show :: Emit -> String #

showList :: [Emit] -> ShowS #

Generic Emit Source # 
Instance details

Defined in Language.GLSL.AST

Associated Types

type Rep Emit :: Type -> Type #

Methods

from :: Emit -> Rep Emit x #

to :: Rep Emit x -> Emit #

type Rep Emit Source # 
Instance details

Defined in Language.GLSL.AST

type Rep Emit = D1 ('MetaData "Emit" "Language.GLSL.AST" "glsl-0.0.1.1-inplace" 'False) (C1 ('MetaCons "EmitPosition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Expr)) :+: C1 ('MetaCons "EmitFragDepth" 'PrefixI 'False) (U1 :: Type -> Type))

class Annot a where Source #

Instances

Instances details
Annot () Source # 
Instance details

Defined in Language.GLSL.AST

Annot Liveness Source # 
Instance details

Defined in Language.GLSL.Optimizer.Liveness

(Annot a, Annot b) => Annot (a, b) Source # 
Instance details

Defined in Language.GLSL.AST

Methods

parseAnnot :: Parser (a, b) Source #

ppAnnot :: (a, b) -> Maybe Builder Source #