ombra-0.3.1.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Shader

Contents

Description

An example of shader variable:

        data Transform2 = Transform2 GMat3 deriving Generic

An example of vertex shader:

        vertexShader :: VertexShader
        -- The types of the uniforms:
                                '[Transform2, View2, Depth]
        -- The types of the attributes:
                                '[Position2, UV]
        -- The types of the varying (outputs), excluding VertexShaderOutput.
                                '[UV]
        vertexShader 
        -- Set of uniforms:
                     (Transform2 trans :- View2 view :- Depth z :- N)
        -- Set of attributes:
                     (Position2 (GVec2 x y) :- uv@(UV _) :- N) =
        -- Matrix and vector multiplication:
                        let GVec3 x' y' _ = view .*. trans .* GVec3 x y 1
        -- Set of outputs:
                        in Vertex (GVec4 x' y' z 1) -- Vertex position.
                           :- uv :- N

Synopsis

Documentation

module Data.Cross

Types

type Shader gs is os = SVList gs -> SVList is -> SVList os Source #

A function from a set of uniforms and a set of inputs (attributes or varyings) to a set of outputs (varyings). It can be used to represent a reusable piece of shader code, other than actual shaders.

type VertexShader g i o = Shader g i (VertexShaderOutput ': o) Source #

A Shader with a VertexShaderOutput output.

type FragmentShader g i = Shader g i (FragmentShaderOutput ': '[]) Source #

A Shader with only a FragmentShaderOutput output.

data VertexShaderOutput Source #

The position of the vertex.

Constructors

Vertex GVec4 

Instances

Generic VertexShaderOutput Source # 
type Rep VertexShaderOutput Source # 
type Rep VertexShaderOutput = D1 (MetaData "VertexShaderOutput" "Graphics.Rendering.Ombra.Shader.Stages" "ombra-0.3.1.0-I8WL6jt4qyYKc1kCNwFK7w" False) (C1 (MetaCons "Vertex" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GVec4)))

type ShaderVars = Set ShaderVar Source #

A type-level set of ShaderVars.

type VOShaderVars o = (ShaderVars o, ShaderVars (VertexShaderOutput ': o)) Source #

ShaderVars for the output of VartexShader.

class Generic g => Uniform s g Source #

Minimal complete definition

withUniforms

class Generic g => Attribute s g Source #

Minimal complete definition

withAttributes

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

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

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

Generic Void 

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 

Associated Types

type Rep ExitCode :: * -> * #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic IVec4 # 

Associated Types

type Rep IVec4 :: * -> * #

Methods

from :: IVec4 -> Rep IVec4 x #

to :: Rep IVec4 x -> IVec4 #

Generic IVec3 # 

Associated Types

type Rep IVec3 :: * -> * #

Methods

from :: IVec3 -> Rep IVec3 x #

to :: Rep IVec3 x -> IVec3 #

Generic IVec2 # 

Associated Types

type Rep IVec2 :: * -> * #

Methods

from :: IVec2 -> Rep IVec2 x #

to :: Rep IVec2 x -> IVec2 #

Generic Mat4 # 

Associated Types

type Rep Mat4 :: * -> * #

Methods

from :: Mat4 -> Rep Mat4 x #

to :: Rep Mat4 x -> Mat4 #

Generic Mat3 # 

Associated Types

type Rep Mat3 :: * -> * #

Methods

from :: Mat3 -> Rep Mat3 x #

to :: Rep Mat3 x -> Mat3 #

Generic Mat2 # 

Associated Types

type Rep Mat2 :: * -> * #

Methods

from :: Mat2 -> Rep Mat2 x #

to :: Rep Mat2 x -> Mat2 #

Generic Vec4 # 

Associated Types

type Rep Vec4 :: * -> * #

Methods

from :: Vec4 -> Rep Vec4 x #

to :: Rep Vec4 x -> Vec4 #

Generic Vec3 # 

Associated Types

type Rep Vec3 :: * -> * #

Methods

from :: Vec3 -> Rep Vec3 x #

to :: Rep Vec3 x -> Vec3 #

Generic Vec2 # 

Associated Types

type Rep Vec2 :: * -> * #

Methods

from :: Vec2 -> Rep Vec2 x #

to :: Rep Vec2 x -> Vec2 #

Generic VertexShaderOutput # 
Generic UV # 

Associated Types

type Rep UV :: * -> * #

Methods

from :: UV -> Rep UV x #

to :: Rep UV x -> UV #

Generic Position2 # 

Associated Types

type Rep Position2 :: * -> * #

Generic View2 # 

Associated Types

type Rep View2 :: * -> * #

Methods

from :: View2 -> Rep View2 x #

to :: Rep View2 x -> View2 #

Generic Transform2 # 

Associated Types

type Rep Transform2 :: * -> * #

Generic Depth # 

Associated Types

type Rep Depth :: * -> * #

Methods

from :: Depth -> Rep Depth x #

to :: Rep Depth x -> Depth #

Generic Image # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Generic Normal3 # 

Associated Types

type Rep Normal3 :: * -> * #

Methods

from :: Normal3 -> Rep Normal3 x #

to :: Rep Normal3 x -> Normal3 #

Generic Position3 # 

Associated Types

type Rep Position3 :: * -> * #

Generic Project3 # 

Associated Types

type Rep Project3 :: * -> * #

Methods

from :: Project3 -> Rep Project3 x #

to :: Rep Project3 x -> Project3 #

Generic View3 # 

Associated Types

type Rep View3 :: * -> * #

Methods

from :: View3 -> Rep View3 x #

to :: Rep View3 x -> View3 #

Generic Transform3 # 

Associated Types

type Rep Transform3 :: * -> * #

Generic Texture2 # 

Associated Types

type Rep Texture2 :: * -> * #

Methods

from :: Texture2 -> Rep Texture2 x #

to :: Rep Texture2 x -> Texture2 #

Generic [a] 

Associated Types

type Rep [a] :: * -> * #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

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

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

Generic (V1 p) 

Associated Types

type Rep (V1 p) :: * -> * #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p) 

Associated Types

type Rep (U1 p) :: * -> * #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (Par1 p) 

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

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

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

Generic (Min a) 

Associated Types

type Rep (Min a) :: * -> * #

Methods

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

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

Generic (Max a) 

Associated Types

type Rep (Max a) :: * -> * #

Methods

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

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

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

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

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

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

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

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

Generic (WrappedMonoid m) 

Associated Types

type Rep (WrappedMonoid m) :: * -> * #

Generic (Option a) 

Associated Types

type Rep (Option a) :: * -> * #

Methods

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

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

Generic (NonEmpty a) 

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

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

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

Generic (Complex a) 

Associated Types

type Rep (Complex a) :: * -> * #

Methods

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

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

Generic (ZipList a) 

Associated Types

type Rep (ZipList a) :: * -> * #

Methods

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

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

Generic (Dual a) 

Associated Types

type Rep (Dual a) :: * -> * #

Methods

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

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

Generic (Endo a) 

Associated Types

type Rep (Endo a) :: * -> * #

Methods

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

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

Generic (Sum a) 

Associated Types

type Rep (Sum a) :: * -> * #

Methods

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

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

Generic (Product a) 

Associated Types

type Rep (Product a) :: * -> * #

Methods

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

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

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

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

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

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

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

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

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (Rec1 f p) 

Associated Types

type Rep (Rec1 f p) :: * -> * #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec Char p) 

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p) 

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p) 

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (URec (Ptr ()) p) 

Associated Types

type Rep (URec (Ptr ()) p) :: * -> * #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (a, b) 

Associated Types

type Rep (a, b) :: * -> * #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Arg a b) 

Associated Types

type Rep (Arg a b) :: * -> * #

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (WrappedMonad m a) 

Associated Types

type Rep (WrappedMonad m a) :: * -> * #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Generic (K1 i c p) 

Associated Types

type Rep (K1 i c p) :: * -> * #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((:+:) f g p) 

Associated Types

type Rep ((:+:) f g p) :: * -> * #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((:*:) f g p) 

Associated Types

type Rep ((:*:) f g p) :: * -> * #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic ((:.:) f g p) 

Associated Types

type Rep ((:.:) f g p) :: * -> * #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c) 

Associated Types

type Rep (a, b, c) :: * -> * #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c) 

Associated Types

type Rep (WrappedArrow a b c) :: * -> * #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Const k a b) 

Associated Types

type Rep (Const k a b) :: * -> * #

Methods

from :: Const k a b -> Rep (Const k a b) x #

to :: Rep (Const k a b) x -> Const k a b #

Generic (Alt k f a) 

Associated Types

type Rep (Alt k f a) :: * -> * #

Methods

from :: Alt k f a -> Rep (Alt k f a) x #

to :: Rep (Alt k f a) x -> Alt k f a #

Generic (M1 i c f p) 

Associated Types

type Rep (M1 i c f p) :: * -> * #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic (a, b, c, d) 

Associated Types

type Rep (a, b, c, d) :: * -> * #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Sum k f g a) 

Associated Types

type Rep (Sum k f g a) :: * -> * #

Methods

from :: Sum k f g a -> Rep (Sum k f g a) x #

to :: Rep (Sum k f g a) x -> Sum k f g a #

Generic (Product k f g a) 

Associated Types

type Rep (Product k f g a) :: * -> * #

Methods

from :: Product k f g a -> Rep (Product k f g a) x #

to :: Rep (Product k f g a) x -> Product k f g a #

Generic (a, b, c, d, e) 

Associated Types

type Rep (a, b, c, d, e) :: * -> * #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (Compose k1 k f g a) 

Associated Types

type Rep (Compose k1 k f g a) :: * -> * #

Methods

from :: Compose k1 k f g a -> Rep (Compose k1 k f g a) x #

to :: Rep (Compose k1 k f g a) x -> Compose k1 k f g a #

Generic (a, b, c, d, e, f) 

Associated Types

type Rep (a, b, c, d, e, f) :: * -> * #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 

Associated Types

type Rep (a, b, c, d, e, f, g) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

data SVList :: [*] -> * where Source #

An heterogeneous list of ShaderVars.

Constructors

N :: SVList '[] 
(:-) :: ShaderVar a => a -> SVList xs -> SVList (a ': xs) infixr 4 

GPU types

data GInt Source #

A GPU integer.

data GSampler2D Source #

A GPU 2D texture handle.

data GSamplerCube Source #

A GPU cube texture handler.

data GVec2 Source #

A GPU 2D float vector.

Constructors

GVec2 GFloat GFloat 

data GVec3 Source #

A GPU 3D float vector.

Constructors

GVec3 GFloat GFloat GFloat 

data GVec4 Source #

A GPU 4D float vector.

data GBVec2 Source #

A GPU 2D boolean vector.

Constructors

GBVec2 GBool GBool 

data GBVec3 Source #

A GPU 3D boolean vector.

Constructors

GBVec3 GBool GBool GBool 

data GBVec4 Source #

A GPU 4D boolean vector.

Constructors

GBVec4 GBool GBool GBool GBool 

data GIVec2 Source #

A GPU 2D integer vector.

Constructors

GIVec2 GInt GInt 

data GIVec3 Source #

A GPU 3D integer vector.

Constructors

GIVec3 GInt GInt GInt 

data GIVec4 Source #

A GPU 4D integer vector.

Constructors

GIVec4 GInt GInt GInt GInt 

data GMat2 Source #

A GPU 2x2 float matrix.

Constructors

GMat2 GVec2 GVec2 

Instances

data GMat3 Source #

A GPU 3x3 float matrix.

Constructors

GMat3 GVec3 GVec3 GVec3 

Instances

data GMat4 Source #

A GPU 4x4 float matrix.

Constructors

GMat4 GVec4 GVec4 GVec4 GVec4 

Instances

data GArray n t Source #

A GPU array.

Instances

type BooleanOf (GArray n t) # 
type BooleanOf (GArray n t) = GBool

GPU functions

(!) :: (ShaderType t, KnownNat n) => GArray n t -> GInt -> t Source #

loop Source #

Arguments

:: ShaderType a 
=> Int

Maximum number of iterations (should be as low as possible)

-> a

Initial value

-> (GInt -> a -> (a, GBool))

Iteration -> Old value -> (Next, Stop)

-> a 

store :: ShaderType a => a -> a Source #

Avoid evaluating the expression of the argument more than one time. Conditionals and loops imply it.

arrayLength :: (ShaderType t, KnownNat n) => GArray n t -> GInt Source #

Various math functions

class Matrix a where Source #

Minimal complete definition

idmtx, transpose, (.*.), (.*)

Associated Types

type Row a = b | b -> a Source #

Methods

idmtx :: a Source #

transpose :: a -> a Source #

(.*.) :: a -> a -> a infixl 7 Source #

(.*) :: a -> Row a -> Row a infixl 7 Source #

(*.) :: Row a -> a -> Row a infixr 7 Source #

Instances

Matrix Mat4 Source # 

Associated Types

type Row Mat4 = (b :: *) Source #

Matrix Mat3 Source # 

Associated Types

type Row Mat3 = (b :: *) Source #

Matrix Mat2 Source # 

Associated Types

type Row Mat2 = (b :: *) Source #

class VectorSpace v => Ext v where Source #

Minimal complete definition

(^|), (^|^), extract

Associated Types

type Extended v = w | w -> v Source #

Methods

(^|) :: v -> Scalar v -> Extended v infixl 5 Source #

Extend the vector with a specified scalar.

(^|^) :: v -> Extended v -> Extended v infixl 5 Source #

Extend the first vector using the components of the second vector.

For instance: Mat2 (Vec2 x y) (Vec2 z w) ^|^ idmtx = Mat3 (Vec3 x y 0) (Vec3 z w 0) (Vec3 0 0 1)

extract :: Extended v -> v Source #

Extract a smaller vector.

minG :: GenTypeGFloat a b => a -> b -> a Source #

Faster GPU 'min'/'B.minB'.

maxG :: GenTypeGFloat a b => a -> b -> a Source #

Faster GPU 'max'/'B.maxB'.

modG :: GenType a => a -> a -> a Source #

GPU mod that can be used on floats and float vectors.

floorG :: GenType a => a -> a Source #

ceilingG :: GenType a => a -> a Source #

radians :: GenType a => a -> a Source #

degrees :: GenType a => a -> a Source #

exp2 :: GenType a => a -> a Source #

log2 :: GenType a => a -> a Source #

inversesqrt :: GenType a => a -> a Source #

fract :: GenType a => a -> a Source #

clamp :: GenTypeGFloat a b => a -> b -> b -> a Source #

mix :: GenTypeGFloat a b => a -> a -> b -> a Source #

step :: GenTypeGFloat a b => b -> a -> a Source #

smoothstep :: GenTypeGFloat a b => b -> b -> a -> a Source #

distance :: GenType a => a -> a -> GFloat Source #

faceforward :: GenType a => a -> a -> a -> a Source #

reflect :: GenType a => a -> a -> a Source #

refract :: GenType a => a -> a -> GFloat -> a Source #

matrixCompMult :: (GMatrix a, GMatrix b, GMatrix c) => a -> b -> c Source #

dFdx :: GenType a => a -> a Source #

Partial derivative of the argument with respect to the window X coordinate.

dFdy :: GenType a => a -> a Source #

Partial derivative of the argument with respect to the window Y coordinate.

fwidth :: GenType a => a -> a Source #

Sum of the absolute values of dFdx and dFdy.

Vector relational functions

lessThan :: VecOrd a => a -> a -> GBool Source #

lessThanEqual :: VecOrd a => a -> a -> GBool Source #

greaterThan :: VecOrd a => a -> a -> GBool Source #

equal :: VecEq a => a -> a -> GBool Source #

notEqual :: VecEq a => a -> a -> GBool Source #

Constructors

class ShaderType t => ToGBool t Source #

bool :: ToGBool t => t -> GBool Source #

class ShaderType t => ToGInt t Source #

int :: ToGInt t => t -> GInt Source #

class ShaderType t => ToGFloat t Source #

Other

position :: GVec4 Source #

The position of the vertex (only works in the vertex shader).

fragData :: GArray 16 GVec4 Source #

The data of the fragment (only works in the fragment shader).

fragCoord :: GVec4 Source #

The coordinates of the fragment (only works in the fragment shader).

fragFrontFacing :: GBool Source #

If the fragment belongs to a front-facing primitive (only works in the fragment shader).

Common shader variables

data UV Source #

Constructors

UV GVec2 

Instances

Generic UV Source # 

Associated Types

type Rep UV :: * -> * #

Methods

from :: UV -> Rep UV x #

to :: Rep UV x -> UV #

type Rep UV Source # 
type Rep UV = D1 (MetaData "UV" "Graphics.Rendering.Ombra.Shader" "ombra-0.3.1.0-I8WL6jt4qyYKc1kCNwFK7w" False) (C1 (MetaCons "UV" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GVec2)))

Orphan instances

Floating GFloat Source # 
Fractional GFloat Source # 
Num GInt Source # 

Methods

(+) :: GInt -> GInt -> GInt #

(-) :: GInt -> GInt -> GInt #

(*) :: GInt -> GInt -> GInt #

negate :: GInt -> GInt #

abs :: GInt -> GInt #

signum :: GInt -> GInt #

fromInteger :: Integer -> GInt #

Num GFloat Source # 
NumB GInt Source # 

Associated Types

type IntegerOf GInt :: * #

NumB GFloat Source # 

Associated Types

type IntegerOf GFloat :: * #

IntegralB GInt Source # 

Methods

quot :: GInt -> GInt -> GInt #

rem :: GInt -> GInt -> GInt #

div :: GInt -> GInt -> GInt #

mod :: GInt -> GInt -> GInt #

quotRem :: GInt -> GInt -> (GInt, GInt) #

divMod :: GInt -> GInt -> (GInt, GInt) #

toIntegerB :: GInt -> IntegerOf GInt #

RealFracB GFloat Source # 
RealFloatB GFloat Source # 
Boolean GBool Source # 

Methods

true :: GBool #

false :: GBool #

notB :: GBool -> GBool #

(&&*) :: GBool -> GBool -> GBool #

(||*) :: GBool -> GBool -> GBool #

(ShaderType a, (~) * (BooleanOf a) GBool) => IfB a Source # 

Methods

ifB :: (* ~ bool) (BooleanOf a) => bool -> a -> a -> a #

(ShaderType a, (~) * (BooleanOf a) GBool) => EqB a Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf a) => a -> a -> bool #

(/=*) :: (* ~ bool) (BooleanOf a) => a -> a -> bool #

(ShaderType a, (~) * (BooleanOf a) GBool) => OrdB a Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf a) => a -> a -> bool #

(<=*) :: (* ~ bool) (BooleanOf a) => a -> a -> bool #

(>*) :: (* ~ bool) (BooleanOf a) => a -> a -> bool #

(>=*) :: (* ~ bool) (BooleanOf a) => a -> a -> bool #

HasCross3 GVec3 Source # 

Methods

cross3 :: GVec3 -> GVec3 -> GVec3 #

VectorSpace GMat4 Source # 

Associated Types

type Scalar GMat4 :: * #

Methods

(*^) :: Scalar GMat4 -> GMat4 -> GMat4 #

VectorSpace GMat3 Source # 

Associated Types

type Scalar GMat3 :: * #

Methods

(*^) :: Scalar GMat3 -> GMat3 -> GMat3 #

VectorSpace GMat2 Source # 

Associated Types

type Scalar GMat2 :: * #

Methods

(*^) :: Scalar GMat2 -> GMat2 -> GMat2 #

VectorSpace GVec4 Source # 

Associated Types

type Scalar GVec4 :: * #

Methods

(*^) :: Scalar GVec4 -> GVec4 -> GVec4 #

VectorSpace GVec3 Source # 

Associated Types

type Scalar GVec3 :: * #

Methods

(*^) :: Scalar GVec3 -> GVec3 -> GVec3 #

VectorSpace GVec2 Source # 

Associated Types

type Scalar GVec2 :: * #

Methods

(*^) :: Scalar GVec2 -> GVec2 -> GVec2 #

InnerSpace GVec4 Source # 

Methods

(<.>) :: GVec4 -> GVec4 -> Scalar GVec4 #

InnerSpace GVec3 Source # 

Methods

(<.>) :: GVec3 -> GVec3 -> Scalar GVec3 #

InnerSpace GVec2 Source # 

Methods

(<.>) :: GVec2 -> GVec2 -> Scalar GVec2 #

AdditiveGroup GMat4 Source # 
AdditiveGroup GMat3 Source # 
AdditiveGroup GMat2 Source # 
AdditiveGroup GVec4 Source # 
AdditiveGroup GVec3 Source # 
AdditiveGroup GVec2 Source # 
AdditiveGroup GFloat Source # 
Matrix GMat4 Source # 

Associated Types

type Row GMat4 = (b :: *) Source #

Matrix GMat3 Source # 

Associated Types

type Row GMat3 = (b :: *) Source #

Matrix GMat2 Source # 

Associated Types

type Row GMat2 = (b :: *) Source #

Ext GMat3 Source # 
Ext GMat2 Source # 
Ext GVec3 Source # 
Ext GVec2 Source #