ixshader-0.0.1.0: A shallow embedding of the OpenGL Shading Language in Haskell.

Safe HaskellNone
LanguageHaskell2010

Graphics.IxShader.Qualifiers

Synopsis

Documentation

newtype Uniform typ name Source #

Constructors

Uniform 

Fields

newtype In typ name Source #

Constructors

In 

Fields

Instances

newtype Out typ name Source #

Constructors

Out 

Fields

Instances

newtype Const typ Source #

Constructors

Const 

Fields

type family ReadFrom a where ... Source #

Equations

ReadFrom (Uniform t n) = t 
ReadFrom (In t n) = t 
ReadFrom (Out t n) = Error '(Out t n, "Cannot be read.") 
ReadFrom (Const t) = t 
ReadFrom t = t 

type family WriteTo a where ... Source #

Equations

WriteTo (Uniform t n) = Error '(Uniform t n, "Cannot be written.") 
WriteTo (In t n) = Error '(In t n, "Cannot be written.") 
WriteTo (Out t n) = t 
WriteTo (Const t) = Error '(Const t, "Cannot be written.") 
WriteTo t = t 

class Cast a b where Source #

Minimal complete definition

cast

Methods

cast :: a -> b Source #

Instances

(Socketed a, Socketed (ReadFrom a), (~) * b (ReadFrom a)) => Cast a b Source # 

Methods

cast :: a -> b Source #

(+) :: Readable a b => a -> b -> ReadFrom a infixl 6 Source #

(-) :: Readable a b => a -> b -> ReadFrom a infixl 6 Source #

(*) :: Readable a b => a -> b -> ReadFrom a infixl 7 Source #

abs :: (Socketed a, Socketed (ReadFrom a)) => a -> ReadFrom a Source #

(/) :: Readable a b => a -> b -> ReadFrom a infixl 7 Source #

exp :: (Socketed a, Socketed (ReadFrom a)) => a -> ReadFrom a Source #

log :: (Socketed a, Socketed (ReadFrom a)) => a -> ReadFrom a Source #

(**) :: Readable a b => a -> b -> ReadFrom a Source #

logBase :: Readable a b => a -> b -> ReadFrom a Source #

sin :: (Socketed a, Socketed (ReadFrom a)) => a -> ReadFrom a Source #

cos :: (Socketed a, Socketed (ReadFrom a)) => a -> ReadFrom a Source #

tan :: (Socketed a, Socketed (ReadFrom a)) => a -> ReadFrom a Source #

(==) :: Readable a b => a -> b -> Xbool infix 4 Source #

(/=) :: Readable a b => a -> b -> Xbool infix 4 Source #

(<) :: Readable a b => a -> b -> Xbool infix 4 Source #

(<=) :: Readable a b => a -> b -> Xbool infix 4 Source #

(>) :: Readable a b => a -> b -> Xbool infix 4 Source #

(>=) :: Readable a b => a -> b -> Xbool infix 4 Source #

max :: Readable a b => a -> b -> ReadFrom a Source #

min :: Readable a b => a -> b -> ReadFrom a Source #

dot :: Readable a b => a -> b -> Xfloat Source #

data GLContext Source #

Some glsl evaluation contexts. This is used to choose alternate syntax in cases where shader code differs between contexts, for example the in keyword is not available on glsl bound for a webgl context, and should be replaced with attribute.

class HasContext a where Source #

An easy way to get the term level value of a type of kind GLContext.

Minimal complete definition

getCtx

uniform_ :: forall t name ts ctx. (KnownSymbol name, Socketed t, KnownTypeSymbol t) => IxShader ctx ts (ts :++ '[Uniform t name]) (Uniform t name) Source #

in_ :: forall t name ts ctx. (HasContext ctx, KnownSymbol name, Socketed t, KnownTypeSymbol t) => IxShader ctx ts (ts :++ '[In t name]) (In t name) Source #

out_ :: forall t name ts ctx. (HasContext ctx, KnownSymbol name, Socketed t, KnownTypeSymbol t) => IxShader ctx ts (ts :++ '[Out t name]) (Out t name) Source #

gl_Position :: forall ts ctx. IxShader ctx ts (ts :++ '[Out Xvec4 "gl_Position"]) (Out Xvec4 "gl_Position") Source #

type family GLFragName (a :: GLContext) where ... Source #

Equations

GLFragName OpenGLContext = "fragColor" 
GLFragName WebGLContext = "gl_FragColor" 

gl_FragColor :: forall ctx ts. (HasContext ctx, KnownSymbol (GLFragName ctx)) => IxShader ctx ts (ts :++ '[Out Xvec4 (GLFragName ctx)]) (Out Xvec4 (GLFragName ctx)) Source #