ombra-1.1.0.0: Render engine.

LicenseBSD3
Maintainerziocroc@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Shader.Language

Contents

Description

This module exports the shader EDSL.

Synopsis

Documentation

Types

GPU types

data GBool Source #

A GPU boolean.

Instances

ToGFloat GBool Source # 
ToGBool GBool Source # 
ToGInt GBool Source # 
GLES => GeometryVertex GBool Source # 

Associated Types

type AttributeTypes GBool :: [*] Source #

type Vertex GBool = (v :: *) Source #

GLES => Uniform GBool Source # 

Associated Types

type CPUUniform GBool :: * Source #

Methods

foldrUniform :: Proxy * GBool -> (UniformValue -> b -> b) -> b -> CPUUniform GBool -> b Source #

ShaderInput GBool Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBool, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBool -> b Source #

MultiShaderType GBool Source # 

Associated Types

type ExprMST GBool :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBool -> GBool Source #

toExprMST :: GBool -> ExprMST GBool Source #

fromExprMST :: ExprMST GBool -> GBool Source #

type BooleanOf GBool # 
data (:->:) GBool # 
type AttributeTypes GBool Source # 
type AttributeTypes GBool = (:) * GBool ([] *)
type Vertex GBool Source # 
type CPUUniform GBool Source # 
type ExprMST GBool Source # 

data GFloat Source #

A GPU 32-bit float.

Instances

ToGFloat GFloat Source # 
ToGBool GFloat Source # 
ToGInt GFloat Source # 
GenType GFloat Source # 
GLES => GeometryVertex GFloat Source # 

Associated Types

type AttributeTypes GFloat :: [*] Source #

type Vertex GFloat = (v :: *) Source #

FragmentShaderOutput GFloat Source # 

Associated Types

type NFloats GFloat :: Nat Source #

GLES => Uniform GFloat Source # 

Associated Types

type CPUUniform GFloat :: * Source #

Methods

foldrUniform :: Proxy * GFloat -> (UniformValue -> b -> b) -> b -> CPUUniform GFloat -> b Source #

ShaderInput GFloat Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GFloat, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GFloat -> b Source #

MultiShaderType GFloat Source # 

Associated Types

type ExprMST GFloat :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GFloat -> GFloat Source #

toExprMST :: GFloat -> ExprMST GFloat Source #

fromExprMST :: ExprMST GFloat -> GFloat Source #

type IntegerOf GFloat # 
type BooleanOf GFloat # 
data (:->:) GFloat # 
type AttributeTypes GFloat Source # 
type AttributeTypes GFloat = (:) * GFloat ([] *)
type Vertex GFloat Source # 
type NFloats GFloat Source # 
type NFloats GFloat = 1
type CPUUniform GFloat Source # 
type ExprMST GFloat Source # 

data GInt Source #

A GPU 32-bit integer.

Instances

ToGFloat GInt Source # 
ToGBool GInt Source # 
ToGInt GInt Source # 
GLES => GeometryVertex GInt Source # 

Associated Types

type AttributeTypes GInt :: [*] Source #

type Vertex GInt = (v :: *) Source #

GLES => Uniform GInt Source # 

Associated Types

type CPUUniform GInt :: * Source #

Methods

foldrUniform :: Proxy * GInt -> (UniformValue -> b -> b) -> b -> CPUUniform GInt -> b Source #

ShaderInput GInt Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GInt, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GInt -> b Source #

MultiShaderType GInt Source # 

Associated Types

type ExprMST GInt :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GInt -> GInt Source #

toExprMST :: GInt -> ExprMST GInt Source #

fromExprMST :: ExprMST GInt -> GInt Source #

type IntegerOf GInt # 
type BooleanOf GInt # 
data (:->:) GInt # 
type AttributeTypes GInt Source # 
type AttributeTypes GInt = (:) * GInt ([] *)
type Vertex GInt Source # 
type CPUUniform GInt Source # 
type ExprMST GInt Source # 

type TextureSampler = GSampler2D Source #

data GVec2 Source #

A GPU 2D float vector.

Constructors

GVec2 GFloat GFloat 

Instances

VecEq GVec2 Source # 
VecOrd GVec2 Source # 
GLES => GeometryVertex GVec2 Source # 

Associated Types

type AttributeTypes GVec2 :: [*] Source #

type Vertex GVec2 = (v :: *) Source #

FragmentShaderOutput GVec2 Source # 

Associated Types

type NFloats GVec2 :: Nat Source #

GLES => Uniform GVec2 Source # 

Associated Types

type CPUUniform GVec2 :: * Source #

Methods

foldrUniform :: Proxy * GVec2 -> (UniformValue -> b -> b) -> b -> CPUUniform GVec2 -> b Source #

ShaderInput GVec2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GVec2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GVec2 -> b Source #

MultiShaderType GVec2 Source # 

Associated Types

type ExprMST GVec2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GVec2 -> GVec2 Source #

toExprMST :: GVec2 -> ExprMST GVec2 Source #

fromExprMST :: ExprMST GVec2 -> GVec2 Source #

type BooleanOf GVec2 # 
data (:->:) GVec2 # 
type Scalar GVec2 # 
type Extended GVec2 Source # 
type AttributeTypes GVec2 Source # 
type AttributeTypes GVec2 = (:) * GVec2 ([] *)
type Vertex GVec2 Source # 
type NFloats GVec2 Source # 
type NFloats GVec2 = 2
type CPUUniform GVec2 Source # 
type ExprMST GVec2 Source # 

data GVec3 Source #

A GPU 3D float vector.

Constructors

GVec3 GFloat GFloat GFloat 

Instances

VecEq GVec3 Source # 
VecOrd GVec3 Source # 
GLES => GeometryVertex GVec3 Source # 

Associated Types

type AttributeTypes GVec3 :: [*] Source #

type Vertex GVec3 = (v :: *) Source #

FragmentShaderOutput GVec3 Source # 

Associated Types

type NFloats GVec3 :: Nat Source #

GLES => Uniform GVec3 Source # 

Associated Types

type CPUUniform GVec3 :: * Source #

Methods

foldrUniform :: Proxy * GVec3 -> (UniformValue -> b -> b) -> b -> CPUUniform GVec3 -> b Source #

ShaderInput GVec3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GVec3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GVec3 -> b Source #

MultiShaderType GVec3 Source # 

Associated Types

type ExprMST GVec3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GVec3 -> GVec3 Source #

toExprMST :: GVec3 -> ExprMST GVec3 Source #

fromExprMST :: ExprMST GVec3 -> GVec3 Source #

type BooleanOf GVec3 # 
data (:->:) GVec3 # 
type Scalar GVec3 # 
type Extended GVec3 Source # 
type AttributeTypes GVec3 Source # 
type AttributeTypes GVec3 = (:) * GVec3 ([] *)
type Vertex GVec3 Source # 
type NFloats GVec3 Source # 
type NFloats GVec3 = 3
type CPUUniform GVec3 Source # 
type ExprMST GVec3 Source # 

data GVec4 Source #

A GPU 4D float vector.

Instances

VecEq GVec4 Source # 
VecOrd GVec4 Source # 
GLES => GeometryVertex GVec4 Source # 

Associated Types

type AttributeTypes GVec4 :: [*] Source #

type Vertex GVec4 = (v :: *) Source #

FragmentShaderOutput GVec4 Source # 

Associated Types

type NFloats GVec4 :: Nat Source #

GLES => Uniform GVec4 Source # 

Associated Types

type CPUUniform GVec4 :: * Source #

Methods

foldrUniform :: Proxy * GVec4 -> (UniformValue -> b -> b) -> b -> CPUUniform GVec4 -> b Source #

ShaderInput GVec4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GVec4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GVec4 -> b Source #

MultiShaderType GVec4 Source # 

Associated Types

type ExprMST GVec4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GVec4 -> GVec4 Source #

toExprMST :: GVec4 -> ExprMST GVec4 Source #

fromExprMST :: ExprMST GVec4 -> GVec4 Source #

GLES => MonadRead GVec4 Draw Source # 
type BooleanOf GVec4 # 
data (:->:) GVec4 # 
type Scalar GVec4 # 
type AttributeTypes GVec4 Source # 
type AttributeTypes GVec4 = (:) * GVec4 ([] *)
type Vertex GVec4 Source # 
type NFloats GVec4 Source # 
type NFloats GVec4 = 4
type CPUUniform GVec4 Source # 
type ExprMST GVec4 Source # 

data GBVec2 Source #

A GPU 2D boolean vector.

Constructors

GBVec2 GBool GBool 

Instances

GBoolVector GBVec2 Source # 
VecEq GBVec2 Source # 
GLES => Uniform GBVec2 Source # 

Associated Types

type CPUUniform GBVec2 :: * Source #

Methods

foldrUniform :: Proxy * GBVec2 -> (UniformValue -> b -> b) -> b -> CPUUniform GBVec2 -> b Source #

ShaderInput GBVec2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBVec2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBVec2 -> b Source #

MultiShaderType GBVec2 Source # 

Associated Types

type ExprMST GBVec2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBVec2 -> GBVec2 Source #

toExprMST :: GBVec2 -> ExprMST GBVec2 Source #

fromExprMST :: ExprMST GBVec2 -> GBVec2 Source #

type BooleanOf GBVec2 # 
data (:->:) GBVec2 # 
type CPUUniform GBVec2 Source # 
type ExprMST GBVec2 Source # 

data GBVec3 Source #

A GPU 3D boolean vector.

Constructors

GBVec3 GBool GBool GBool 

Instances

GBoolVector GBVec3 Source # 
VecEq GBVec3 Source # 
GLES => Uniform GBVec3 Source # 

Associated Types

type CPUUniform GBVec3 :: * Source #

Methods

foldrUniform :: Proxy * GBVec3 -> (UniformValue -> b -> b) -> b -> CPUUniform GBVec3 -> b Source #

ShaderInput GBVec3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBVec3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBVec3 -> b Source #

MultiShaderType GBVec3 Source # 

Associated Types

type ExprMST GBVec3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBVec3 -> GBVec3 Source #

toExprMST :: GBVec3 -> ExprMST GBVec3 Source #

fromExprMST :: ExprMST GBVec3 -> GBVec3 Source #

type BooleanOf GBVec3 # 
data (:->:) GBVec3 # 
type CPUUniform GBVec3 Source # 
type ExprMST GBVec3 Source # 

data GBVec4 Source #

A GPU 4D boolean vector.

Constructors

GBVec4 GBool GBool GBool GBool 

Instances

GBoolVector GBVec4 Source # 
VecEq GBVec4 Source # 
GLES => Uniform GBVec4 Source # 

Associated Types

type CPUUniform GBVec4 :: * Source #

Methods

foldrUniform :: Proxy * GBVec4 -> (UniformValue -> b -> b) -> b -> CPUUniform GBVec4 -> b Source #

ShaderInput GBVec4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBVec4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBVec4 -> b Source #

MultiShaderType GBVec4 Source # 

Associated Types

type ExprMST GBVec4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBVec4 -> GBVec4 Source #

toExprMST :: GBVec4 -> ExprMST GBVec4 Source #

fromExprMST :: ExprMST GBVec4 -> GBVec4 Source #

type BooleanOf GBVec4 # 
data (:->:) GBVec4 # 
type CPUUniform GBVec4 Source # 
type ExprMST GBVec4 Source # 

data GIVec2 Source #

A GPU 2D integer vector.

Constructors

GIVec2 GInt GInt 

Instances

VecEq GIVec2 Source # 
VecOrd GIVec2 Source # 
GLES => GeometryVertex GIVec2 Source # 

Associated Types

type AttributeTypes GIVec2 :: [*] Source #

type Vertex GIVec2 = (v :: *) Source #

GLES => Uniform GIVec2 Source # 

Associated Types

type CPUUniform GIVec2 :: * Source #

Methods

foldrUniform :: Proxy * GIVec2 -> (UniformValue -> b -> b) -> b -> CPUUniform GIVec2 -> b Source #

ShaderInput GIVec2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GIVec2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GIVec2 -> b Source #

MultiShaderType GIVec2 Source # 

Associated Types

type ExprMST GIVec2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GIVec2 -> GIVec2 Source #

toExprMST :: GIVec2 -> ExprMST GIVec2 Source #

fromExprMST :: ExprMST GIVec2 -> GIVec2 Source #

type BooleanOf GIVec2 # 
data (:->:) GIVec2 # 
type AttributeTypes GIVec2 Source # 
type AttributeTypes GIVec2 = (:) * GIVec2 ([] *)
type Vertex GIVec2 Source # 
type CPUUniform GIVec2 Source # 
type ExprMST GIVec2 Source # 

data GIVec3 Source #

A GPU 3D integer vector.

Constructors

GIVec3 GInt GInt GInt 

Instances

VecEq GIVec3 Source # 
VecOrd GIVec3 Source # 
GLES => GeometryVertex GIVec3 Source # 

Associated Types

type AttributeTypes GIVec3 :: [*] Source #

type Vertex GIVec3 = (v :: *) Source #

GLES => Uniform GIVec3 Source # 

Associated Types

type CPUUniform GIVec3 :: * Source #

Methods

foldrUniform :: Proxy * GIVec3 -> (UniformValue -> b -> b) -> b -> CPUUniform GIVec3 -> b Source #

ShaderInput GIVec3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GIVec3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GIVec3 -> b Source #

MultiShaderType GIVec3 Source # 

Associated Types

type ExprMST GIVec3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GIVec3 -> GIVec3 Source #

toExprMST :: GIVec3 -> ExprMST GIVec3 Source #

fromExprMST :: ExprMST GIVec3 -> GIVec3 Source #

type BooleanOf GIVec3 # 
data (:->:) GIVec3 # 
type AttributeTypes GIVec3 Source # 
type AttributeTypes GIVec3 = (:) * GIVec3 ([] *)
type Vertex GIVec3 Source # 
type CPUUniform GIVec3 Source # 
type ExprMST GIVec3 Source # 

data GIVec4 Source #

A GPU 4D integer vector.

Constructors

GIVec4 GInt GInt GInt GInt 

Instances

VecEq GIVec4 Source # 
VecOrd GIVec4 Source # 
GLES => GeometryVertex GIVec4 Source # 

Associated Types

type AttributeTypes GIVec4 :: [*] Source #

type Vertex GIVec4 = (v :: *) Source #

GLES => Uniform GIVec4 Source # 

Associated Types

type CPUUniform GIVec4 :: * Source #

Methods

foldrUniform :: Proxy * GIVec4 -> (UniformValue -> b -> b) -> b -> CPUUniform GIVec4 -> b Source #

ShaderInput GIVec4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GIVec4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GIVec4 -> b Source #

MultiShaderType GIVec4 Source # 

Associated Types

type ExprMST GIVec4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GIVec4 -> GIVec4 Source #

toExprMST :: GIVec4 -> ExprMST GIVec4 Source #

fromExprMST :: ExprMST GIVec4 -> GIVec4 Source #

type BooleanOf GIVec4 # 
data (:->:) GIVec4 # 
type AttributeTypes GIVec4 Source # 
type AttributeTypes GIVec4 = (:) * GIVec4 ([] *)
type Vertex GIVec4 Source # 
type CPUUniform GIVec4 Source # 
type ExprMST GIVec4 Source # 

data GMat2 Source #

A GPU 2x2 float matrix.

Constructors

GMat2 GVec2 GVec2 

Instances

GLES => Uniform GMat2 Source # 

Associated Types

type CPUUniform GMat2 :: * Source #

Methods

foldrUniform :: Proxy * GMat2 -> (UniformValue -> b -> b) -> b -> CPUUniform GMat2 -> b Source #

ShaderInput GMat2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GMat2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GMat2 -> b Source #

MultiShaderType GMat2 Source # 

Associated Types

type ExprMST GMat2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GMat2 -> GMat2 Source #

toExprMST :: GMat2 -> ExprMST GMat2 Source #

fromExprMST :: ExprMST GMat2 -> GMat2 Source #

type BooleanOf GMat2 # 
data (:->:) GMat2 # 
type Scalar GMat2 # 
type Row GMat2 Source # 
type Row GMat2 = GVec2
type Extended GMat2 Source # 
type CPUUniform GMat2 Source # 
type ExprMST GMat2 Source # 

data GMat3 Source #

A GPU 3x3 float matrix.

Constructors

GMat3 GVec3 GVec3 GVec3 

Instances

GLES => Uniform GMat3 Source # 

Associated Types

type CPUUniform GMat3 :: * Source #

Methods

foldrUniform :: Proxy * GMat3 -> (UniformValue -> b -> b) -> b -> CPUUniform GMat3 -> b Source #

ShaderInput GMat3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GMat3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GMat3 -> b Source #

MultiShaderType GMat3 Source # 

Associated Types

type ExprMST GMat3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GMat3 -> GMat3 Source #

toExprMST :: GMat3 -> ExprMST GMat3 Source #

fromExprMST :: ExprMST GMat3 -> GMat3 Source #

type BooleanOf GMat3 # 
data (:->:) GMat3 # 
type Scalar GMat3 # 
type Row GMat3 Source # 
type Row GMat3 = GVec3
type Extended GMat3 Source # 
type CPUUniform GMat3 Source # 
type ExprMST GMat3 Source # 

data GMat4 Source #

A GPU 4x4 float matrix.

Constructors

GMat4 GVec4 GVec4 GVec4 GVec4 

Instances

GLES => Uniform GMat4 Source # 

Associated Types

type CPUUniform GMat4 :: * Source #

Methods

foldrUniform :: Proxy * GMat4 -> (UniformValue -> b -> b) -> b -> CPUUniform GMat4 -> b Source #

ShaderInput GMat4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GMat4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GMat4 -> b Source #

MultiShaderType GMat4 Source # 

Associated Types

type ExprMST GMat4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GMat4 -> GMat4 Source #

toExprMST :: GMat4 -> ExprMST GMat4 Source #

fromExprMST :: ExprMST GMat4 -> GMat4 Source #

type BooleanOf GMat4 # 
data (:->:) GMat4 # 
type Scalar GMat4 # 
type Row GMat4 Source # 
type Row GMat4 = GVec4
type CPUUniform GMat4 Source # 
type ExprMST GMat4 Source # 

class ShaderType a => GenType a Source #

GFloats or float vectors.

Instances

(GFloatVec a, ShaderType a) => GenType a Source # 
GenType GFloat Source # 

type GenTypeGFloat a b = (GenTypeGFloatConstr a b, ShaderType a, ShaderType b) Source #

a must be a GenType, while b can either be the same as a, or a GFloat.

data GArray n t Source #

A GPU array.

Instances

(KnownNat n, ShaderType t, BaseUniform (GArray n t), GLES) => Uniform (GArray n t) Source # 

Associated Types

type CPUUniform (GArray n t) :: * Source #

Methods

foldrUniform :: Proxy * (GArray n t) -> (UniformValue -> b -> b) -> b -> CPUUniform (GArray n t) -> b Source #

(KnownNat n, ShaderType t) => ShaderInput (GArray n t) Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GArray n t, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GArray n t -> b Source #

(KnownNat n, ShaderType t) => MultiShaderType (GArray n t) Source # 

Associated Types

type ExprMST (GArray n t) :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GArray n t -> GArray n t Source #

toExprMST :: GArray n t -> ExprMST (GArray n t) Source #

fromExprMST :: ExprMST (GArray n t) -> GArray n t Source #

type BooleanOf (GArray n t) # 
type BooleanOf (GArray n t) = GBool
data (:->:) (GArray n t) # 
data (:->:) (GArray n t) = GArrayTrie ((:->:) (ExprMST (GArray n t)) b)
type CPUUniform (GArray n t) Source # 
type CPUUniform (GArray n t)
type ExprMST (GArray n t) Source # 
type ExprMST (GArray n t)

GPU functions

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

Access an array element at a given index.

sampleTexture :: TextureSampler -> GVec2 -> GVec4 Source #

Sample a texel from a texture. Sampling in the vertex shader is not supported on some hardware.

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 #

Linear interpolation between two values.

mix x y t = x*(1-t) + y*t

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

step e x returns 0 if x < e, 1 otherwise.

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 => a -> a -> a Source #

Component-wise multiplication of matrices.

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

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 #