glsl-0.0.0.1: Parser and optimizer for a small subset of GLSL
Safe HaskellNone
LanguageHaskell2010

Language.GLSL.Types

Documentation

data GLSL a Source #

Constructors

GLSL Version [TopDecl a] 

Instances

Instances details
Functor GLSL Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Foldable GLSL Source # 
Instance details

Defined in Language.GLSL.Types

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.Types

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) #

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

Defined in Language.GLSL.Types

Methods

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

show :: GLSL a -> String #

showList :: [GLSL a] -> ShowS #

newtype Version Source #

Constructors

Version Int 

Instances

Instances details
Show Version Source # 
Instance details

Defined in Language.GLSL.Types

data TopDecl a Source #

Instances

Instances details
Functor TopDecl Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Foldable TopDecl Source # 
Instance details

Defined in Language.GLSL.Types

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.Types

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) #

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

Defined in Language.GLSL.Types

Methods

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

show :: TopDecl a -> String #

showList :: [TopDecl a] -> ShowS #

data ProcName Source #

Constructors

ProcMain 
ProcName NameId 

Instances

Instances details
Show ProcName Source # 
Instance details

Defined in Language.GLSL.Types

data LayoutSpec Source #

Instances

Instances details
Show LayoutSpec Source # 
Instance details

Defined in Language.GLSL.Types

data ParamDecl Source #

Constructors

Param ParamKind LocalDecl 

Instances

Instances details
Show ParamDecl Source # 
Instance details

Defined in Language.GLSL.Types

data ParamKind Source #

Constructors

PkIn 
PkOut 
PkInout 

Instances

Instances details
Show ParamKind Source # 
Instance details

Defined in Language.GLSL.Types

data LocalDecl Source #

Constructors

LDecl Type NameId (Maybe Expr) 

Instances

Instances details
Show LocalDecl Source # 
Instance details

Defined in Language.GLSL.Types

data GlobalDecl Source #

Constructors

GDecl GDeclKind Type Name 

Instances

Instances details
Show GlobalDecl Source # 
Instance details

Defined in Language.GLSL.Types

data GDeclKind Source #

Constructors

GkIn 
GkOut 
GkUniform 

Instances

Instances details
Show GDeclKind Source # 
Instance details

Defined in Language.GLSL.Types

data Type Source #

Instances

Instances details
Eq Type Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Show Type Source # 
Instance details

Defined in Language.GLSL.Types

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

newtype NameId Source #

Constructors

NameId Int 

Instances

Instances details
Eq NameId Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Show NameId Source # 
Instance details

Defined in Language.GLSL.Types

data Name Source #

Constructors

Name Namespace NameId 

Instances

Instances details
Show Name Source # 
Instance details

Defined in Language.GLSL.Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

data Namespace Source #

Constructors

NsT 
NsS 
NsU 
NsVF 
NsIn 
NsOut 

Instances

Instances details
Eq Namespace Source # 
Instance details

Defined in Language.GLSL.Types

Show Namespace Source # 
Instance details

Defined in Language.GLSL.Types

data Swizzle Source #

Constructors

X 
Y 
Z 
W 

Instances

Instances details
Eq Swizzle Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Show Swizzle Source # 
Instance details

Defined in Language.GLSL.Types

data NameExpr Source #

Instances

Instances details
Show NameExpr Source # 
Instance details

Defined in Language.GLSL.Types

data Cast Source #

Constructors

Cast 
NoCast 

Instances

Instances details
Show Cast Source # 
Instance details

Defined in Language.GLSL.Types

Methods

showsPrec :: Int -> Cast -> ShowS #

show :: Cast -> String #

showList :: [Cast] -> ShowS #

data BinaryOp Source #

Instances

Instances details
Eq BinaryOp Source # 
Instance details

Defined in Language.GLSL.Types

Show BinaryOp Source # 
Instance details

Defined in Language.GLSL.Types

data UnaryOp Source #

Constructors

UOpMinus 
UOpNot 

Instances

Instances details
Eq UnaryOp Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Show UnaryOp Source # 
Instance details

Defined in Language.GLSL.Types

data StmtAnnot a Source #

Constructors

SA 

Fields

Instances

Instances details
Functor StmtAnnot Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Applicative StmtAnnot Source # 
Instance details

Defined in Language.GLSL.Types

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.Types

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.Types

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) #

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

Defined in Language.GLSL.Types

data Stmt a Source #

Instances

Instances details
Functor Stmt Source # 
Instance details

Defined in Language.GLSL.Types

Methods

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

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

Applicative Stmt Source # 
Instance details

Defined in Language.GLSL.Types

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.Types

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.Types

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) #

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

Defined in Language.GLSL.Types

Methods

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

show :: Stmt a -> String #

showList :: [Stmt a] -> ShowS #

data Emit Source #

Instances

Instances details
Show Emit Source # 
Instance details

Defined in Language.GLSL.Types

Methods

showsPrec :: Int -> Emit -> ShowS #

show :: Emit -> String #

showList :: [Emit] -> ShowS #

ppL :: (a -> Builder) -> [a] -> Builder Source #

ppS :: Builder -> (a -> Builder) -> [a] -> Builder Source #

class Annot a where Source #

Instances

Instances details
Annot () Source # 
Instance details

Defined in Language.GLSL.Types

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.Types

Methods

parseAnnot :: Parser (a, b) Source #

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

parseTest :: Show a => Parser a -> Text -> IO () Source #

t :: Show a => Parser a -> String -> IO () Source #

pp :: (a -> Builder) -> a -> String Source #

ppl :: (a -> Builder) -> [a] -> String Source #