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

Safe HaskellNone
LanguageHaskell2010

Graphics.IxShader

Synopsis

Documentation

(.=) :: forall a b i ctx. (Socketed a, Socketed b, WriteTo a ~ ReadFrom b) => a -> b -> IxShader ctx i i () infixr 1 Source #

step :: (Socketed a, Socketed b, Socketed c) => a -> b -> c Source #

type family LengthOf a where ... Source #

Equations

LengthOf Xfloat = Xfloat 
LengthOf Xvec2 = Xfloat 
LengthOf Xvec3 = Xfloat 
LengthOf Xvec4 = Xfloat 
LengthOf (Uniform t n) = LengthOf t 
LengthOf (In t n) = LengthOf t 
LengthOf (Out t n) = LengthOf t 
LengthOf (Const t) = LengthOf t 
LengthOf a = Error '(a, "Cannot call length on this type.") 

type family CompCat as bs where ... Source #

Equations

CompCat as bs = VectOf (NumComps as :+ NumComps bs) (CompType as) 

(.:) :: forall a b. (KnownTypeSymbol (CompCat (ReadFrom a) (ReadFrom b)), Socketed a, Socketed b, Socketed (CompCat (ReadFrom a) (ReadFrom b))) => a -> b -> CompCat (ReadFrom a) (ReadFrom b) infixr 5 Source #

main_ :: forall ctx i a. IxShader ctx i i a -> IxShader ctx i (i :++ '[Main]) () Source #

(+=) :: Readable a b => a -> b -> ReadFrom a infixr 5 Source #

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

mod :: (Socketed a, Socketed b) => a -> b -> a Source #

at :: (Socketed a, Socketed (CompType a)) => a -> Xint -> CompType a Source #

for :: (Socketed a, KnownTypeSymbol a) => (String, a) -> (a -> (Xbool, a)) -> (a -> IxShader ctx i i b) -> IxShader ctx i i b Source #

bigfattestvertex :: forall ctx. HasContext ctx => IxShader ctx '[] '[Uniform Xvec2 "u_resolution", Out Xvec4 "gl_Position", Function Xint "myFunc" (Xint, Xint), Main] () Source #

class KnownSymbol n #

This class gives the string associated with a type-level symbol. There are instances of the class for every concrete literal: "hello", etc.

Since: 4.7.0.0

Minimal complete definition

symbolSing

(&&&) :: Arrow a => forall b c c'. a b c -> a b c' -> a b (c, c') #

Fanout: send the input to both argument arrows and combine their output.

The default definition may be overridden with a more efficient version if desired.

module Prelude