HaGL-0.1.0.0: Haskell-embedded OpenGL
Copyright(c) Simeon Krastnikov 2022-2023
LicenseMIT
MaintainerSimeon Krastnikov <skrastnikov@gmail.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.HaGL

Description

This module exports everything that comprises the core language.

It is best used with the following extensions enabled: GADTs, DataKinds, ViewPatterns, FlexibleContexts.

Note that quite a few of the exported functions clash with unrelated ones from Prelude (max, length, mod, any, etc.) or class methods with identical behaviour (abs, sin, etc.), in an effort to prioritize consistency with GLSL function naming.

In summary, this module can be imported as follows:

    {-# LANGUAGE GADTs #-}
    {-# LANGUAGE DataKinds #-}
    {-# LANGUAGE ViewPatterns #-}
    {-# LANGUAGE FlexibleContexts #-}

    import Prelude hiding (max, sin, cos, ...)

    import Graphics.HaGL

HaGL expressions have the type GLExpr (d :: GLDomain) t, where d is the domain of computation and t is the underlying numeric type, which is always an instance of GLType. Here are some example expressions:

    -- A vertex attribute constructed from its input values on three vertices
    x :: GLExpr VertexDomain Float
    x = vert [-1, 0, 1]

    -- Numeric operators and functions like (+) and sin can handle generic
    -- expressions. Note that in this example the domain of the inputs to
    -- these functions is VertexDomain, so we know that these functions will 
    -- be computed in a vertex shader.
    y :: GLExpr VertexDomain Float
    y = sin (2 * x + 1)

    -- 'frag x' is a a fragment variable corresponding to an interpolation of
    -- the value of x at the vertices that define its containing primitive.
    -- Because it has the type 'GLExpr FragmentDomain Float', the addition
    -- below will be computed in a fragment shader.
    z :: GLExpr FragmentDomain Float
    z = frag x + 3

    -- 'time' is a built-in I/O variable and as such it is computed on the CPU
    time :: GLExpr HostDomain Float

    -- We can use 'uniform' to lift a host variable to an arbitrary domain
    -- Here 'uniform time' is inferred to have type 'GLExpr VertexDomain Float':
    yPlusTime :: GLExpr VertexDomain Float
    yPlusTime = y + uniform time

    -- Here 'uniform time' is inferred to be of type 'GLExpr FragmentDomain Float':
    zPlusTime :: GLExpr FragmentDomain Float
    zPlusTime = z + uniform time

    -- A generic floating-point vector of length 4
    v :: GLExpr d (Vec 4 Float)
    v = vec4 1 1 1 1

    -- A vector can be initialized from a numeric literal, so long as its
    -- underlying type 'Vec n t' is specified or can be inferred.
    -- Here is another way to define the same vector v:
    v' :: GLExpr d (Vec 4 Float)
    v' = 1

    -- Matrices are constructed from their columns:
    m :: GLExpr d (Mat 2 3 Float)
    m = mat2x3 (vec2 1 2) (vec2 3 4) (vec2 5 6)

    -- Operators like (.+) and (.*) act component-wise on vectors and matrices:
    _ = m .+ m .== mat2x3 (vec2 2 4) (vec2 6 8) (vec2 10 12)

    -- Non-boolean primitives and vectors over such types are instances of Num;
    -- in such cases Num methods like (+) can be used instead.
    _ = vec2 1 1 + 1 .== vec2 2 2

    -- The operator (.#) performs scalar multiplication:
    _ = 3 .# v
    _ = 3 .# m

    -- The operator (.@) performs matrix multiplication
    -- (including matrix-vector multiplication):
    m1 :: GLExpr d (Mat 2 3 Float)
    m1 = ...
    m2 :: GLExpr d (Mat 3 4 Float)
    m2 = ...
    m1m2 :: GLExpr d (Mat 2 4 Float)
    m1m2 = m1 .@ m2

    -- All multiplications here will take place in a vertex shader:
    m1m2v :: GLExpr VertexDomain (Vec 2 Float)
    m1m2v = m1m2 .@ v

    -- The inferred type of m1m2 in this expression is 
    -- 'GLExpr HostDomain (Mat 2 4 Float)' so the multiplication of m1 and m2 
    -- will take place on the CPU.
    -- The inferred type of uniform m1m2 is 'GLExpr VertexDomain (Mat 2 4 Float)'
    -- and that of v is 'GLExpr VertexDomain (Vec 2 Float)' so their
    -- multiplication will take place in a vertex shader.
    m1m2v' :: GLExpr VertexDomain (Vec 2 Float)
    m1m2v' = uniform m1m2 .@ v

GLExprs can be used to construct GLObjs, which being instances of Drawable can be interpreted by a given Backend using draw. For example:

-- initialize pos from the vertices of some 3D object
pos :: GLExpr VertexDomain (Vec 4 Float)
pos = vert [vec4 1 0 0 1, ...]

red :: GLExpr FragmentDomain (Vec 4 Float)
red = vec4 1 0 0 1

redObj :: GLObj
redObj = GLObj {
    primitiveMode = TriangleStrip,
    indices = Nothing,
    position = pos,
    color = red,
    discardWhen = False
}

-- or equivalently,
redObj' :: GLObj
redObj' = triangleStrip { position = pos, color = red }

-- we can now draw the object
main :: IO ()
main = draw GlutBackend redObj

A complete set of examples explained in more depth can be found in the "Getting Started" guide.

Synopsis

GLType

Any instance of GLType can be the underlying type t of a GLExpr These types are:

  • Primitive types: Float, Double, Int, UInt, Bool
  • Vectors: Vec n Float, Vec n Double, Vec n Int, Vec n UInt, Vec n Bool
  • Matrices: Mat p q Float, Mat p q Double
  • Arrays: Represented as [t], where t is a primitive type or a vector

class (Eq t, Show t) => GLType t Source #

The class of base raw types. Users should not and need not implement any instances of this class.

Minimal complete definition

showGlslType, showGlslVal, glMap, glZipWith, glZipWith3, eltSize, numComponents, arrayLen, getGlslType, uniformSet

Instances

Instances details
GLType UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Bool Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType [UInt] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [UInt] -> String

showGlslVal :: [UInt] -> String

glMap :: (GLElt [UInt] -> GLElt [UInt]) -> [UInt] -> [UInt]

glZipWith :: (GLElt [UInt] -> GLElt [UInt] -> GLElt [UInt]) -> [UInt] -> [UInt] -> [UInt]

glZipWith3 :: (GLElt [UInt] -> GLElt [UInt] -> GLElt [UInt] -> GLElt [UInt]) -> [UInt] -> [UInt] -> [UInt] -> [UInt]

eltSize :: [[UInt]] -> Int

numComponents :: [[UInt]] -> Int

arrayLen :: [UInt] -> Int

getGlslType :: [[UInt]] -> DataType

uniformSet :: GLint -> [UInt] -> IO ()

GLType [Vec 2 UInt] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 UInt] -> String

showGlslVal :: [Vec 2 UInt] -> String

glMap :: (GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt]) -> [Vec 2 UInt] -> [Vec 2 UInt]

glZipWith :: (GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt]) -> [Vec 2 UInt] -> [Vec 2 UInt] -> [Vec 2 UInt]

glZipWith3 :: (GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt]) -> [Vec 2 UInt] -> [Vec 2 UInt] -> [Vec 2 UInt] -> [Vec 2 UInt]

eltSize :: [[Vec 2 UInt]] -> Int

numComponents :: [[Vec 2 UInt]] -> Int

arrayLen :: [Vec 2 UInt] -> Int

getGlslType :: [[Vec 2 UInt]] -> DataType

uniformSet :: GLint -> [Vec 2 UInt] -> IO ()

GLType [Vec 2 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Bool] -> String

showGlslVal :: [Vec 2 Bool] -> String

glMap :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool]

glZipWith :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool]

glZipWith3 :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool]

eltSize :: [[Vec 2 Bool]] -> Int

numComponents :: [[Vec 2 Bool]] -> Int

arrayLen :: [Vec 2 Bool] -> Int

getGlslType :: [[Vec 2 Bool]] -> DataType

uniformSet :: GLint -> [Vec 2 Bool] -> IO ()

GLType [Vec 2 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Double] -> String

showGlslVal :: [Vec 2 Double] -> String

glMap :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double]

glZipWith :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double]

glZipWith3 :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double]

eltSize :: [[Vec 2 Double]] -> Int

numComponents :: [[Vec 2 Double]] -> Int

arrayLen :: [Vec 2 Double] -> Int

getGlslType :: [[Vec 2 Double]] -> DataType

uniformSet :: GLint -> [Vec 2 Double] -> IO ()

GLType [Vec 2 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Float] -> String

showGlslVal :: [Vec 2 Float] -> String

glMap :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float]

glZipWith :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float]

glZipWith3 :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float]

eltSize :: [[Vec 2 Float]] -> Int

numComponents :: [[Vec 2 Float]] -> Int

arrayLen :: [Vec 2 Float] -> Int

getGlslType :: [[Vec 2 Float]] -> DataType

uniformSet :: GLint -> [Vec 2 Float] -> IO ()

GLType [Vec 2 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Int] -> String

showGlslVal :: [Vec 2 Int] -> String

glMap :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int]

glZipWith :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int]

glZipWith3 :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int]

eltSize :: [[Vec 2 Int]] -> Int

numComponents :: [[Vec 2 Int]] -> Int

arrayLen :: [Vec 2 Int] -> Int

getGlslType :: [[Vec 2 Int]] -> DataType

uniformSet :: GLint -> [Vec 2 Int] -> IO ()

GLType [Vec 3 UInt] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 UInt] -> String

showGlslVal :: [Vec 3 UInt] -> String

glMap :: (GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt]) -> [Vec 3 UInt] -> [Vec 3 UInt]

glZipWith :: (GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt]) -> [Vec 3 UInt] -> [Vec 3 UInt] -> [Vec 3 UInt]

glZipWith3 :: (GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt]) -> [Vec 3 UInt] -> [Vec 3 UInt] -> [Vec 3 UInt] -> [Vec 3 UInt]

eltSize :: [[Vec 3 UInt]] -> Int

numComponents :: [[Vec 3 UInt]] -> Int

arrayLen :: [Vec 3 UInt] -> Int

getGlslType :: [[Vec 3 UInt]] -> DataType

uniformSet :: GLint -> [Vec 3 UInt] -> IO ()

GLType [Vec 3 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Bool] -> String

showGlslVal :: [Vec 3 Bool] -> String

glMap :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool]

glZipWith :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool]

glZipWith3 :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool]

eltSize :: [[Vec 3 Bool]] -> Int

numComponents :: [[Vec 3 Bool]] -> Int

arrayLen :: [Vec 3 Bool] -> Int

getGlslType :: [[Vec 3 Bool]] -> DataType

uniformSet :: GLint -> [Vec 3 Bool] -> IO ()

GLType [Vec 3 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Double] -> String

showGlslVal :: [Vec 3 Double] -> String

glMap :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double]

glZipWith :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double]

glZipWith3 :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double]

eltSize :: [[Vec 3 Double]] -> Int

numComponents :: [[Vec 3 Double]] -> Int

arrayLen :: [Vec 3 Double] -> Int

getGlslType :: [[Vec 3 Double]] -> DataType

uniformSet :: GLint -> [Vec 3 Double] -> IO ()

GLType [Vec 3 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Float] -> String

showGlslVal :: [Vec 3 Float] -> String

glMap :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float]

glZipWith :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float]

glZipWith3 :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float]

eltSize :: [[Vec 3 Float]] -> Int

numComponents :: [[Vec 3 Float]] -> Int

arrayLen :: [Vec 3 Float] -> Int

getGlslType :: [[Vec 3 Float]] -> DataType

uniformSet :: GLint -> [Vec 3 Float] -> IO ()

GLType [Vec 3 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Int] -> String

showGlslVal :: [Vec 3 Int] -> String

glMap :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int]

glZipWith :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int]

glZipWith3 :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int]

eltSize :: [[Vec 3 Int]] -> Int

numComponents :: [[Vec 3 Int]] -> Int

arrayLen :: [Vec 3 Int] -> Int

getGlslType :: [[Vec 3 Int]] -> DataType

uniformSet :: GLint -> [Vec 3 Int] -> IO ()

GLType [Vec 4 UInt] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 UInt] -> String

showGlslVal :: [Vec 4 UInt] -> String

glMap :: (GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt]) -> [Vec 4 UInt] -> [Vec 4 UInt]

glZipWith :: (GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt]) -> [Vec 4 UInt] -> [Vec 4 UInt] -> [Vec 4 UInt]

glZipWith3 :: (GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt]) -> [Vec 4 UInt] -> [Vec 4 UInt] -> [Vec 4 UInt] -> [Vec 4 UInt]

eltSize :: [[Vec 4 UInt]] -> Int

numComponents :: [[Vec 4 UInt]] -> Int

arrayLen :: [Vec 4 UInt] -> Int

getGlslType :: [[Vec 4 UInt]] -> DataType

uniformSet :: GLint -> [Vec 4 UInt] -> IO ()

GLType [Vec 4 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Bool] -> String

showGlslVal :: [Vec 4 Bool] -> String

glMap :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool]

glZipWith :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool]

glZipWith3 :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool]

eltSize :: [[Vec 4 Bool]] -> Int

numComponents :: [[Vec 4 Bool]] -> Int

arrayLen :: [Vec 4 Bool] -> Int

getGlslType :: [[Vec 4 Bool]] -> DataType

uniformSet :: GLint -> [Vec 4 Bool] -> IO ()

GLType [Vec 4 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Double] -> String

showGlslVal :: [Vec 4 Double] -> String

glMap :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double]

glZipWith :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double]

glZipWith3 :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double]

eltSize :: [[Vec 4 Double]] -> Int

numComponents :: [[Vec 4 Double]] -> Int

arrayLen :: [Vec 4 Double] -> Int

getGlslType :: [[Vec 4 Double]] -> DataType

uniformSet :: GLint -> [Vec 4 Double] -> IO ()

GLType [Vec 4 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Float] -> String

showGlslVal :: [Vec 4 Float] -> String

glMap :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float]

glZipWith :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float]

glZipWith3 :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float]

eltSize :: [[Vec 4 Float]] -> Int

numComponents :: [[Vec 4 Float]] -> Int

arrayLen :: [Vec 4 Float] -> Int

getGlslType :: [[Vec 4 Float]] -> DataType

uniformSet :: GLint -> [Vec 4 Float] -> IO ()

GLType [Vec 4 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Int] -> String

showGlslVal :: [Vec 4 Int] -> String

glMap :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int]

glZipWith :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int]

glZipWith3 :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int]

eltSize :: [[Vec 4 Int]] -> Int

numComponents :: [[Vec 4 Int]] -> Int

arrayLen :: [Vec 4 Int] -> Int

getGlslType :: [[Vec 4 Int]] -> DataType

uniformSet :: GLint -> [Vec 4 Int] -> IO ()

GLType [Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Bool] -> String

showGlslVal :: [Bool] -> String

glMap :: (GLElt [Bool] -> GLElt [Bool]) -> [Bool] -> [Bool]

glZipWith :: (GLElt [Bool] -> GLElt [Bool] -> GLElt [Bool]) -> [Bool] -> [Bool] -> [Bool]

glZipWith3 :: (GLElt [Bool] -> GLElt [Bool] -> GLElt [Bool] -> GLElt [Bool]) -> [Bool] -> [Bool] -> [Bool] -> [Bool]

eltSize :: [[Bool]] -> Int

numComponents :: [[Bool]] -> Int

arrayLen :: [Bool] -> Int

getGlslType :: [[Bool]] -> DataType

uniformSet :: GLint -> [Bool] -> IO ()

GLType [Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType [Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Float] -> String

showGlslVal :: [Float] -> String

glMap :: (GLElt [Float] -> GLElt [Float]) -> [Float] -> [Float]

glZipWith :: (GLElt [Float] -> GLElt [Float] -> GLElt [Float]) -> [Float] -> [Float] -> [Float]

glZipWith3 :: (GLElt [Float] -> GLElt [Float] -> GLElt [Float] -> GLElt [Float]) -> [Float] -> [Float] -> [Float] -> [Float]

eltSize :: [[Float]] -> Int

numComponents :: [[Float]] -> Int

arrayLen :: [Float] -> Int

getGlslType :: [[Float]] -> DataType

uniformSet :: GLint -> [Float] -> IO ()

GLType [Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Int] -> String

showGlslVal :: [Int] -> String

glMap :: (GLElt [Int] -> GLElt [Int]) -> [Int] -> [Int]

glZipWith :: (GLElt [Int] -> GLElt [Int] -> GLElt [Int]) -> [Int] -> [Int] -> [Int]

glZipWith3 :: (GLElt [Int] -> GLElt [Int] -> GLElt [Int] -> GLElt [Int]) -> [Int] -> [Int] -> [Int] -> [Int]

eltSize :: [[Int]] -> Int

numComponents :: [[Int]] -> Int

arrayLen :: [Int] -> Int

getGlslType :: [[Int]] -> DataType

uniformSet :: GLint -> [Int] -> IO ()

GLType (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 UInt) -> String

showGlslVal :: Vec 2 UInt -> String

glMap :: (GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt)) -> Vec 2 UInt -> Vec 2 UInt

glZipWith :: (GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt)) -> Vec 2 UInt -> Vec 2 UInt -> Vec 2 UInt

glZipWith3 :: (GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt)) -> Vec 2 UInt -> Vec 2 UInt -> Vec 2 UInt -> Vec 2 UInt

eltSize :: [Vec 2 UInt] -> Int

numComponents :: [Vec 2 UInt] -> Int

arrayLen :: Vec 2 UInt -> Int

getGlslType :: [Vec 2 UInt] -> DataType

uniformSet :: GLint -> Vec 2 UInt -> IO ()

GLType (Vec 2 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Bool) -> String

showGlslVal :: Vec 2 Bool -> String

glMap :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool

glZipWith :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool

glZipWith3 :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool

eltSize :: [Vec 2 Bool] -> Int

numComponents :: [Vec 2 Bool] -> Int

arrayLen :: Vec 2 Bool -> Int

getGlslType :: [Vec 2 Bool] -> DataType

uniformSet :: GLint -> Vec 2 Bool -> IO ()

GLType (Vec 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Float) -> String

showGlslVal :: Vec 2 Float -> String

glMap :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float

glZipWith :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float

glZipWith3 :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float

eltSize :: [Vec 2 Float] -> Int

numComponents :: [Vec 2 Float] -> Int

arrayLen :: Vec 2 Float -> Int

getGlslType :: [Vec 2 Float] -> DataType

uniformSet :: GLint -> Vec 2 Float -> IO ()

GLType (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Int) -> String

showGlslVal :: Vec 2 Int -> String

glMap :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int

glZipWith :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int

glZipWith3 :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int

eltSize :: [Vec 2 Int] -> Int

numComponents :: [Vec 2 Int] -> Int

arrayLen :: Vec 2 Int -> Int

getGlslType :: [Vec 2 Int] -> DataType

uniformSet :: GLint -> Vec 2 Int -> IO ()

GLType (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 UInt) -> String

showGlslVal :: Vec 3 UInt -> String

glMap :: (GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt)) -> Vec 3 UInt -> Vec 3 UInt

glZipWith :: (GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt)) -> Vec 3 UInt -> Vec 3 UInt -> Vec 3 UInt

glZipWith3 :: (GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt)) -> Vec 3 UInt -> Vec 3 UInt -> Vec 3 UInt -> Vec 3 UInt

eltSize :: [Vec 3 UInt] -> Int

numComponents :: [Vec 3 UInt] -> Int

arrayLen :: Vec 3 UInt -> Int

getGlslType :: [Vec 3 UInt] -> DataType

uniformSet :: GLint -> Vec 3 UInt -> IO ()

GLType (Vec 3 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Bool) -> String

showGlslVal :: Vec 3 Bool -> String

glMap :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool

glZipWith :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool

glZipWith3 :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool

eltSize :: [Vec 3 Bool] -> Int

numComponents :: [Vec 3 Bool] -> Int

arrayLen :: Vec 3 Bool -> Int

getGlslType :: [Vec 3 Bool] -> DataType

uniformSet :: GLint -> Vec 3 Bool -> IO ()

GLType (Vec 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Float) -> String

showGlslVal :: Vec 3 Float -> String

glMap :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float

glZipWith :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float

glZipWith3 :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float

eltSize :: [Vec 3 Float] -> Int

numComponents :: [Vec 3 Float] -> Int

arrayLen :: Vec 3 Float -> Int

getGlslType :: [Vec 3 Float] -> DataType

uniformSet :: GLint -> Vec 3 Float -> IO ()

GLType (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Int) -> String

showGlslVal :: Vec 3 Int -> String

glMap :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int

glZipWith :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int

glZipWith3 :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int

eltSize :: [Vec 3 Int] -> Int

numComponents :: [Vec 3 Int] -> Int

arrayLen :: Vec 3 Int -> Int

getGlslType :: [Vec 3 Int] -> DataType

uniformSet :: GLint -> Vec 3 Int -> IO ()

GLType (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 UInt) -> String

showGlslVal :: Vec 4 UInt -> String

glMap :: (GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt)) -> Vec 4 UInt -> Vec 4 UInt

glZipWith :: (GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt)) -> Vec 4 UInt -> Vec 4 UInt -> Vec 4 UInt

glZipWith3 :: (GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt)) -> Vec 4 UInt -> Vec 4 UInt -> Vec 4 UInt -> Vec 4 UInt

eltSize :: [Vec 4 UInt] -> Int

numComponents :: [Vec 4 UInt] -> Int

arrayLen :: Vec 4 UInt -> Int

getGlslType :: [Vec 4 UInt] -> DataType

uniformSet :: GLint -> Vec 4 UInt -> IO ()

GLType (Vec 4 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Bool) -> String

showGlslVal :: Vec 4 Bool -> String

glMap :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool

glZipWith :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool

glZipWith3 :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool

eltSize :: [Vec 4 Bool] -> Int

numComponents :: [Vec 4 Bool] -> Int

arrayLen :: Vec 4 Bool -> Int

getGlslType :: [Vec 4 Bool] -> DataType

uniformSet :: GLint -> Vec 4 Bool -> IO ()

GLType (Vec 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Float) -> String

showGlslVal :: Vec 4 Float -> String

glMap :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float

glZipWith :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float

glZipWith3 :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float

eltSize :: [Vec 4 Float] -> Int

numComponents :: [Vec 4 Float] -> Int

arrayLen :: Vec 4 Float -> Int

getGlslType :: [Vec 4 Float] -> DataType

uniformSet :: GLint -> Vec 4 Float -> IO ()

GLType (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Int) -> String

showGlslVal :: Vec 4 Int -> String

glMap :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int

glZipWith :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int

glZipWith3 :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int

eltSize :: [Vec 4 Int] -> Int

numComponents :: [Vec 4 Int] -> Int

arrayLen :: Vec 4 Int -> Int

getGlslType :: [Vec 4 Int] -> DataType

uniformSet :: GLint -> Vec 4 Int -> IO ()

GLType (Mat 2 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 2 Double) -> String

showGlslVal :: Mat 2 2 Double -> String

glMap :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double

glZipWith :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double

glZipWith3 :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double

eltSize :: [Mat 2 2 Double] -> Int

numComponents :: [Mat 2 2 Double] -> Int

arrayLen :: Mat 2 2 Double -> Int

getGlslType :: [Mat 2 2 Double] -> DataType

uniformSet :: GLint -> Mat 2 2 Double -> IO ()

GLType (Mat 2 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 2 Float) -> String

showGlslVal :: Mat 2 2 Float -> String

glMap :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float

glZipWith :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float

glZipWith3 :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float

eltSize :: [Mat 2 2 Float] -> Int

numComponents :: [Mat 2 2 Float] -> Int

arrayLen :: Mat 2 2 Float -> Int

getGlslType :: [Mat 2 2 Float] -> DataType

uniformSet :: GLint -> Mat 2 2 Float -> IO ()

GLType (Mat 2 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 3 Double) -> String

showGlslVal :: Mat 2 3 Double -> String

glMap :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double

glZipWith :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double

glZipWith3 :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double

eltSize :: [Mat 2 3 Double] -> Int

numComponents :: [Mat 2 3 Double] -> Int

arrayLen :: Mat 2 3 Double -> Int

getGlslType :: [Mat 2 3 Double] -> DataType

uniformSet :: GLint -> Mat 2 3 Double -> IO ()

GLType (Mat 2 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 3 Float) -> String

showGlslVal :: Mat 2 3 Float -> String

glMap :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float

glZipWith :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float

glZipWith3 :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float

eltSize :: [Mat 2 3 Float] -> Int

numComponents :: [Mat 2 3 Float] -> Int

arrayLen :: Mat 2 3 Float -> Int

getGlslType :: [Mat 2 3 Float] -> DataType

uniformSet :: GLint -> Mat 2 3 Float -> IO ()

GLType (Mat 2 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 4 Double) -> String

showGlslVal :: Mat 2 4 Double -> String

glMap :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double

glZipWith :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double

glZipWith3 :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double

eltSize :: [Mat 2 4 Double] -> Int

numComponents :: [Mat 2 4 Double] -> Int

arrayLen :: Mat 2 4 Double -> Int

getGlslType :: [Mat 2 4 Double] -> DataType

uniformSet :: GLint -> Mat 2 4 Double -> IO ()

GLType (Mat 2 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 4 Float) -> String

showGlslVal :: Mat 2 4 Float -> String

glMap :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float

glZipWith :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float

glZipWith3 :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float

eltSize :: [Mat 2 4 Float] -> Int

numComponents :: [Mat 2 4 Float] -> Int

arrayLen :: Mat 2 4 Float -> Int

getGlslType :: [Mat 2 4 Float] -> DataType

uniformSet :: GLint -> Mat 2 4 Float -> IO ()

GLType (Mat 3 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 2 Double) -> String

showGlslVal :: Mat 3 2 Double -> String

glMap :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double

glZipWith :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double

glZipWith3 :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double

eltSize :: [Mat 3 2 Double] -> Int

numComponents :: [Mat 3 2 Double] -> Int

arrayLen :: Mat 3 2 Double -> Int

getGlslType :: [Mat 3 2 Double] -> DataType

uniformSet :: GLint -> Mat 3 2 Double -> IO ()

GLType (Mat 3 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 2 Float) -> String

showGlslVal :: Mat 3 2 Float -> String

glMap :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float

glZipWith :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float

glZipWith3 :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float

eltSize :: [Mat 3 2 Float] -> Int

numComponents :: [Mat 3 2 Float] -> Int

arrayLen :: Mat 3 2 Float -> Int

getGlslType :: [Mat 3 2 Float] -> DataType

uniformSet :: GLint -> Mat 3 2 Float -> IO ()

GLType (Mat 3 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 3 Double) -> String

showGlslVal :: Mat 3 3 Double -> String

glMap :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double

glZipWith :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double

glZipWith3 :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double

eltSize :: [Mat 3 3 Double] -> Int

numComponents :: [Mat 3 3 Double] -> Int

arrayLen :: Mat 3 3 Double -> Int

getGlslType :: [Mat 3 3 Double] -> DataType

uniformSet :: GLint -> Mat 3 3 Double -> IO ()

GLType (Mat 3 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 3 Float) -> String

showGlslVal :: Mat 3 3 Float -> String

glMap :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float

glZipWith :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float

glZipWith3 :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float

eltSize :: [Mat 3 3 Float] -> Int

numComponents :: [Mat 3 3 Float] -> Int

arrayLen :: Mat 3 3 Float -> Int

getGlslType :: [Mat 3 3 Float] -> DataType

uniformSet :: GLint -> Mat 3 3 Float -> IO ()

GLType (Mat 3 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 4 Double) -> String

showGlslVal :: Mat 3 4 Double -> String

glMap :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double

glZipWith :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double

glZipWith3 :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double

eltSize :: [Mat 3 4 Double] -> Int

numComponents :: [Mat 3 4 Double] -> Int

arrayLen :: Mat 3 4 Double -> Int

getGlslType :: [Mat 3 4 Double] -> DataType

uniformSet :: GLint -> Mat 3 4 Double -> IO ()

GLType (Mat 3 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 4 Float) -> String

showGlslVal :: Mat 3 4 Float -> String

glMap :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float

glZipWith :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float

glZipWith3 :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float

eltSize :: [Mat 3 4 Float] -> Int

numComponents :: [Mat 3 4 Float] -> Int

arrayLen :: Mat 3 4 Float -> Int

getGlslType :: [Mat 3 4 Float] -> DataType

uniformSet :: GLint -> Mat 3 4 Float -> IO ()

GLType (Mat 4 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 2 Double) -> String

showGlslVal :: Mat 4 2 Double -> String

glMap :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double

glZipWith :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double

glZipWith3 :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double

eltSize :: [Mat 4 2 Double] -> Int

numComponents :: [Mat 4 2 Double] -> Int

arrayLen :: Mat 4 2 Double -> Int

getGlslType :: [Mat 4 2 Double] -> DataType

uniformSet :: GLint -> Mat 4 2 Double -> IO ()

GLType (Mat 4 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 2 Float) -> String

showGlslVal :: Mat 4 2 Float -> String

glMap :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float

glZipWith :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float

glZipWith3 :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float

eltSize :: [Mat 4 2 Float] -> Int

numComponents :: [Mat 4 2 Float] -> Int

arrayLen :: Mat 4 2 Float -> Int

getGlslType :: [Mat 4 2 Float] -> DataType

uniformSet :: GLint -> Mat 4 2 Float -> IO ()

GLType (Mat 4 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 3 Double) -> String

showGlslVal :: Mat 4 3 Double -> String

glMap :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double

glZipWith :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double

glZipWith3 :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double

eltSize :: [Mat 4 3 Double] -> Int

numComponents :: [Mat 4 3 Double] -> Int

arrayLen :: Mat 4 3 Double -> Int

getGlslType :: [Mat 4 3 Double] -> DataType

uniformSet :: GLint -> Mat 4 3 Double -> IO ()

GLType (Mat 4 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 3 Float) -> String

showGlslVal :: Mat 4 3 Float -> String

glMap :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float

glZipWith :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float

glZipWith3 :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float

eltSize :: [Mat 4 3 Float] -> Int

numComponents :: [Mat 4 3 Float] -> Int

arrayLen :: Mat 4 3 Float -> Int

getGlslType :: [Mat 4 3 Float] -> DataType

uniformSet :: GLint -> Mat 4 3 Float -> IO ()

GLType (Mat 4 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 4 Double) -> String

showGlslVal :: Mat 4 4 Double -> String

glMap :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double

glZipWith :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double

glZipWith3 :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double

eltSize :: [Mat 4 4 Double] -> Int

numComponents :: [Mat 4 4 Double] -> Int

arrayLen :: Mat 4 4 Double -> Int

getGlslType :: [Mat 4 4 Double] -> DataType

uniformSet :: GLint -> Mat 4 4 Double -> IO ()

GLType (Mat 4 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 4 Float) -> String

showGlslVal :: Mat 4 4 Float -> String

glMap :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float

glZipWith :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float

glZipWith3 :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float

eltSize :: [Mat 4 4 Float] -> Int

numComponents :: [Mat 4 4 Float] -> Int

arrayLen :: Mat 4 4 Float -> Int

getGlslType :: [Mat 4 4 Float] -> DataType

uniformSet :: GLint -> Mat 4 4 Float -> IO ()

data Float #

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

Instances

Instances details
GLFloating Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLInputType Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt Float

Methods

toStorableList :: [Float] -> [StoreElt Float]

GLNumeric Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

genDiv :: Float -> Float -> Float

GLPrim Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Float

GLPrimOrVec Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSigned Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingle Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingleNumeric Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

Domain GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Domain

Methods

glMap1 :: GLenum -> GLfloat -> GLfloat -> GLint -> GLint -> Ptr GLfloat -> IO ()

glMap2 :: GLenum -> GLfloat -> GLfloat -> GLint -> GLint -> GLfloat -> GLfloat -> GLint -> GLint -> Ptr GLfloat -> IO ()

glGetMapv :: GLenum -> GLenum -> Ptr GLfloat -> IO ()

evalCoord1 :: GLfloat -> IO () #

evalCoord1v :: Ptr GLfloat -> IO () #

evalCoord2 :: (GLfloat, GLfloat) -> IO () #

evalCoord2v :: Ptr GLfloat -> IO () #

glMapGrid1 :: GLint -> GLfloat -> GLfloat -> IO ()

glMapGrid2 :: GLint -> GLfloat -> GLfloat -> GLint -> GLfloat -> GLfloat -> IO ()

get2 :: GetPName2F p => (GLfloat -> GLfloat -> a) -> p -> IO a

get4 :: GetPName4F p => (GLfloat -> GLfloat -> GLfloat -> GLfloat -> a) -> p -> IO a

MatrixComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.MatrixComponent

PixelMapComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.PixelRectangles.PixelMap

Methods

getPixelMapv :: GLenum -> Ptr GLfloat -> IO ()

pixelMapv :: GLenum -> GLsizei -> Ptr GLfloat -> IO ()

RasterPosComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.RasterPos

WindowPosComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.RasterPos

Rect GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Rectangles

Methods

rect :: Vertex2 GLfloat -> Vertex2 GLfloat -> IO () #

rectv :: Ptr GLfloat -> Ptr GLfloat -> IO () #

Uniform GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Shaders.Uniform

UniformComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Shaders.Uniform

ColorComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

FogCoordComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

fogCoord1 :: GLfloat -> IO ()

fogCoord1v :: Ptr GLfloat -> IO ()

IndexComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

index1 :: GLfloat -> IO ()

index1v :: Ptr GLfloat -> IO ()

NormalComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

normal3 :: GLfloat -> GLfloat -> GLfloat -> IO ()

normal3v :: Ptr GLfloat -> IO ()

TexCoordComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

VertexAttribComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

vertexAttrib1 :: AttribLocation -> GLfloat -> IO () #

vertexAttrib2 :: AttribLocation -> GLfloat -> GLfloat -> IO () #

vertexAttrib3 :: AttribLocation -> GLfloat -> GLfloat -> GLfloat -> IO () #

vertexAttrib4 :: AttribLocation -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO () #

vertexAttrib1N :: AttribLocation -> GLfloat -> IO () #

vertexAttrib2N :: AttribLocation -> GLfloat -> GLfloat -> IO () #

vertexAttrib3N :: AttribLocation -> GLfloat -> GLfloat -> GLfloat -> IO () #

vertexAttrib4N :: AttribLocation -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO () #

vertexAttrib1I :: AttribLocation -> GLfloat -> IO () #

vertexAttrib2I :: AttribLocation -> GLfloat -> GLfloat -> IO () #

vertexAttrib3I :: AttribLocation -> GLfloat -> GLfloat -> GLfloat -> IO () #

vertexAttrib4I :: AttribLocation -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO () #

vertexAttrib1v :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib2v :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib3v :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib4v :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib1Nv :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib2Nv :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib3Nv :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib4Nv :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib1Iv :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib2Iv :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib3Iv :: AttribLocation -> Ptr GLfloat -> IO () #

vertexAttrib4Iv :: AttribLocation -> Ptr GLfloat -> IO () #

VertexComponent GLfloat 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

vertex2 :: GLfloat -> GLfloat -> IO ()

vertex3 :: GLfloat -> GLfloat -> GLfloat -> IO ()

vertex4 :: GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()

vertex2v :: Ptr GLfloat -> IO ()

vertex3v :: Ptr GLfloat -> IO ()

vertex4v :: Ptr GLfloat -> IO ()

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Floating Float

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat Float

Since: base-2.1

Instance details

Defined in GHC.Float

Read Float

Since: base-2.1

Instance details

Defined in GHC.Read

Eq Float

Note that due to the presence of NaN, Float's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float's Eq instance does not satisfy extensionality:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Float

Note that due to the presence of NaN, Float's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Float)
False

Also note that, due to the same, Ord's operator interactions are not respected by Float's instance:

>>> (0/0 :: Float) > 1
False
>>> compare (0/0 :: Float) 1
GT
Instance details

Defined in GHC.Classes

Methods

compare :: Float -> Float -> Ordering #

(<) :: Float -> Float -> Bool #

(<=) :: Float -> Float -> Bool #

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Hashable Float

Note: prior to hashable-1.3.0.0, hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Lift Float 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Float -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Float -> Code m Float #

Generic1 (URec Float :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Float) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Float a -> Rep1 (URec Float) a #

to1 :: forall (a :: k0). Rep1 (URec Float) a -> URec Float a #

GLType [Vec 2 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Float] -> String

showGlslVal :: [Vec 2 Float] -> String

glMap :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float]

glZipWith :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float]

glZipWith3 :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float]

eltSize :: [[Vec 2 Float]] -> Int

numComponents :: [[Vec 2 Float]] -> Int

arrayLen :: [Vec 2 Float] -> Int

getGlslType :: [[Vec 2 Float]] -> DataType

uniformSet :: GLint -> [Vec 2 Float] -> IO ()

GLType [Vec 3 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Float] -> String

showGlslVal :: [Vec 3 Float] -> String

glMap :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float]

glZipWith :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float]

glZipWith3 :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float]

eltSize :: [[Vec 3 Float]] -> Int

numComponents :: [[Vec 3 Float]] -> Int

arrayLen :: [Vec 3 Float] -> Int

getGlslType :: [[Vec 3 Float]] -> DataType

uniformSet :: GLint -> [Vec 3 Float] -> IO ()

GLType [Vec 4 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Float] -> String

showGlslVal :: [Vec 4 Float] -> String

glMap :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float]

glZipWith :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float]

glZipWith3 :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float]

eltSize :: [[Vec 4 Float]] -> Int

numComponents :: [[Vec 4 Float]] -> Int

arrayLen :: [Vec 4 Float] -> Int

getGlslType :: [[Vec 4 Float]] -> DataType

uniformSet :: GLint -> [Vec 4 Float] -> IO ()

GLType [Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Float] -> String

showGlslVal :: [Float] -> String

glMap :: (GLElt [Float] -> GLElt [Float]) -> [Float] -> [Float]

glZipWith :: (GLElt [Float] -> GLElt [Float] -> GLElt [Float]) -> [Float] -> [Float] -> [Float]

glZipWith3 :: (GLElt [Float] -> GLElt [Float] -> GLElt [Float] -> GLElt [Float]) -> [Float] -> [Float] -> [Float] -> [Float]

eltSize :: [[Float]] -> Int

numComponents :: [[Float]] -> Int

arrayLen :: [Float] -> Int

getGlslType :: [[Float]] -> DataType

uniformSet :: GLint -> [Float] -> IO ()

Foldable (UFloat :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UFloat m -> m #

foldMap :: Monoid m => (a -> m) -> UFloat a -> m #

foldMap' :: Monoid m => (a -> m) -> UFloat a -> m #

foldr :: (a -> b -> b) -> b -> UFloat a -> b #

foldr' :: (a -> b -> b) -> b -> UFloat a -> b #

foldl :: (b -> a -> b) -> b -> UFloat a -> b #

foldl' :: (b -> a -> b) -> b -> UFloat a -> b #

foldr1 :: (a -> a -> a) -> UFloat a -> a #

foldl1 :: (a -> a -> a) -> UFloat a -> a #

toList :: UFloat a -> [a] #

null :: UFloat a -> Bool #

length :: UFloat a -> Int #

elem :: Eq a => a -> UFloat a -> Bool #

maximum :: Ord a => UFloat a -> a #

minimum :: Ord a => UFloat a -> a #

sum :: Num a => UFloat a -> a #

product :: Num a => UFloat a -> a #

Traversable (UFloat :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) #

GLInputType (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 Float)

Methods

toStorableList :: [Vec 2 Float] -> [StoreElt (Vec 2 Float)]

GLInputType (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 Float)

Methods

toStorableList :: [Vec 3 Float] -> [StoreElt (Vec 3 Float)]

GLInputType (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 Float)

Methods

toStorableList :: [Vec 4 Float] -> [StoreElt (Vec 4 Float)]

GLPrimOrVec (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Float) -> String

showGlslVal :: Vec 2 Float -> String

glMap :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float

glZipWith :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float

glZipWith3 :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float

eltSize :: [Vec 2 Float] -> Int

numComponents :: [Vec 2 Float] -> Int

arrayLen :: Vec 2 Float -> Int

getGlslType :: [Vec 2 Float] -> DataType

uniformSet :: GLint -> Vec 2 Float -> IO ()

GLType (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Float) -> String

showGlslVal :: Vec 3 Float -> String

glMap :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float

glZipWith :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float

glZipWith3 :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float

eltSize :: [Vec 3 Float] -> Int

numComponents :: [Vec 3 Float] -> Int

arrayLen :: Vec 3 Float -> Int

getGlslType :: [Vec 3 Float] -> DataType

uniformSet :: GLint -> Vec 3 Float -> IO ()

GLType (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Float) -> String

showGlslVal :: Vec 4 Float -> String

glMap :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float

glZipWith :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float

glZipWith3 :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float

eltSize :: [Vec 4 Float] -> Int

numComponents :: [Vec 4 Float] -> Int

arrayLen :: Vec 4 Float -> Int

getGlslType :: [Vec 4 Float] -> DataType

uniformSet :: GLint -> Vec 4 Float -> IO ()

Functor (URec Float :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b #

(<$) :: a -> URec Float b -> URec Float a #

GLType (Mat 2 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 2 Float) -> String

showGlslVal :: Mat 2 2 Float -> String

glMap :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float

glZipWith :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float

glZipWith3 :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float

eltSize :: [Mat 2 2 Float] -> Int

numComponents :: [Mat 2 2 Float] -> Int

arrayLen :: Mat 2 2 Float -> Int

getGlslType :: [Mat 2 2 Float] -> DataType

uniformSet :: GLint -> Mat 2 2 Float -> IO ()

GLType (Mat 2 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 3 Float) -> String

showGlslVal :: Mat 2 3 Float -> String

glMap :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float

glZipWith :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float

glZipWith3 :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float

eltSize :: [Mat 2 3 Float] -> Int

numComponents :: [Mat 2 3 Float] -> Int

arrayLen :: Mat 2 3 Float -> Int

getGlslType :: [Mat 2 3 Float] -> DataType

uniformSet :: GLint -> Mat 2 3 Float -> IO ()

GLType (Mat 2 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 4 Float) -> String

showGlslVal :: Mat 2 4 Float -> String

glMap :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float

glZipWith :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float

glZipWith3 :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float

eltSize :: [Mat 2 4 Float] -> Int

numComponents :: [Mat 2 4 Float] -> Int

arrayLen :: Mat 2 4 Float -> Int

getGlslType :: [Mat 2 4 Float] -> DataType

uniformSet :: GLint -> Mat 2 4 Float -> IO ()

GLType (Mat 3 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 2 Float) -> String

showGlslVal :: Mat 3 2 Float -> String

glMap :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float

glZipWith :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float

glZipWith3 :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float

eltSize :: [Mat 3 2 Float] -> Int

numComponents :: [Mat 3 2 Float] -> Int

arrayLen :: Mat 3 2 Float -> Int

getGlslType :: [Mat 3 2 Float] -> DataType

uniformSet :: GLint -> Mat 3 2 Float -> IO ()

GLType (Mat 3 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 3 Float) -> String

showGlslVal :: Mat 3 3 Float -> String

glMap :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float

glZipWith :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float

glZipWith3 :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float

eltSize :: [Mat 3 3 Float] -> Int

numComponents :: [Mat 3 3 Float] -> Int

arrayLen :: Mat 3 3 Float -> Int

getGlslType :: [Mat 3 3 Float] -> DataType

uniformSet :: GLint -> Mat 3 3 Float -> IO ()

GLType (Mat 3 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 4 Float) -> String

showGlslVal :: Mat 3 4 Float -> String

glMap :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float

glZipWith :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float

glZipWith3 :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float

eltSize :: [Mat 3 4 Float] -> Int

numComponents :: [Mat 3 4 Float] -> Int

arrayLen :: Mat 3 4 Float -> Int

getGlslType :: [Mat 3 4 Float] -> DataType

uniformSet :: GLint -> Mat 3 4 Float -> IO ()

GLType (Mat 4 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 2 Float) -> String

showGlslVal :: Mat 4 2 Float -> String

glMap :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float

glZipWith :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float

glZipWith3 :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float

eltSize :: [Mat 4 2 Float] -> Int

numComponents :: [Mat 4 2 Float] -> Int

arrayLen :: Mat 4 2 Float -> Int

getGlslType :: [Mat 4 2 Float] -> DataType

uniformSet :: GLint -> Mat 4 2 Float -> IO ()

GLType (Mat 4 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 3 Float) -> String

showGlslVal :: Mat 4 3 Float -> String

glMap :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float

glZipWith :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float

glZipWith3 :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float

eltSize :: [Mat 4 3 Float] -> Int

numComponents :: [Mat 4 3 Float] -> Int

arrayLen :: Mat 4 3 Float -> Int

getGlslType :: [Mat 4 3 Float] -> DataType

uniformSet :: GLint -> Mat 4 3 Float -> IO ()

GLType (Mat 4 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 4 Float) -> String

showGlslVal :: Mat 4 4 Float -> String

glMap :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float

glZipWith :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float

glZipWith3 :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float

eltSize :: [Mat 4 4 Float] -> Int

numComponents :: [Mat 4 4 Float] -> Int

arrayLen :: Mat 4 4 Float -> Int

getGlslType :: [Mat 4 4 Float] -> DataType

uniformSet :: GLint -> Mat 4 4 Float -> IO ()

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Show (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Eq (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

data URec Float (p :: k)

Used for marking occurrences of Float#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Float (p :: k) = UFloat {}
type Rep1 (URec Float :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type)))
type Rep (URec Float p) 
Instance details

Defined in GHC.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

data Double #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Instances details
GLFloating Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLNumeric Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

genDiv :: Double -> Double -> Double

GLPrim Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Double

GLPrimOrVec Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSigned Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

Domain GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Domain

Methods

glMap1 :: GLenum -> GLdouble -> GLdouble -> GLint -> GLint -> Ptr GLdouble -> IO ()

glMap2 :: GLenum -> GLdouble -> GLdouble -> GLint -> GLint -> GLdouble -> GLdouble -> GLint -> GLint -> Ptr GLdouble -> IO ()

glGetMapv :: GLenum -> GLenum -> Ptr GLdouble -> IO ()

evalCoord1 :: GLdouble -> IO () #

evalCoord1v :: Ptr GLdouble -> IO () #

evalCoord2 :: (GLdouble, GLdouble) -> IO () #

evalCoord2v :: Ptr GLdouble -> IO () #

glMapGrid1 :: GLint -> GLdouble -> GLdouble -> IO ()

glMapGrid2 :: GLint -> GLdouble -> GLdouble -> GLint -> GLdouble -> GLdouble -> IO ()

get2 :: GetPName2F p => (GLdouble -> GLdouble -> a) -> p -> IO a

get4 :: GetPName4F p => (GLdouble -> GLdouble -> GLdouble -> GLdouble -> a) -> p -> IO a

MatrixComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.MatrixComponent

RasterPosComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.RasterPos

WindowPosComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.RasterPos

Rect GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Rectangles

Uniform GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Shaders.Uniform

UniformComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.Shaders.Uniform

ColorComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

FogCoordComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

fogCoord1 :: GLdouble -> IO ()

fogCoord1v :: Ptr GLdouble -> IO ()

IndexComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

index1 :: GLdouble -> IO ()

index1v :: Ptr GLdouble -> IO ()

NormalComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

normal3 :: GLdouble -> GLdouble -> GLdouble -> IO ()

normal3v :: Ptr GLdouble -> IO ()

TexCoordComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

VertexAttribComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Methods

vertexAttrib1 :: AttribLocation -> GLdouble -> IO () #

vertexAttrib2 :: AttribLocation -> GLdouble -> GLdouble -> IO () #

vertexAttrib3 :: AttribLocation -> GLdouble -> GLdouble -> GLdouble -> IO () #

vertexAttrib4 :: AttribLocation -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO () #

vertexAttrib1N :: AttribLocation -> GLdouble -> IO () #

vertexAttrib2N :: AttribLocation -> GLdouble -> GLdouble -> IO () #

vertexAttrib3N :: AttribLocation -> GLdouble -> GLdouble -> GLdouble -> IO () #

vertexAttrib4N :: AttribLocation -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO () #

vertexAttrib1I :: AttribLocation -> GLdouble -> IO () #

vertexAttrib2I :: AttribLocation -> GLdouble -> GLdouble -> IO () #

vertexAttrib3I :: AttribLocation -> GLdouble -> GLdouble -> GLdouble -> IO () #

vertexAttrib4I :: AttribLocation -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO () #

vertexAttrib1v :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib2v :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib3v :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib4v :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib1Nv :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib2Nv :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib3Nv :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib4Nv :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib1Iv :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib2Iv :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib3Iv :: AttribLocation -> Ptr GLdouble -> IO () #

vertexAttrib4Iv :: AttribLocation -> Ptr GLdouble -> IO () #

VertexComponent GLdouble 
Instance details

Defined in Graphics.Rendering.OpenGL.GL.VertexSpec

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

Floating Double

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat Double

Since: base-2.1

Instance details

Defined in GHC.Float

Read Double

Since: base-2.1

Instance details

Defined in GHC.Read

Eq Double

Note that due to the presence of NaN, Double's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Double

Note that due to the presence of NaN, Double's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Double)
False

Also note that, due to the same, Ord's operator interactions are not respected by Double's instance:

>>> (0/0 :: Double) > 1
False
>>> compare (0/0 :: Double) 1
GT
Instance details

Defined in GHC.Classes

Hashable Double

Note: prior to hashable-1.3.0.0, hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Lift Double 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Double -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Double -> Code m Double #

Generic1 (URec Double :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Double) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Double a -> Rep1 (URec Double) a #

to1 :: forall (a :: k0). Rep1 (URec Double) a -> URec Double a #

GLType [Vec 2 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Double] -> String

showGlslVal :: [Vec 2 Double] -> String

glMap :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double]

glZipWith :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double]

glZipWith3 :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double]

eltSize :: [[Vec 2 Double]] -> Int

numComponents :: [[Vec 2 Double]] -> Int

arrayLen :: [Vec 2 Double] -> Int

getGlslType :: [[Vec 2 Double]] -> DataType

uniformSet :: GLint -> [Vec 2 Double] -> IO ()

GLType [Vec 3 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Double] -> String

showGlslVal :: [Vec 3 Double] -> String

glMap :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double]

glZipWith :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double]

glZipWith3 :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double]

eltSize :: [[Vec 3 Double]] -> Int

numComponents :: [[Vec 3 Double]] -> Int

arrayLen :: [Vec 3 Double] -> Int

getGlslType :: [[Vec 3 Double]] -> DataType

uniformSet :: GLint -> [Vec 3 Double] -> IO ()

GLType [Vec 4 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Double] -> String

showGlslVal :: [Vec 4 Double] -> String

glMap :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double]

glZipWith :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double]

glZipWith3 :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double]

eltSize :: [[Vec 4 Double]] -> Int

numComponents :: [[Vec 4 Double]] -> Int

arrayLen :: [Vec 4 Double] -> Int

getGlslType :: [[Vec 4 Double]] -> DataType

uniformSet :: GLint -> [Vec 4 Double] -> IO ()

GLType [Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Foldable (UDouble :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UDouble m -> m #

foldMap :: Monoid m => (a -> m) -> UDouble a -> m #

foldMap' :: Monoid m => (a -> m) -> UDouble a -> m #

foldr :: (a -> b -> b) -> b -> UDouble a -> b #

foldr' :: (a -> b -> b) -> b -> UDouble a -> b #

foldl :: (b -> a -> b) -> b -> UDouble a -> b #

foldl' :: (b -> a -> b) -> b -> UDouble a -> b #

foldr1 :: (a -> a -> a) -> UDouble a -> a #

foldl1 :: (a -> a -> a) -> UDouble a -> a #

toList :: UDouble a -> [a] #

null :: UDouble a -> Bool #

length :: UDouble a -> Int #

elem :: Eq a => a -> UDouble a -> Bool #

maximum :: Ord a => UDouble a -> a #

minimum :: Ord a => UDouble a -> a #

sum :: Num a => UDouble a -> a #

product :: Num a => UDouble a -> a #

Traversable (UDouble :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) #

GLPrimOrVec (Vec 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Functor (URec Double :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b #

(<$) :: a -> URec Double b -> URec Double a #

GLType (Mat 2 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 2 Double) -> String

showGlslVal :: Mat 2 2 Double -> String

glMap :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double

glZipWith :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double

glZipWith3 :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double

eltSize :: [Mat 2 2 Double] -> Int

numComponents :: [Mat 2 2 Double] -> Int

arrayLen :: Mat 2 2 Double -> Int

getGlslType :: [Mat 2 2 Double] -> DataType

uniformSet :: GLint -> Mat 2 2 Double -> IO ()

GLType (Mat 2 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 3 Double) -> String

showGlslVal :: Mat 2 3 Double -> String

glMap :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double

glZipWith :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double

glZipWith3 :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double

eltSize :: [Mat 2 3 Double] -> Int

numComponents :: [Mat 2 3 Double] -> Int

arrayLen :: Mat 2 3 Double -> Int

getGlslType :: [Mat 2 3 Double] -> DataType

uniformSet :: GLint -> Mat 2 3 Double -> IO ()

GLType (Mat 2 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 4 Double) -> String

showGlslVal :: Mat 2 4 Double -> String

glMap :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double

glZipWith :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double

glZipWith3 :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double

eltSize :: [Mat 2 4 Double] -> Int

numComponents :: [Mat 2 4 Double] -> Int

arrayLen :: Mat 2 4 Double -> Int

getGlslType :: [Mat 2 4 Double] -> DataType

uniformSet :: GLint -> Mat 2 4 Double -> IO ()

GLType (Mat 3 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 2 Double) -> String

showGlslVal :: Mat 3 2 Double -> String

glMap :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double

glZipWith :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double

glZipWith3 :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double

eltSize :: [Mat 3 2 Double] -> Int

numComponents :: [Mat 3 2 Double] -> Int

arrayLen :: Mat 3 2 Double -> Int

getGlslType :: [Mat 3 2 Double] -> DataType

uniformSet :: GLint -> Mat 3 2 Double -> IO ()

GLType (Mat 3 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 3 Double) -> String

showGlslVal :: Mat 3 3 Double -> String

glMap :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double

glZipWith :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double

glZipWith3 :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double

eltSize :: [Mat 3 3 Double] -> Int

numComponents :: [Mat 3 3 Double] -> Int

arrayLen :: Mat 3 3 Double -> Int

getGlslType :: [Mat 3 3 Double] -> DataType

uniformSet :: GLint -> Mat 3 3 Double -> IO ()

GLType (Mat 3 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 4 Double) -> String

showGlslVal :: Mat 3 4 Double -> String

glMap :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double

glZipWith :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double

glZipWith3 :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double

eltSize :: [Mat 3 4 Double] -> Int

numComponents :: [Mat 3 4 Double] -> Int

arrayLen :: Mat 3 4 Double -> Int

getGlslType :: [Mat 3 4 Double] -> DataType

uniformSet :: GLint -> Mat 3 4 Double -> IO ()

GLType (Mat 4 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 2 Double) -> String

showGlslVal :: Mat 4 2 Double -> String

glMap :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double

glZipWith :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double

glZipWith3 :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double

eltSize :: [Mat 4 2 Double] -> Int

numComponents :: [Mat 4 2 Double] -> Int

arrayLen :: Mat 4 2 Double -> Int

getGlslType :: [Mat 4 2 Double] -> DataType

uniformSet :: GLint -> Mat 4 2 Double -> IO ()

GLType (Mat 4 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 3 Double) -> String

showGlslVal :: Mat 4 3 Double -> String

glMap :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double

glZipWith :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double

glZipWith3 :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double

eltSize :: [Mat 4 3 Double] -> Int

numComponents :: [Mat 4 3 Double] -> Int

arrayLen :: Mat 4 3 Double -> Int

getGlslType :: [Mat 4 3 Double] -> DataType

uniformSet :: GLint -> Mat 4 3 Double -> IO ()

GLType (Mat 4 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 4 Double) -> String

showGlslVal :: Mat 4 4 Double -> String

glMap :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double

glZipWith :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double

glZipWith3 :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double

eltSize :: [Mat 4 4 Double] -> Int

numComponents :: [Mat 4 4 Double] -> Int

arrayLen :: Mat 4 4 Double -> Int

getGlslType :: [Mat 4 4 Double] -> DataType

uniformSet :: GLint -> Mat 4 4 Double -> IO ()

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Show (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Eq (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

data URec Double (p :: k)

Used for marking occurrences of Double#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Double (p :: k) = UDouble {}
type Rep1 (URec Double :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type)))
type Rep (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

data Int #

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Instances

Instances details
GLInputType Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt Int

Methods

toStorableList :: [Int] -> [StoreElt Int]

GLInteger Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLNumeric Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

genDiv :: Int -> Int -> Int

GLPrim Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Int

GLPrimOrVec Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSigned Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingle Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingleNumeric Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Bits Int

Since: base-2.1

Instance details

Defined in GHC.Bits

Methods

(.&.) :: Int -> Int -> Int #

(.|.) :: Int -> Int -> Int #

xor :: Int -> Int -> Int #

complement :: Int -> Int #

shift :: Int -> Int -> Int #

rotate :: Int -> Int -> Int #

zeroBits :: Int #

bit :: Int -> Int #

setBit :: Int -> Int -> Int #

clearBit :: Int -> Int -> Int #

complementBit :: Int -> Int -> Int #

testBit :: Int -> Int -> Bool #

bitSizeMaybe :: Int -> Maybe Int #

bitSize :: Int -> Int #

isSigned :: Int -> Bool #

shiftL :: Int -> Int -> Int #

unsafeShiftL :: Int -> Int -> Int #

shiftR :: Int -> Int -> Int #

unsafeShiftR :: Int -> Int -> Int #

rotateL :: Int -> Int -> Int #

rotateR :: Int -> Int -> Int #

popCount :: Int -> Int #

FiniteBits Int

Since: base-4.6.0.0

Instance details

Defined in GHC.Bits

Bounded Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: Int #

maxBound :: Int #

Enum Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Ix Int

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

range :: (Int, Int) -> [Int] #

index :: (Int, Int) -> Int -> Int #

unsafeIndex :: (Int, Int) -> Int -> Int #

inRange :: (Int, Int) -> Int -> Bool #

rangeSize :: (Int, Int) -> Int #

unsafeRangeSize :: (Int, Int) -> Int #

Num Int

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Read Int

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Int

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

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

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

toInteger :: Int -> Integer #

Real Int

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

toRational :: Int -> Rational #

Show Int

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Eq Int 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Int 
Instance details

Defined in GHC.Classes

Methods

compare :: Int -> Int -> Ordering #

(<) :: Int -> Int -> Bool #

(<=) :: Int -> Int -> Bool #

(>) :: Int -> Int -> Bool #

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

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Hashable Int 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Lift Int 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Int -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int -> Code m Int #

Generic1 (URec Int :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Int) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec Int a -> Rep1 (URec Int) a #

to1 :: forall (a :: k0). Rep1 (URec Int) a -> URec Int a #

GLType [Vec 2 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Int] -> String

showGlslVal :: [Vec 2 Int] -> String

glMap :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int]

glZipWith :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int]

glZipWith3 :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int]

eltSize :: [[Vec 2 Int]] -> Int

numComponents :: [[Vec 2 Int]] -> Int

arrayLen :: [Vec 2 Int] -> Int

getGlslType :: [[Vec 2 Int]] -> DataType

uniformSet :: GLint -> [Vec 2 Int] -> IO ()

GLType [Vec 3 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Int] -> String

showGlslVal :: [Vec 3 Int] -> String

glMap :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int]

glZipWith :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int]

glZipWith3 :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int]

eltSize :: [[Vec 3 Int]] -> Int

numComponents :: [[Vec 3 Int]] -> Int

arrayLen :: [Vec 3 Int] -> Int

getGlslType :: [[Vec 3 Int]] -> DataType

uniformSet :: GLint -> [Vec 3 Int] -> IO ()

GLType [Vec 4 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Int] -> String

showGlslVal :: [Vec 4 Int] -> String

glMap :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int]

glZipWith :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int]

glZipWith3 :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int]

eltSize :: [[Vec 4 Int]] -> Int

numComponents :: [[Vec 4 Int]] -> Int

arrayLen :: [Vec 4 Int] -> Int

getGlslType :: [[Vec 4 Int]] -> DataType

uniformSet :: GLint -> [Vec 4 Int] -> IO ()

GLType [Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Int] -> String

showGlslVal :: [Int] -> String

glMap :: (GLElt [Int] -> GLElt [Int]) -> [Int] -> [Int]

glZipWith :: (GLElt [Int] -> GLElt [Int] -> GLElt [Int]) -> [Int] -> [Int] -> [Int]

glZipWith3 :: (GLElt [Int] -> GLElt [Int] -> GLElt [Int] -> GLElt [Int]) -> [Int] -> [Int] -> [Int] -> [Int]

eltSize :: [[Int]] -> Int

numComponents :: [[Int]] -> Int

arrayLen :: [Int] -> Int

getGlslType :: [[Int]] -> DataType

uniformSet :: GLint -> [Int] -> IO ()

Foldable (UInt :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UInt m -> m #

foldMap :: Monoid m => (a -> m) -> UInt a -> m #

foldMap' :: Monoid m => (a -> m) -> UInt a -> m #

foldr :: (a -> b -> b) -> b -> UInt a -> b #

foldr' :: (a -> b -> b) -> b -> UInt a -> b #

foldl :: (b -> a -> b) -> b -> UInt a -> b #

foldl' :: (b -> a -> b) -> b -> UInt a -> b #

foldr1 :: (a -> a -> a) -> UInt a -> a #

foldl1 :: (a -> a -> a) -> UInt a -> a #

toList :: UInt a -> [a] #

null :: UInt a -> Bool #

length :: UInt a -> Int #

elem :: Eq a => a -> UInt a -> Bool #

maximum :: Ord a => UInt a -> a #

minimum :: Ord a => UInt a -> a #

sum :: Num a => UInt a -> a #

product :: Num a => UInt a -> a #

Traversable (UInt :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) #

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) #

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) #

sequence :: Monad m => UInt (m a) -> m (UInt a) #

GLInputType (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 Int)

Methods

toStorableList :: [Vec 2 Int] -> [StoreElt (Vec 2 Int)]

GLInputType (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 Int)

Methods

toStorableList :: [Vec 3 Int] -> [StoreElt (Vec 3 Int)]

GLInputType (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 Int)

Methods

toStorableList :: [Vec 4 Int] -> [StoreElt (Vec 4 Int)]

GLPrimOrVec (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Int) -> String

showGlslVal :: Vec 2 Int -> String

glMap :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int

glZipWith :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int

glZipWith3 :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int

eltSize :: [Vec 2 Int] -> Int

numComponents :: [Vec 2 Int] -> Int

arrayLen :: Vec 2 Int -> Int

getGlslType :: [Vec 2 Int] -> DataType

uniformSet :: GLint -> Vec 2 Int -> IO ()

GLType (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Int) -> String

showGlslVal :: Vec 3 Int -> String

glMap :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int

glZipWith :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int

glZipWith3 :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int

eltSize :: [Vec 3 Int] -> Int

numComponents :: [Vec 3 Int] -> Int

arrayLen :: Vec 3 Int -> Int

getGlslType :: [Vec 3 Int] -> DataType

uniformSet :: GLint -> Vec 3 Int -> IO ()

GLType (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Int) -> String

showGlslVal :: Vec 4 Int -> String

glMap :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int

glZipWith :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int

glZipWith3 :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int

eltSize :: [Vec 4 Int] -> Int

numComponents :: [Vec 4 Int] -> Int

arrayLen :: Vec 4 Int -> Int

getGlslType :: [Vec 4 Int] -> DataType

uniformSet :: GLint -> Vec 4 Int -> IO ()

Functor (URec Int :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b #

(<$) :: a -> URec Int b -> URec Int a #

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Show (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Eq (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Int p -> URec Int p -> Ordering #

(<) :: URec Int p -> URec Int p -> Bool #

(<=) :: URec Int p -> URec Int p -> Bool #

(>) :: URec Int p -> URec Int p -> Bool #

(>=) :: URec Int p -> URec Int p -> Bool #

max :: URec Int p -> URec Int p -> URec Int p #

min :: URec Int p -> URec Int p -> URec Int p #

data URec Int (p :: k)

Used for marking occurrences of Int#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Int (p :: k) = UInt {}
type Rep1 (URec Int :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec Int :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: k -> Type)))
type Rep (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

type UInt = Word32 Source #

An unsigned integer

data Bool #

Instances

Instances details
GLPrim Bool Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Bool

GLSingle Bool Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType Bool Source # 
Instance details

Defined in Graphics.HaGL.GLType

Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Bits Bool

Interpret Bool as 1-bit bit-field

Since: base-4.7.0.0

Instance details

Defined in GHC.Bits

FiniteBits Bool

Since: base-4.7.0.0

Instance details

Defined in GHC.Bits

Bounded Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

SingKind Bool

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Bool

Methods

fromSing :: forall (a :: Bool). Sing a -> DemoteRep Bool

Ix Bool

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

range :: (Bool, Bool) -> [Bool] #

index :: (Bool, Bool) -> Bool -> Int #

unsafeIndex :: (Bool, Bool) -> Bool -> Int #

inRange :: (Bool, Bool) -> Bool -> Bool #

rangeSize :: (Bool, Bool) -> Int #

unsafeRangeSize :: (Bool, Bool) -> Int #

Read Bool

Since: base-2.1

Instance details

Defined in GHC.Read

Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Eq Bool 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Bool 
Instance details

Defined in GHC.Classes

Methods

compare :: Bool -> Bool -> Ordering #

(<) :: Bool -> Bool -> Bool #

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

(>) :: Bool -> Bool -> Bool #

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Hashable Bool 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

SingI 'False

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'False

SingI 'True

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'True

Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Bool -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bool -> Code m Bool #

GLType [Vec 2 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Bool] -> String

showGlslVal :: [Vec 2 Bool] -> String

glMap :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool]

glZipWith :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool]

glZipWith3 :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool]

eltSize :: [[Vec 2 Bool]] -> Int

numComponents :: [[Vec 2 Bool]] -> Int

arrayLen :: [Vec 2 Bool] -> Int

getGlslType :: [[Vec 2 Bool]] -> DataType

uniformSet :: GLint -> [Vec 2 Bool] -> IO ()

GLType [Vec 3 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Bool] -> String

showGlslVal :: [Vec 3 Bool] -> String

glMap :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool]

glZipWith :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool]

glZipWith3 :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool]

eltSize :: [[Vec 3 Bool]] -> Int

numComponents :: [[Vec 3 Bool]] -> Int

arrayLen :: [Vec 3 Bool] -> Int

getGlslType :: [[Vec 3 Bool]] -> DataType

uniformSet :: GLint -> [Vec 3 Bool] -> IO ()

GLType [Vec 4 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Bool] -> String

showGlslVal :: [Vec 4 Bool] -> String

glMap :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool]

glZipWith :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool]

glZipWith3 :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool]

eltSize :: [[Vec 4 Bool]] -> Int

numComponents :: [[Vec 4 Bool]] -> Int

arrayLen :: [Vec 4 Bool] -> Int

getGlslType :: [[Vec 4 Bool]] -> DataType

uniformSet :: GLint -> [Vec 4 Bool] -> IO ()

GLType [Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Bool] -> String

showGlslVal :: [Bool] -> String

glMap :: (GLElt [Bool] -> GLElt [Bool]) -> [Bool] -> [Bool]

glZipWith :: (GLElt [Bool] -> GLElt [Bool] -> GLElt [Bool]) -> [Bool] -> [Bool] -> [Bool]

glZipWith3 :: (GLElt [Bool] -> GLElt [Bool] -> GLElt [Bool] -> GLElt [Bool]) -> [Bool] -> [Bool] -> [Bool] -> [Bool]

eltSize :: [[Bool]] -> Int

numComponents :: [[Bool]] -> Int

arrayLen :: [Bool] -> Int

getGlslType :: [[Bool]] -> DataType

uniformSet :: GLint -> [Bool] -> IO ()

GLType (Vec 2 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Bool) -> String

showGlslVal :: Vec 2 Bool -> String

glMap :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool

glZipWith :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool

glZipWith3 :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool

eltSize :: [Vec 2 Bool] -> Int

numComponents :: [Vec 2 Bool] -> Int

arrayLen :: Vec 2 Bool -> Int

getGlslType :: [Vec 2 Bool] -> DataType

uniformSet :: GLint -> Vec 2 Bool -> IO ()

GLType (Vec 3 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Bool) -> String

showGlslVal :: Vec 3 Bool -> String

glMap :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool

glZipWith :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool

glZipWith3 :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool

eltSize :: [Vec 3 Bool] -> Int

numComponents :: [Vec 3 Bool] -> Int

arrayLen :: Vec 3 Bool -> Int

getGlslType :: [Vec 3 Bool] -> DataType

uniformSet :: GLint -> Vec 3 Bool -> IO ()

GLType (Vec 4 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Bool) -> String

showGlslVal :: Vec 4 Bool -> String

glMap :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool

glZipWith :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool

glZipWith3 :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool

eltSize :: [Vec 4 Bool] -> Int

numComponents :: [Vec 4 Bool] -> Int

arrayLen :: Vec 4 Bool -> Int

getGlslType :: [Vec 4 Bool] -> DataType

uniformSet :: GLint -> Vec 4 Bool -> IO ()

type DemoteRep Bool 
Instance details

Defined in GHC.Generics

type DemoteRep Bool = Bool
type Rep Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))
data Sing (a :: Bool) 
Instance details

Defined in GHC.Generics

data Sing (a :: Bool) where

data Mat (p :: Nat) (q :: Nat) (t :: *) Source #

A matrix with p rows, q columns, and element type t

Instances

Instances details
GLType [Vec 2 UInt] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 UInt] -> String

showGlslVal :: [Vec 2 UInt] -> String

glMap :: (GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt]) -> [Vec 2 UInt] -> [Vec 2 UInt]

glZipWith :: (GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt]) -> [Vec 2 UInt] -> [Vec 2 UInt] -> [Vec 2 UInt]

glZipWith3 :: (GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt] -> GLElt [Vec 2 UInt]) -> [Vec 2 UInt] -> [Vec 2 UInt] -> [Vec 2 UInt] -> [Vec 2 UInt]

eltSize :: [[Vec 2 UInt]] -> Int

numComponents :: [[Vec 2 UInt]] -> Int

arrayLen :: [Vec 2 UInt] -> Int

getGlslType :: [[Vec 2 UInt]] -> DataType

uniformSet :: GLint -> [Vec 2 UInt] -> IO ()

GLType [Vec 2 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Bool] -> String

showGlslVal :: [Vec 2 Bool] -> String

glMap :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool]

glZipWith :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool]

glZipWith3 :: (GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool] -> GLElt [Vec 2 Bool]) -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool] -> [Vec 2 Bool]

eltSize :: [[Vec 2 Bool]] -> Int

numComponents :: [[Vec 2 Bool]] -> Int

arrayLen :: [Vec 2 Bool] -> Int

getGlslType :: [[Vec 2 Bool]] -> DataType

uniformSet :: GLint -> [Vec 2 Bool] -> IO ()

GLType [Vec 2 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Double] -> String

showGlslVal :: [Vec 2 Double] -> String

glMap :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double]

glZipWith :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double]

glZipWith3 :: (GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double] -> GLElt [Vec 2 Double]) -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double] -> [Vec 2 Double]

eltSize :: [[Vec 2 Double]] -> Int

numComponents :: [[Vec 2 Double]] -> Int

arrayLen :: [Vec 2 Double] -> Int

getGlslType :: [[Vec 2 Double]] -> DataType

uniformSet :: GLint -> [Vec 2 Double] -> IO ()

GLType [Vec 2 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Float] -> String

showGlslVal :: [Vec 2 Float] -> String

glMap :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float]

glZipWith :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float]

glZipWith3 :: (GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float] -> GLElt [Vec 2 Float]) -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float] -> [Vec 2 Float]

eltSize :: [[Vec 2 Float]] -> Int

numComponents :: [[Vec 2 Float]] -> Int

arrayLen :: [Vec 2 Float] -> Int

getGlslType :: [[Vec 2 Float]] -> DataType

uniformSet :: GLint -> [Vec 2 Float] -> IO ()

GLType [Vec 2 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 2 Int] -> String

showGlslVal :: [Vec 2 Int] -> String

glMap :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int]

glZipWith :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int]

glZipWith3 :: (GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int] -> GLElt [Vec 2 Int]) -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int] -> [Vec 2 Int]

eltSize :: [[Vec 2 Int]] -> Int

numComponents :: [[Vec 2 Int]] -> Int

arrayLen :: [Vec 2 Int] -> Int

getGlslType :: [[Vec 2 Int]] -> DataType

uniformSet :: GLint -> [Vec 2 Int] -> IO ()

GLType [Vec 3 UInt] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 UInt] -> String

showGlslVal :: [Vec 3 UInt] -> String

glMap :: (GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt]) -> [Vec 3 UInt] -> [Vec 3 UInt]

glZipWith :: (GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt]) -> [Vec 3 UInt] -> [Vec 3 UInt] -> [Vec 3 UInt]

glZipWith3 :: (GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt] -> GLElt [Vec 3 UInt]) -> [Vec 3 UInt] -> [Vec 3 UInt] -> [Vec 3 UInt] -> [Vec 3 UInt]

eltSize :: [[Vec 3 UInt]] -> Int

numComponents :: [[Vec 3 UInt]] -> Int

arrayLen :: [Vec 3 UInt] -> Int

getGlslType :: [[Vec 3 UInt]] -> DataType

uniformSet :: GLint -> [Vec 3 UInt] -> IO ()

GLType [Vec 3 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Bool] -> String

showGlslVal :: [Vec 3 Bool] -> String

glMap :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool]

glZipWith :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool]

glZipWith3 :: (GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool] -> GLElt [Vec 3 Bool]) -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool] -> [Vec 3 Bool]

eltSize :: [[Vec 3 Bool]] -> Int

numComponents :: [[Vec 3 Bool]] -> Int

arrayLen :: [Vec 3 Bool] -> Int

getGlslType :: [[Vec 3 Bool]] -> DataType

uniformSet :: GLint -> [Vec 3 Bool] -> IO ()

GLType [Vec 3 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Double] -> String

showGlslVal :: [Vec 3 Double] -> String

glMap :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double]

glZipWith :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double]

glZipWith3 :: (GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double] -> GLElt [Vec 3 Double]) -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double] -> [Vec 3 Double]

eltSize :: [[Vec 3 Double]] -> Int

numComponents :: [[Vec 3 Double]] -> Int

arrayLen :: [Vec 3 Double] -> Int

getGlslType :: [[Vec 3 Double]] -> DataType

uniformSet :: GLint -> [Vec 3 Double] -> IO ()

GLType [Vec 3 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Float] -> String

showGlslVal :: [Vec 3 Float] -> String

glMap :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float]

glZipWith :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float]

glZipWith3 :: (GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float] -> GLElt [Vec 3 Float]) -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float] -> [Vec 3 Float]

eltSize :: [[Vec 3 Float]] -> Int

numComponents :: [[Vec 3 Float]] -> Int

arrayLen :: [Vec 3 Float] -> Int

getGlslType :: [[Vec 3 Float]] -> DataType

uniformSet :: GLint -> [Vec 3 Float] -> IO ()

GLType [Vec 3 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 3 Int] -> String

showGlslVal :: [Vec 3 Int] -> String

glMap :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int]

glZipWith :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int]

glZipWith3 :: (GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int] -> GLElt [Vec 3 Int]) -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int] -> [Vec 3 Int]

eltSize :: [[Vec 3 Int]] -> Int

numComponents :: [[Vec 3 Int]] -> Int

arrayLen :: [Vec 3 Int] -> Int

getGlslType :: [[Vec 3 Int]] -> DataType

uniformSet :: GLint -> [Vec 3 Int] -> IO ()

GLType [Vec 4 UInt] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 UInt] -> String

showGlslVal :: [Vec 4 UInt] -> String

glMap :: (GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt]) -> [Vec 4 UInt] -> [Vec 4 UInt]

glZipWith :: (GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt]) -> [Vec 4 UInt] -> [Vec 4 UInt] -> [Vec 4 UInt]

glZipWith3 :: (GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt] -> GLElt [Vec 4 UInt]) -> [Vec 4 UInt] -> [Vec 4 UInt] -> [Vec 4 UInt] -> [Vec 4 UInt]

eltSize :: [[Vec 4 UInt]] -> Int

numComponents :: [[Vec 4 UInt]] -> Int

arrayLen :: [Vec 4 UInt] -> Int

getGlslType :: [[Vec 4 UInt]] -> DataType

uniformSet :: GLint -> [Vec 4 UInt] -> IO ()

GLType [Vec 4 Bool] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Bool] -> String

showGlslVal :: [Vec 4 Bool] -> String

glMap :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool]

glZipWith :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool]

glZipWith3 :: (GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool] -> GLElt [Vec 4 Bool]) -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool] -> [Vec 4 Bool]

eltSize :: [[Vec 4 Bool]] -> Int

numComponents :: [[Vec 4 Bool]] -> Int

arrayLen :: [Vec 4 Bool] -> Int

getGlslType :: [[Vec 4 Bool]] -> DataType

uniformSet :: GLint -> [Vec 4 Bool] -> IO ()

GLType [Vec 4 Double] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Double] -> String

showGlslVal :: [Vec 4 Double] -> String

glMap :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double]

glZipWith :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double]

glZipWith3 :: (GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double] -> GLElt [Vec 4 Double]) -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double] -> [Vec 4 Double]

eltSize :: [[Vec 4 Double]] -> Int

numComponents :: [[Vec 4 Double]] -> Int

arrayLen :: [Vec 4 Double] -> Int

getGlslType :: [[Vec 4 Double]] -> DataType

uniformSet :: GLint -> [Vec 4 Double] -> IO ()

GLType [Vec 4 Float] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Float] -> String

showGlslVal :: [Vec 4 Float] -> String

glMap :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float]

glZipWith :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float]

glZipWith3 :: (GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float] -> GLElt [Vec 4 Float]) -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float] -> [Vec 4 Float]

eltSize :: [[Vec 4 Float]] -> Int

numComponents :: [[Vec 4 Float]] -> Int

arrayLen :: [Vec 4 Float] -> Int

getGlslType :: [[Vec 4 Float]] -> DataType

uniformSet :: GLint -> [Vec 4 Float] -> IO ()

GLType [Vec 4 Int] Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a [Vec 4 Int] -> String

showGlslVal :: [Vec 4 Int] -> String

glMap :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int]

glZipWith :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int]

glZipWith3 :: (GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int] -> GLElt [Vec 4 Int]) -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int] -> [Vec 4 Int]

eltSize :: [[Vec 4 Int]] -> Int

numComponents :: [[Vec 4 Int]] -> Int

arrayLen :: [Vec 4 Int] -> Int

getGlslType :: [[Vec 4 Int]] -> DataType

uniformSet :: GLint -> [Vec 4 Int] -> IO ()

(GLPrim t, GLType (Mat p 2 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 2 t)) Source #

Methods

decon :: GLExpr d (Mat p 2 t) -> Decon (GLExpr d (Mat p 2 t)) Source #

(GLPrim t, GLType (Mat p 3 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 3 t)) Source #

Methods

decon :: GLExpr d (Mat p 3 t) -> Decon (GLExpr d (Mat p 3 t)) Source #

(GLPrim t, GLType (Mat p 4 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 4 t)) Source #

Methods

decon :: GLExpr d (Mat p 4 t) -> Decon (GLExpr d (Mat p 4 t)) Source #

(GLPrim t, GLType (Vec 2 t)) => Deconstructible (GLExpr d (Vec 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 2 t)) Source #

Methods

decon :: GLExpr d (Vec 2 t) -> Decon (GLExpr d (Vec 2 t)) Source #

(GLPrim t, GLType (Vec 3 t)) => Deconstructible (GLExpr d (Vec 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 3 t)) Source #

Methods

decon :: GLExpr d (Vec 3 t) -> Decon (GLExpr d (Vec 3 t)) Source #

(GLPrim t, GLType (Vec 4 t)) => Deconstructible (GLExpr d (Vec 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 4 t)) Source #

Methods

decon :: GLExpr d (Vec 4 t) -> Decon (GLExpr d (Vec 4 t)) Source #

GLInputType (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 UInt)

Methods

toStorableList :: [Vec 2 UInt] -> [StoreElt (Vec 2 UInt)]

GLInputType (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 Float)

Methods

toStorableList :: [Vec 2 Float] -> [StoreElt (Vec 2 Float)]

GLInputType (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 Int)

Methods

toStorableList :: [Vec 2 Int] -> [StoreElt (Vec 2 Int)]

GLInputType (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 UInt)

Methods

toStorableList :: [Vec 3 UInt] -> [StoreElt (Vec 3 UInt)]

GLInputType (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 Float)

Methods

toStorableList :: [Vec 3 Float] -> [StoreElt (Vec 3 Float)]

GLInputType (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 Int)

Methods

toStorableList :: [Vec 3 Int] -> [StoreElt (Vec 3 Int)]

GLInputType (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 UInt)

Methods

toStorableList :: [Vec 4 UInt] -> [StoreElt (Vec 4 UInt)]

GLInputType (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 Float)

Methods

toStorableList :: [Vec 4 Float] -> [StoreElt (Vec 4 Float)]

GLInputType (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 Int)

Methods

toStorableList :: [Vec 4 Int] -> [StoreElt (Vec 4 Int)]

GLPrimOrVec (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 UInt) -> String

showGlslVal :: Vec 2 UInt -> String

glMap :: (GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt)) -> Vec 2 UInt -> Vec 2 UInt

glZipWith :: (GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt)) -> Vec 2 UInt -> Vec 2 UInt -> Vec 2 UInt

glZipWith3 :: (GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt) -> GLElt (Vec 2 UInt)) -> Vec 2 UInt -> Vec 2 UInt -> Vec 2 UInt -> Vec 2 UInt

eltSize :: [Vec 2 UInt] -> Int

numComponents :: [Vec 2 UInt] -> Int

arrayLen :: Vec 2 UInt -> Int

getGlslType :: [Vec 2 UInt] -> DataType

uniformSet :: GLint -> Vec 2 UInt -> IO ()

GLType (Vec 2 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Bool) -> String

showGlslVal :: Vec 2 Bool -> String

glMap :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool

glZipWith :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool

glZipWith3 :: (GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool) -> GLElt (Vec 2 Bool)) -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool -> Vec 2 Bool

eltSize :: [Vec 2 Bool] -> Int

numComponents :: [Vec 2 Bool] -> Int

arrayLen :: Vec 2 Bool -> Int

getGlslType :: [Vec 2 Bool] -> DataType

uniformSet :: GLint -> Vec 2 Bool -> IO ()

GLType (Vec 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Float) -> String

showGlslVal :: Vec 2 Float -> String

glMap :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float

glZipWith :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float

glZipWith3 :: (GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float) -> GLElt (Vec 2 Float)) -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float -> Vec 2 Float

eltSize :: [Vec 2 Float] -> Int

numComponents :: [Vec 2 Float] -> Int

arrayLen :: Vec 2 Float -> Int

getGlslType :: [Vec 2 Float] -> DataType

uniformSet :: GLint -> Vec 2 Float -> IO ()

GLType (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 2 Int) -> String

showGlslVal :: Vec 2 Int -> String

glMap :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int

glZipWith :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int

glZipWith3 :: (GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int) -> GLElt (Vec 2 Int)) -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int -> Vec 2 Int

eltSize :: [Vec 2 Int] -> Int

numComponents :: [Vec 2 Int] -> Int

arrayLen :: Vec 2 Int -> Int

getGlslType :: [Vec 2 Int] -> DataType

uniformSet :: GLint -> Vec 2 Int -> IO ()

GLType (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 UInt) -> String

showGlslVal :: Vec 3 UInt -> String

glMap :: (GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt)) -> Vec 3 UInt -> Vec 3 UInt

glZipWith :: (GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt)) -> Vec 3 UInt -> Vec 3 UInt -> Vec 3 UInt

glZipWith3 :: (GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt) -> GLElt (Vec 3 UInt)) -> Vec 3 UInt -> Vec 3 UInt -> Vec 3 UInt -> Vec 3 UInt

eltSize :: [Vec 3 UInt] -> Int

numComponents :: [Vec 3 UInt] -> Int

arrayLen :: Vec 3 UInt -> Int

getGlslType :: [Vec 3 UInt] -> DataType

uniformSet :: GLint -> Vec 3 UInt -> IO ()

GLType (Vec 3 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Bool) -> String

showGlslVal :: Vec 3 Bool -> String

glMap :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool

glZipWith :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool

glZipWith3 :: (GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool) -> GLElt (Vec 3 Bool)) -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool -> Vec 3 Bool

eltSize :: [Vec 3 Bool] -> Int

numComponents :: [Vec 3 Bool] -> Int

arrayLen :: Vec 3 Bool -> Int

getGlslType :: [Vec 3 Bool] -> DataType

uniformSet :: GLint -> Vec 3 Bool -> IO ()

GLType (Vec 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Float) -> String

showGlslVal :: Vec 3 Float -> String

glMap :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float

glZipWith :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float

glZipWith3 :: (GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float) -> GLElt (Vec 3 Float)) -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float -> Vec 3 Float

eltSize :: [Vec 3 Float] -> Int

numComponents :: [Vec 3 Float] -> Int

arrayLen :: Vec 3 Float -> Int

getGlslType :: [Vec 3 Float] -> DataType

uniformSet :: GLint -> Vec 3 Float -> IO ()

GLType (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 3 Int) -> String

showGlslVal :: Vec 3 Int -> String

glMap :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int

glZipWith :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int

glZipWith3 :: (GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int) -> GLElt (Vec 3 Int)) -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int -> Vec 3 Int

eltSize :: [Vec 3 Int] -> Int

numComponents :: [Vec 3 Int] -> Int

arrayLen :: Vec 3 Int -> Int

getGlslType :: [Vec 3 Int] -> DataType

uniformSet :: GLint -> Vec 3 Int -> IO ()

GLType (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 UInt) -> String

showGlslVal :: Vec 4 UInt -> String

glMap :: (GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt)) -> Vec 4 UInt -> Vec 4 UInt

glZipWith :: (GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt)) -> Vec 4 UInt -> Vec 4 UInt -> Vec 4 UInt

glZipWith3 :: (GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt) -> GLElt (Vec 4 UInt)) -> Vec 4 UInt -> Vec 4 UInt -> Vec 4 UInt -> Vec 4 UInt

eltSize :: [Vec 4 UInt] -> Int

numComponents :: [Vec 4 UInt] -> Int

arrayLen :: Vec 4 UInt -> Int

getGlslType :: [Vec 4 UInt] -> DataType

uniformSet :: GLint -> Vec 4 UInt -> IO ()

GLType (Vec 4 Bool) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Bool) -> String

showGlslVal :: Vec 4 Bool -> String

glMap :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool

glZipWith :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool

glZipWith3 :: (GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool) -> GLElt (Vec 4 Bool)) -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool -> Vec 4 Bool

eltSize :: [Vec 4 Bool] -> Int

numComponents :: [Vec 4 Bool] -> Int

arrayLen :: Vec 4 Bool -> Int

getGlslType :: [Vec 4 Bool] -> DataType

uniformSet :: GLint -> Vec 4 Bool -> IO ()

GLType (Vec 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLType (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Float) -> String

showGlslVal :: Vec 4 Float -> String

glMap :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float

glZipWith :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float

glZipWith3 :: (GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float) -> GLElt (Vec 4 Float)) -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float -> Vec 4 Float

eltSize :: [Vec 4 Float] -> Int

numComponents :: [Vec 4 Float] -> Int

arrayLen :: Vec 4 Float -> Int

getGlslType :: [Vec 4 Float] -> DataType

uniformSet :: GLint -> Vec 4 Float -> IO ()

GLType (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Vec 4 Int) -> String

showGlslVal :: Vec 4 Int -> String

glMap :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int

glZipWith :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int

glZipWith3 :: (GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int) -> GLElt (Vec 4 Int)) -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int -> Vec 4 Int

eltSize :: [Vec 4 Int] -> Int

numComponents :: [Vec 4 Int] -> Int

arrayLen :: Vec 4 Int -> Int

getGlslType :: [Vec 4 Int] -> DataType

uniformSet :: GLint -> Vec 4 Int -> IO ()

Foldable (Mat p q) Source # 
Instance details

Defined in Graphics.HaGL.Numerical

Methods

fold :: Monoid m => Mat p q m -> m #

foldMap :: Monoid m => (a -> m) -> Mat p q a -> m #

foldMap' :: Monoid m => (a -> m) -> Mat p q a -> m #

foldr :: (a -> b -> b) -> b -> Mat p q a -> b #

foldr' :: (a -> b -> b) -> b -> Mat p q a -> b #

foldl :: (b -> a -> b) -> b -> Mat p q a -> b #

foldl' :: (b -> a -> b) -> b -> Mat p q a -> b #

foldr1 :: (a -> a -> a) -> Mat p q a -> a #

foldl1 :: (a -> a -> a) -> Mat p q a -> a #

toList :: Mat p q a -> [a] #

null :: Mat p q a -> Bool #

length :: Mat p q a -> Int #

elem :: Eq a => a -> Mat p q a -> Bool #

maximum :: Ord a => Mat p q a -> a #

minimum :: Ord a => Mat p q a -> a #

sum :: Num a => Mat p q a -> a #

product :: Num a => Mat p q a -> a #

(KnownNat p, KnownNat q) => Applicative (Mat p q) Source # 
Instance details

Defined in Graphics.HaGL.Numerical

Methods

pure :: a -> Mat p q a #

(<*>) :: Mat p q (a -> b) -> Mat p q a -> Mat p q b #

liftA2 :: (a -> b -> c) -> Mat p q a -> Mat p q b -> Mat p q c #

(*>) :: Mat p q a -> Mat p q b -> Mat p q b #

(<*) :: Mat p q a -> Mat p q b -> Mat p q a #

Functor (Mat p q) Source # 
Instance details

Defined in Graphics.HaGL.Numerical

Methods

fmap :: (a -> b) -> Mat p q a -> Mat p q b #

(<$) :: a -> Mat p q b -> Mat p q a #

(GLType (Vec n UInt), GLType (Vec n Int), GLType (Vec n Bool), KnownNat n) => Num (GLExpr d (Vec n UInt)) Source # 
Instance details

Defined in Graphics.HaGL

Methods

(+) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

(-) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

(*) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

negate :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

abs :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

signum :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

fromInteger :: Integer -> GLExpr d (Vec n UInt) #

GLType (Mat 2 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 2 Double) -> String

showGlslVal :: Mat 2 2 Double -> String

glMap :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double

glZipWith :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double

glZipWith3 :: (GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double) -> GLElt (Mat 2 2 Double)) -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double -> Mat 2 2 Double

eltSize :: [Mat 2 2 Double] -> Int

numComponents :: [Mat 2 2 Double] -> Int

arrayLen :: Mat 2 2 Double -> Int

getGlslType :: [Mat 2 2 Double] -> DataType

uniformSet :: GLint -> Mat 2 2 Double -> IO ()

GLType (Mat 2 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 2 Float) -> String

showGlslVal :: Mat 2 2 Float -> String

glMap :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float

glZipWith :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float

glZipWith3 :: (GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float) -> GLElt (Mat 2 2 Float)) -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float -> Mat 2 2 Float

eltSize :: [Mat 2 2 Float] -> Int

numComponents :: [Mat 2 2 Float] -> Int

arrayLen :: Mat 2 2 Float -> Int

getGlslType :: [Mat 2 2 Float] -> DataType

uniformSet :: GLint -> Mat 2 2 Float -> IO ()

GLType (Mat 2 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 3 Double) -> String

showGlslVal :: Mat 2 3 Double -> String

glMap :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double

glZipWith :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double

glZipWith3 :: (GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double) -> GLElt (Mat 2 3 Double)) -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double -> Mat 2 3 Double

eltSize :: [Mat 2 3 Double] -> Int

numComponents :: [Mat 2 3 Double] -> Int

arrayLen :: Mat 2 3 Double -> Int

getGlslType :: [Mat 2 3 Double] -> DataType

uniformSet :: GLint -> Mat 2 3 Double -> IO ()

GLType (Mat 2 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 3 Float) -> String

showGlslVal :: Mat 2 3 Float -> String

glMap :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float

glZipWith :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float

glZipWith3 :: (GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float) -> GLElt (Mat 2 3 Float)) -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float -> Mat 2 3 Float

eltSize :: [Mat 2 3 Float] -> Int

numComponents :: [Mat 2 3 Float] -> Int

arrayLen :: Mat 2 3 Float -> Int

getGlslType :: [Mat 2 3 Float] -> DataType

uniformSet :: GLint -> Mat 2 3 Float -> IO ()

GLType (Mat 2 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 4 Double) -> String

showGlslVal :: Mat 2 4 Double -> String

glMap :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double

glZipWith :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double

glZipWith3 :: (GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double) -> GLElt (Mat 2 4 Double)) -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double -> Mat 2 4 Double

eltSize :: [Mat 2 4 Double] -> Int

numComponents :: [Mat 2 4 Double] -> Int

arrayLen :: Mat 2 4 Double -> Int

getGlslType :: [Mat 2 4 Double] -> DataType

uniformSet :: GLint -> Mat 2 4 Double -> IO ()

GLType (Mat 2 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 2 4 Float) -> String

showGlslVal :: Mat 2 4 Float -> String

glMap :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float

glZipWith :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float

glZipWith3 :: (GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float) -> GLElt (Mat 2 4 Float)) -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float -> Mat 2 4 Float

eltSize :: [Mat 2 4 Float] -> Int

numComponents :: [Mat 2 4 Float] -> Int

arrayLen :: Mat 2 4 Float -> Int

getGlslType :: [Mat 2 4 Float] -> DataType

uniformSet :: GLint -> Mat 2 4 Float -> IO ()

GLType (Mat 3 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 2 Double) -> String

showGlslVal :: Mat 3 2 Double -> String

glMap :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double

glZipWith :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double

glZipWith3 :: (GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double) -> GLElt (Mat 3 2 Double)) -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double -> Mat 3 2 Double

eltSize :: [Mat 3 2 Double] -> Int

numComponents :: [Mat 3 2 Double] -> Int

arrayLen :: Mat 3 2 Double -> Int

getGlslType :: [Mat 3 2 Double] -> DataType

uniformSet :: GLint -> Mat 3 2 Double -> IO ()

GLType (Mat 3 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 2 Float) -> String

showGlslVal :: Mat 3 2 Float -> String

glMap :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float

glZipWith :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float

glZipWith3 :: (GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float) -> GLElt (Mat 3 2 Float)) -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float -> Mat 3 2 Float

eltSize :: [Mat 3 2 Float] -> Int

numComponents :: [Mat 3 2 Float] -> Int

arrayLen :: Mat 3 2 Float -> Int

getGlslType :: [Mat 3 2 Float] -> DataType

uniformSet :: GLint -> Mat 3 2 Float -> IO ()

GLType (Mat 3 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 3 Double) -> String

showGlslVal :: Mat 3 3 Double -> String

glMap :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double

glZipWith :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double

glZipWith3 :: (GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double) -> GLElt (Mat 3 3 Double)) -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double -> Mat 3 3 Double

eltSize :: [Mat 3 3 Double] -> Int

numComponents :: [Mat 3 3 Double] -> Int

arrayLen :: Mat 3 3 Double -> Int

getGlslType :: [Mat 3 3 Double] -> DataType

uniformSet :: GLint -> Mat 3 3 Double -> IO ()

GLType (Mat 3 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 3 Float) -> String

showGlslVal :: Mat 3 3 Float -> String

glMap :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float

glZipWith :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float

glZipWith3 :: (GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float) -> GLElt (Mat 3 3 Float)) -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float -> Mat 3 3 Float

eltSize :: [Mat 3 3 Float] -> Int

numComponents :: [Mat 3 3 Float] -> Int

arrayLen :: Mat 3 3 Float -> Int

getGlslType :: [Mat 3 3 Float] -> DataType

uniformSet :: GLint -> Mat 3 3 Float -> IO ()

GLType (Mat 3 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 4 Double) -> String

showGlslVal :: Mat 3 4 Double -> String

glMap :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double

glZipWith :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double

glZipWith3 :: (GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double) -> GLElt (Mat 3 4 Double)) -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double -> Mat 3 4 Double

eltSize :: [Mat 3 4 Double] -> Int

numComponents :: [Mat 3 4 Double] -> Int

arrayLen :: Mat 3 4 Double -> Int

getGlslType :: [Mat 3 4 Double] -> DataType

uniformSet :: GLint -> Mat 3 4 Double -> IO ()

GLType (Mat 3 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 3 4 Float) -> String

showGlslVal :: Mat 3 4 Float -> String

glMap :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float

glZipWith :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float

glZipWith3 :: (GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float) -> GLElt (Mat 3 4 Float)) -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float -> Mat 3 4 Float

eltSize :: [Mat 3 4 Float] -> Int

numComponents :: [Mat 3 4 Float] -> Int

arrayLen :: Mat 3 4 Float -> Int

getGlslType :: [Mat 3 4 Float] -> DataType

uniformSet :: GLint -> Mat 3 4 Float -> IO ()

GLType (Mat 4 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 2 Double) -> String

showGlslVal :: Mat 4 2 Double -> String

glMap :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double

glZipWith :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double

glZipWith3 :: (GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double) -> GLElt (Mat 4 2 Double)) -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double -> Mat 4 2 Double

eltSize :: [Mat 4 2 Double] -> Int

numComponents :: [Mat 4 2 Double] -> Int

arrayLen :: Mat 4 2 Double -> Int

getGlslType :: [Mat 4 2 Double] -> DataType

uniformSet :: GLint -> Mat 4 2 Double -> IO ()

GLType (Mat 4 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 2 Float) -> String

showGlslVal :: Mat 4 2 Float -> String

glMap :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float

glZipWith :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float

glZipWith3 :: (GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float) -> GLElt (Mat 4 2 Float)) -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float -> Mat 4 2 Float

eltSize :: [Mat 4 2 Float] -> Int

numComponents :: [Mat 4 2 Float] -> Int

arrayLen :: Mat 4 2 Float -> Int

getGlslType :: [Mat 4 2 Float] -> DataType

uniformSet :: GLint -> Mat 4 2 Float -> IO ()

GLType (Mat 4 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 3 Double) -> String

showGlslVal :: Mat 4 3 Double -> String

glMap :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double

glZipWith :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double

glZipWith3 :: (GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double) -> GLElt (Mat 4 3 Double)) -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double -> Mat 4 3 Double

eltSize :: [Mat 4 3 Double] -> Int

numComponents :: [Mat 4 3 Double] -> Int

arrayLen :: Mat 4 3 Double -> Int

getGlslType :: [Mat 4 3 Double] -> DataType

uniformSet :: GLint -> Mat 4 3 Double -> IO ()

GLType (Mat 4 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 3 Float) -> String

showGlslVal :: Mat 4 3 Float -> String

glMap :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float

glZipWith :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float

glZipWith3 :: (GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float) -> GLElt (Mat 4 3 Float)) -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float -> Mat 4 3 Float

eltSize :: [Mat 4 3 Float] -> Int

numComponents :: [Mat 4 3 Float] -> Int

arrayLen :: Mat 4 3 Float -> Int

getGlslType :: [Mat 4 3 Float] -> DataType

uniformSet :: GLint -> Mat 4 3 Float -> IO ()

GLType (Mat 4 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 4 Double) -> String

showGlslVal :: Mat 4 4 Double -> String

glMap :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double

glZipWith :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double

glZipWith3 :: (GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double) -> GLElt (Mat 4 4 Double)) -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double -> Mat 4 4 Double

eltSize :: [Mat 4 4 Double] -> Int

numComponents :: [Mat 4 4 Double] -> Int

arrayLen :: Mat 4 4 Double -> Int

getGlslType :: [Mat 4 4 Double] -> DataType

uniformSet :: GLint -> Mat 4 4 Double -> IO ()

GLType (Mat 4 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

showGlslType :: a (Mat 4 4 Float) -> String

showGlslVal :: Mat 4 4 Float -> String

glMap :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float

glZipWith :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float

glZipWith3 :: (GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float) -> GLElt (Mat 4 4 Float)) -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float -> Mat 4 4 Float

eltSize :: [Mat 4 4 Float] -> Int

numComponents :: [Mat 4 4 Float] -> Int

arrayLen :: Mat 4 4 Float -> Int

getGlslType :: [Mat 4 4 Float] -> DataType

uniformSet :: GLint -> Mat 4 4 Float -> IO ()

(KnownNat p, KnownNat q, Num t) => Num (Mat p q t) Source # 
Instance details

Defined in Graphics.HaGL.Numerical

Methods

(+) :: Mat p q t -> Mat p q t -> Mat p q t #

(-) :: Mat p q t -> Mat p q t -> Mat p q t #

(*) :: Mat p q t -> Mat p q t -> Mat p q t #

negate :: Mat p q t -> Mat p q t #

abs :: Mat p q t -> Mat p q t #

signum :: Mat p q t -> Mat p q t #

fromInteger :: Integer -> Mat p q t #

(KnownNat p, KnownNat q, Fractional t) => Fractional (Mat p q t) Source # 
Instance details

Defined in Graphics.HaGL.Numerical

Methods

(/) :: Mat p q t -> Mat p q t -> Mat p q t #

recip :: Mat p q t -> Mat p q t #

fromRational :: Rational -> Mat p q t #

Show t => Show (Mat p q t) Source # 
Instance details

Defined in Graphics.HaGL.Numerical

Methods

showsPrec :: Int -> Mat p q t -> ShowS #

show :: Mat p q t -> String #

showList :: [Mat p q t] -> ShowS #

Eq t => Eq (Mat p q t) Source # 
Instance details

Defined in Graphics.HaGL.Numerical

Methods

(==) :: Mat p q t -> Mat p q t -> Bool #

(/=) :: Mat p q t -> Mat p q t -> Bool #

type Decon (GLExpr d (Mat p 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Mat p 2 t)) = (GLExpr d (Vec p t), GLExpr d (Vec p t))
type Decon (GLExpr d (Mat p 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Mat p 3 t)) = (GLExpr d (Vec p t), GLExpr d (Vec p t), GLExpr d (Vec p t))
type Decon (GLExpr d (Mat p 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Mat p 4 t)) = (GLExpr d (Vec p t), GLExpr d (Vec p t), GLExpr d (Vec p t), GLExpr d (Vec p t))
type Decon (GLExpr d (Vec 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Vec 2 t)) = (GLExpr d t, GLExpr d t)
type Decon (GLExpr d (Vec 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Vec 3 t)) = (GLExpr d t, GLExpr d t, GLExpr d t)
type Decon (GLExpr d (Vec 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Vec 4 t)) = (GLExpr d t, GLExpr d t, GLExpr d t, GLExpr d t)

type Vec n t = Mat n 1 t Source #

A column vector with n elements and element type t

type family GLElt t where ... Source #

The type of the elements of t or t itself if t is primitive

Equations

GLElt (Mat r c t) = t 
GLElt [t] = t 
GLElt Float = Float 
GLElt Double = Double 
GLElt Int = Int 
GLElt UInt = UInt 
GLElt Bool = Bool 

Raw vector/matrix constructors

Though raw types are not usually constructed directly, the following functions can be used for loading data from externally computed arrays via lifts.

fromMapping :: forall p q t. (KnownNat p, KnownNat q) => ((Int, Int) -> t) -> Mat p q t Source #

Construct a matrix from a mapping that maps indices (i, j) to the element at row i and column j

fromList :: forall p q t. (KnownNat p, KnownNat q) => [t] -> Mat p q t Source #

Construct a matrix from a list of the matrix elements in row-major order

Subclasses of GLType

class (GLType t, Storable t, Enum t, Eq t, Ord t) => GLPrim t Source #

Any primitive type

Minimal complete definition

glCast

Instances

Instances details
GLPrim UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> UInt

GLPrim Bool Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Bool

GLPrim Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Double

GLPrim Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Float

GLPrim Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

glCast :: GLPrim t0 => t0 -> Int

class (GLPrim t, Storable t, Enum t, Eq t, Ord t) => GLSingle t Source #

Any single-precision primitive type

Instances

Instances details
GLSingle UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingle Bool Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingle Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingle Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

class (GLPrim t, Num t) => GLNumeric t Source #

Any numeric primitive type

Minimal complete definition

genDiv

Instances

Instances details
GLNumeric UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

genDiv :: UInt -> UInt -> UInt

GLNumeric Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

genDiv :: Double -> Double -> Double

GLNumeric Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

genDiv :: Float -> Float -> Float

GLNumeric Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

Methods

genDiv :: Int -> Int -> Int

class GLNumeric t => GLSigned t Source #

Any signed primitive type

Instances

Instances details
GLSigned Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSigned Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSigned Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

class (GLSigned t, RealFrac t, Floating t) => GLFloating t Source #

Any single- or double-precision floating-point type

Instances

Instances details
GLFloating Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLFloating Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

class GLSigned t => GLSingleNumeric t Source #

Any single-precision signed primitive type

Instances

Instances details
GLSingleNumeric Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSingleNumeric Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

class (GLPrim t, Integral t, Bits t) => GLInteger t Source #

Any signed or unsigned integer type

Instances

Instances details
GLInteger UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLInteger Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

class GLType t => GLPrimOrVec t Source #

A primitive type or a vector type

Instances

Instances details
GLPrimOrVec UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec Double Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 2 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Double) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLPrimOrVec (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

class (GLPrimOrVec t, Storable (StoreElt t)) => GLInputType t Source #

The underlying type of a vertex input variable. Double-precision types are currently not permitted due to an issue in the OpenGL bindings.

Minimal complete definition

toStorableList

Instances

Instances details
GLInputType UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt UInt

Methods

toStorableList :: [UInt] -> [StoreElt UInt]

GLInputType Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt Float

Methods

toStorableList :: [Float] -> [StoreElt Float]

GLInputType Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt Int

Methods

toStorableList :: [Int] -> [StoreElt Int]

GLInputType (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 UInt)

Methods

toStorableList :: [Vec 2 UInt] -> [StoreElt (Vec 2 UInt)]

GLInputType (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 Float)

Methods

toStorableList :: [Vec 2 Float] -> [StoreElt (Vec 2 Float)]

GLInputType (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 2 Int)

Methods

toStorableList :: [Vec 2 Int] -> [StoreElt (Vec 2 Int)]

GLInputType (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 UInt)

Methods

toStorableList :: [Vec 3 UInt] -> [StoreElt (Vec 3 UInt)]

GLInputType (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 Float)

Methods

toStorableList :: [Vec 3 Float] -> [StoreElt (Vec 3 Float)]

GLInputType (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 3 Int)

Methods

toStorableList :: [Vec 3 Int] -> [StoreElt (Vec 3 Int)]

GLInputType (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 UInt)

Methods

toStorableList :: [Vec 4 UInt] -> [StoreElt (Vec 4 UInt)]

GLInputType (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 Float)

Methods

toStorableList :: [Vec 4 Float] -> [StoreElt (Vec 4 Float)]

GLInputType (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

Associated Types

type StoreElt (Vec 4 Int)

Methods

toStorableList :: [Vec 4 Int] -> [StoreElt (Vec 4 Int)]

class GLInputType t => GLSupportsSmoothInterp t Source #

Any type whose values can be interpolated smoothly when constructing a fragment variable

Instances

Instances details
GLSupportsSmoothInterp Float Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 2 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 3 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsSmoothInterp (Vec 4 Float) Source # 
Instance details

Defined in Graphics.HaGL.GLType

class (GLType t, Integral (GLElt t), Bits (GLElt t)) => GLSupportsBitwiseOps t Source #

Any type which supports bitwise operations

Instances

Instances details
GLSupportsBitwiseOps UInt Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps Int Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 2 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 2 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 3 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 3 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 4 UInt) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLSupportsBitwiseOps (Vec 4 Int) Source # 
Instance details

Defined in Graphics.HaGL.GLType

GLExpr

A HaGL expression can be created in one of the following ways:

data GLExpr (d :: GLDomain) (t :: *) Source #

A generic HaGL expression with domain of computation d and underlying type t

Instances

Instances details
GLPrim t => Enum (ConstExpr t) Source # 
Instance details

Defined in Graphics.HaGL

(GLPrim t, GLType (Mat p 2 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 2 t)) Source #

Methods

decon :: GLExpr d (Mat p 2 t) -> Decon (GLExpr d (Mat p 2 t)) Source #

(GLPrim t, GLType (Mat p 3 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 3 t)) Source #

Methods

decon :: GLExpr d (Mat p 3 t) -> Decon (GLExpr d (Mat p 3 t)) Source #

(GLPrim t, GLType (Mat p 4 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 4 t)) Source #

Methods

decon :: GLExpr d (Mat p 4 t) -> Decon (GLExpr d (Mat p 4 t)) Source #

(GLPrim t, GLType (Vec 2 t)) => Deconstructible (GLExpr d (Vec 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 2 t)) Source #

Methods

decon :: GLExpr d (Vec 2 t) -> Decon (GLExpr d (Vec 2 t)) Source #

(GLPrim t, GLType (Vec 3 t)) => Deconstructible (GLExpr d (Vec 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 3 t)) Source #

Methods

decon :: GLExpr d (Vec 3 t) -> Decon (GLExpr d (Vec 3 t)) Source #

(GLPrim t, GLType (Vec 4 t)) => Deconstructible (GLExpr d (Vec 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 4 t)) Source #

Methods

decon :: GLExpr d (Vec 4 t) -> Decon (GLExpr d (Vec 4 t)) Source #

(GLElt t ~ Float, GLPrimOrVec t, Fractional t) => Floating (GLExpr d t) Source # 
Instance details

Defined in Graphics.HaGL

Methods

pi :: GLExpr d t #

exp :: GLExpr d t -> GLExpr d t #

log :: GLExpr d t -> GLExpr d t #

sqrt :: GLExpr d t -> GLExpr d t #

(**) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

logBase :: GLExpr d t -> GLExpr d t -> GLExpr d t #

sin :: GLExpr d t -> GLExpr d t #

cos :: GLExpr d t -> GLExpr d t #

tan :: GLExpr d t -> GLExpr d t #

asin :: GLExpr d t -> GLExpr d t #

acos :: GLExpr d t -> GLExpr d t #

atan :: GLExpr d t -> GLExpr d t #

sinh :: GLExpr d t -> GLExpr d t #

cosh :: GLExpr d t -> GLExpr d t #

tanh :: GLExpr d t -> GLExpr d t #

asinh :: GLExpr d t -> GLExpr d t #

acosh :: GLExpr d t -> GLExpr d t #

atanh :: GLExpr d t -> GLExpr d t #

log1p :: GLExpr d t -> GLExpr d t #

expm1 :: GLExpr d t -> GLExpr d t #

log1pexp :: GLExpr d t -> GLExpr d t #

log1mexp :: GLExpr d t -> GLExpr d t #

Num (GLExpr d UInt) Source # 
Instance details

Defined in Graphics.HaGL

(GLType (Vec n UInt), GLType (Vec n Int), GLType (Vec n Bool), KnownNat n) => Num (GLExpr d (Vec n UInt)) Source # 
Instance details

Defined in Graphics.HaGL

Methods

(+) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

(-) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

(*) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

negate :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

abs :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

signum :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

fromInteger :: Integer -> GLExpr d (Vec n UInt) #

(GLSigned (GLElt t), GLPrimOrVec t, Num t) => Num (GLExpr d t) Source # 
Instance details

Defined in Graphics.HaGL

Methods

(+) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

(-) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

(*) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

negate :: GLExpr d t -> GLExpr d t #

abs :: GLExpr d t -> GLExpr d t #

signum :: GLExpr d t -> GLExpr d t #

fromInteger :: Integer -> GLExpr d t #

(GLFloating (GLElt t), GLPrimOrVec t, Fractional t) => Fractional (GLExpr d t) Source # 
Instance details

Defined in Graphics.HaGL

Methods

(/) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

recip :: GLExpr d t -> GLExpr d t #

fromRational :: Rational -> GLExpr d t #

type Decon (GLExpr d (Mat p 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Mat p 2 t)) = (GLExpr d (Vec p t), GLExpr d (Vec p t))
type Decon (GLExpr d (Mat p 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Mat p 3 t)) = (GLExpr d (Vec p t), GLExpr d (Vec p t), GLExpr d (Vec p t))
type Decon (GLExpr d (Mat p 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Mat p 4 t)) = (GLExpr d (Vec p t), GLExpr d (Vec p t), GLExpr d (Vec p t), GLExpr d (Vec p t))
type Decon (GLExpr d (Vec 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Vec 2 t)) = (GLExpr d t, GLExpr d t)
type Decon (GLExpr d (Vec 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Vec 3 t)) = (GLExpr d t, GLExpr d t, GLExpr d t)
type Decon (GLExpr d (Vec 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

type Decon (GLExpr d (Vec 4 t)) = (GLExpr d t, GLExpr d t, GLExpr d t, GLExpr d t)

data GLDomain Source #

A label for the domain where a given computation make take place

Constructors

ConstDomain

Labels a constant value computed on the host CPU

HostDomain

Labels a potentially I/O-dependent value computed on the host CPU

VertexDomain

Labels a vertex shader variable

FragmentDomain

Labels a fragment shader variable

Instances

Instances details
Show GLDomain Source # 
Instance details

Defined in Graphics.HaGL.Print

Eq GLDomain Source # 
Instance details

Defined in Graphics.HaGL.GLExpr

Ord GLDomain Source # 
Instance details

Defined in Graphics.HaGL.GLExpr

Constructors

cnst :: GLType t => ConstExpr t -> GLExpr d t Source #

Construct a GLExpr from a raw type. Rarely useful as this can be done implicitly; e.g., from a numeric literal.

true :: GLExpr d Bool Source #

The boolean value true

false :: GLExpr d Bool Source #

The boolean value false

uniform :: GLType t => HostExpr t -> GLExpr d t Source #

Lift a HostExpr to an arbitrary GLExpr whose value is the same across any primitive processed in a shader, if used in the context of one

prec :: GLType t => HostExpr t -> HostExpr t -> HostExpr t Source #

prec x0 x is used to obtain a reference to the value x one "time-step" in the past, or x0 at the zero-th point in time. The prec operator is usually used to define expressions recurrently; for example: let x = prec 0 (x + 1) counts the total number of points in time. The interpretation of a time-step in a given backend is normally an interval that is on average equal to the length of time between two redraws.

vert :: GLInputType t => [ConstExpr t] -> VertExpr t Source #

A vertex input variable (attribute) constructed from a stream of per-vertex data. The number of vertices (the length of the stream) should be consistent across all vertex attributes used to construct a given GLObj.

frag :: GLSupportsSmoothInterp t => VertExpr t -> FragExpr t Source #

A fragment input variable constructed from the output data of a vertex variable, interpolated in a perspective-correct manner over the primitive being processed

noperspFrag :: GLSupportsSmoothInterp t => GLInputType t => VertExpr t -> FragExpr t Source #

A fragment input variable constructed from the output data of a vertex variable, interpolated linearly across the primitive being processed

flatFrag :: GLInputType t => VertExpr t -> FragExpr t Source #

A fragment input variable constructed from the output data of a vertex variable, having the same value across the primitive being processed (cf. the OpenGL API for which vertex is used to determine its value)

Vector, matrix, and array constructors

A constructor of the form vecn creates a column vector with n components; a constructor of the form matpxq creates a matrix with p rows and q columns (matp is an alias for matpxp).

vec2 :: forall {t1} {d :: GLDomain}. GLType (Mat 2 1 t1) => GLExpr d t1 -> GLExpr d t1 -> GLExpr d (Mat 2 1 t1) Source #

vec3 :: forall {t1} {d :: GLDomain}. GLType (Mat 3 1 t1) => GLExpr d t1 -> GLExpr d t1 -> GLExpr d t1 -> GLExpr d (Mat 3 1 t1) Source #

vec4 :: forall {t1} {d :: GLDomain}. GLType (Mat 4 1 t1) => GLExpr d t1 -> GLExpr d t1 -> GLExpr d t1 -> GLExpr d t1 -> GLExpr d (Mat 4 1 t1) Source #

mat2 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 2 t1), GLType (Mat 2 2 t1)) => GLExpr d (Vec 2 t1) -> GLExpr d (Vec 2 t1) -> GLExpr d (Mat 2 2 t1) Source #

mat3 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 3 t1), GLType (Mat 3 3 t1)) => GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Mat 3 3 t1) Source #

mat4 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 4 t1), GLType (Mat 4 4 t1)) => GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Mat 4 4 t1) Source #

mat2x2 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 2 t1), GLType (Mat 2 2 t1)) => GLExpr d (Vec 2 t1) -> GLExpr d (Vec 2 t1) -> GLExpr d (Mat 2 2 t1) Source #

mat2x3 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 2 t1), GLType (Mat 2 3 t1)) => GLExpr d (Vec 2 t1) -> GLExpr d (Vec 2 t1) -> GLExpr d (Vec 2 t1) -> GLExpr d (Mat 2 3 t1) Source #

mat2x4 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 2 t1), GLType (Mat 2 4 t1)) => GLExpr d (Vec 2 t1) -> GLExpr d (Vec 2 t1) -> GLExpr d (Vec 2 t1) -> GLExpr d (Vec 2 t1) -> GLExpr d (Mat 2 4 t1) Source #

mat3x2 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 3 t1), GLType (Mat 3 2 t1)) => GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Mat 3 2 t1) Source #

mat3x3 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 3 t1), GLType (Mat 3 3 t1)) => GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Mat 3 3 t1) Source #

mat3x4 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 3 t1), GLType (Mat 3 4 t1)) => GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Mat 3 4 t1) Source #

mat4x2 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 4 t1), GLType (Mat 4 2 t1)) => GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Mat 4 2 t1) Source #

mat4x3 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 4 t1), GLType (Mat 4 3 t1)) => GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Mat 4 3 t1) Source #

mat4x4 :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Vec 4 t1), GLType (Mat 4 4 t1)) => GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Vec 4 t1) -> GLExpr d (Mat 4 4 t1) Source #

pre :: forall {n :: Nat} {t1} {d :: GLDomain}. (GLType (Vec n t1), GLType (Mat (n + 1) 1 t1)) => GLExpr d t1 -> GLExpr d (Vec n t1) -> GLExpr d (Mat (n + 1) 1 t1) Source #

Extend a vector by prepending an element

app :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLType t1, GLType (Vec n t1), GLType (Mat (n + 1) 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d t1 -> GLExpr d (Mat (n + 1) 1 t1) Source #

Extend a vector by appending an element

($-) :: forall {m :: Nat} {t1} {n :: Nat} {d :: GLDomain}. (GLType (Vec m t1), GLType (Vec n t1), GLType (Mat (m + n) 1 t1)) => GLExpr d (Vec m t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat (m + n) 1 t1) infixr 8 Source #

Concatenate two vectors together

array :: GLType [t1] => [GLExpr 'HostDomain t1] -> GLExpr 'HostDomain [t1] Source #

Create an array from a list of HostExprs

Deconstruction and indexing

To deconstruct a vector into a tuple of primitive elements or to deconstruct a matrix into a tuple of column vectors use decon. This approach pairs particularly well with view patterns:

vec2Flip :: GLExpr d (Vec 2 t) -> GLExpr d (Vec 2 t)
vec2Flip (decon v2 -> (v1, v2)) = vec2 v2 v1

Alternatively, with the synonyms x, y, z, w, referring to the components of a vector in that order, projection functions consisting of an ordered selection of such names followed by an underscore (e.g., xyz_), can be used to extract the corresponding components. For matrices, the projection functions are of the form coln. Note that the types of these functions constrains the length of their input so that the operation is well-defined.

class Deconstructible t where Source #

An expression that can be deconstructed into its components

Associated Types

type Decon t Source #

The resulting type of the deconstruction

Methods

decon :: t -> Decon t Source #

Deconstruct the given expression

Instances

Instances details
(GLPrim t, GLType (Mat p 2 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 2 t)) Source #

Methods

decon :: GLExpr d (Mat p 2 t) -> Decon (GLExpr d (Mat p 2 t)) Source #

(GLPrim t, GLType (Mat p 3 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 3 t)) Source #

Methods

decon :: GLExpr d (Mat p 3 t) -> Decon (GLExpr d (Mat p 3 t)) Source #

(GLPrim t, GLType (Mat p 4 t), GLType (Vec p t)) => Deconstructible (GLExpr d (Mat p 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Mat p 4 t)) Source #

Methods

decon :: GLExpr d (Mat p 4 t) -> Decon (GLExpr d (Mat p 4 t)) Source #

(GLPrim t, GLType (Vec 2 t)) => Deconstructible (GLExpr d (Vec 2 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 2 t)) Source #

Methods

decon :: GLExpr d (Vec 2 t) -> Decon (GLExpr d (Vec 2 t)) Source #

(GLPrim t, GLType (Vec 3 t)) => Deconstructible (GLExpr d (Vec 3 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 3 t)) Source #

Methods

decon :: GLExpr d (Vec 3 t) -> Decon (GLExpr d (Vec 3 t)) Source #

(GLPrim t, GLType (Vec 4 t)) => Deconstructible (GLExpr d (Vec 4 t)) Source # 
Instance details

Defined in Graphics.HaGL

Associated Types

type Decon (GLExpr d (Vec 4 t)) Source #

Methods

decon :: GLExpr d (Vec 4 t) -> Decon (GLExpr d (Vec 4 t)) Source #

x_ :: forall {n :: Nat} {t} {d :: GLDomain}. (OrdCond (CmpNat 1 n) 'True 'True 'False ~ 'True, GLType t, GLType (Vec n t)) => GLExpr d (Vec n t) -> GLExpr d t Source #

y_ :: forall {n :: Nat} {t} {d :: GLDomain}. (OrdCond (CmpNat 2 n) 'True 'True 'False ~ 'True, GLType t, GLType (Vec n t)) => GLExpr d (Vec n t) -> GLExpr d t Source #

z_ :: forall {n :: Nat} {t} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType t, GLType (Vec n t)) => GLExpr d (Vec n t) -> GLExpr d t Source #

w_ :: forall {n :: Nat} {t} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType t, GLType (Vec n t)) => GLExpr d (Vec n t) -> GLExpr d t Source #

xy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 2 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

xz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

xw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

yx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 2 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

yz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

yw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

zx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

zy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

zw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

wx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

wy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

wz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 2 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 2 1 t1) Source #

xyz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

xyw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

xzy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

xzw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

xwy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

xwz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

yxz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

yxw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

yzx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

yzw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

ywx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

ywz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

zxy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

zxw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

zyx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

zyw_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

zwx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

zwy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

wxy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

wxz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

wyx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

wyz_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

wzx_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

wzy_ :: forall {n :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 n) 'True 'True 'False ~ 'True, GLType (Vec n t1), GLType (Mat 3 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat 3 1 t1) Source #

col0 :: forall {c :: Nat} {r :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 1 c) 'True 'True 'False ~ 'True, GLType (Mat r c t1), GLType (Mat r 1 t1)) => GLExpr d (Mat r c t1) -> GLExpr d (Mat r 1 t1) Source #

The first column of a matrix

col1 :: forall {c :: Nat} {r :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 2 c) 'True 'True 'False ~ 'True, GLType (Mat r c t1), GLType (Mat r 1 t1)) => GLExpr d (Mat r c t1) -> GLExpr d (Mat r 1 t1) Source #

The second column of a matrix

col2 :: forall {c :: Nat} {r :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 3 c) 'True 'True 'False ~ 'True, GLType (Mat r c t1), GLType (Mat r 1 t1)) => GLExpr d (Mat r c t1) -> GLExpr d (Mat r 1 t1) Source #

The third column of a matrix

col3 :: forall {c :: Nat} {r :: Nat} {t1} {d :: GLDomain}. (OrdCond (CmpNat 4 c) 'True 'True 'False ~ 'True, GLType (Mat r c t1), GLType (Mat r 1 t1)) => GLExpr d (Mat r c t1) -> GLExpr d (Mat r 1 t1) Source #

The fourth column of a matrix

(.!) :: forall {t} {d :: GLDomain}. (GLType t, GLType [t]) => GLExpr d [t] -> GLExpr d Int -> GLExpr d t Source #

Array index operator, returning the i-th (0-indexed) element of the array

Type conversion

cast :: forall {t1} {t} {d :: GLDomain}. (GLPrim t1, GLPrim t) => GLExpr d t1 -> GLExpr d t Source #

Coerce the primitive type of a value to arbitrary primitive type

matCast :: forall {t1} {t2} {p :: Nat} {q :: Nat} {d :: GLDomain}. (GLPrim t1, GLPrim t2, KnownNat p, KnownNat q, GLType (Mat p q t2)) => GLExpr d (Mat p q t1) -> GLExpr d (Mat p q t2) Source #

Coerce the element type of a matrix to an arbitrary primitive type

Built-in operators and functions

Most definitions here strive to be consistent with the corresponding built-in functions provided by GLSL (cf. The OpenGL Shading Language, Version 4.60.7), in terms of semantics and typing constraints. Some notable exceptions to this rule are:

  • Typing restrictions may be stricter to prevent what would otherwise be runtime errors; for example, matrix multiplication is only defined on matrices with the correct dimensions.
  • The operators (+), (-), (*), as well as the function negate, being methods of Num, are only supported on expressions where the underlying type is one of Int, UInt, Float, Double, or a vector of one of these types. To perform these operations component-wise on matrices use the operators (.+), (.-), (.*), or the function neg respectively.
  • The operator (/) is only supported when the underlying type is Float or Double. The more general operator (./) additionally supports integer and component-wise division.
  • The operator (.%) is the modulo operation on integers or integer-valued vectors.
  • The operator (.#) is used for scalar multiplication.
  • The operator (.@) is used for matrix (including matrix-vector) multiplication.
  • All boolean and bitwise operators are also prefixed with a single dot: (.==), (.<), (.&&), (.&), etc.

Arithmetic operators

(.+) :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLType t) => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 6 Source #

(.-) :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLType t) => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 6 Source #

(.*) :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLType t) => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 7 Source #

(./) :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLType t) => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 7 Source #

(.%) :: forall {t} {d :: GLDomain}. (GLInteger (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 7 Source #

(.#) :: forall {t1} {p :: Nat} {q :: Nat} {d :: GLDomain}. (GLNumeric t1, GLType (Mat p q t1)) => GLExpr d t1 -> GLExpr d (Mat p q t1) -> GLExpr d (Mat p q t1) infixl 7 Source #

Scalar multiplication

(.@) :: forall {t1} {p :: Nat} {r :: Nat} {q :: Nat} {d :: GLDomain}. (GLFloating t1, GLType (Mat p r t1), GLType (Mat p q t1), GLType (Mat q r t1)) => GLExpr d (Mat p q t1) -> GLExpr d (Mat q r t1) -> GLExpr d (Mat p r t1) infixl 7 Source #

Matrix multiplication

neg :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLType t) => GLExpr d t -> GLExpr d t Source #

Arithmetic negation

Boolean operators and comparison functions

(.<) :: forall {t1} {d :: GLDomain}. GLNumeric t1 => GLExpr d t1 -> GLExpr d t1 -> GLExpr d Bool infix 4 Source #

(.<=) :: forall {t1} {d :: GLDomain}. GLNumeric t1 => GLExpr d t1 -> GLExpr d t1 -> GLExpr d Bool infix 4 Source #

(.>) :: forall {t1} {d :: GLDomain}. GLNumeric t1 => GLExpr d t1 -> GLExpr d t1 -> GLExpr d Bool infix 4 Source #

(.>=) :: forall {t1} {d :: GLDomain}. GLNumeric t1 => GLExpr d t1 -> GLExpr d t1 -> GLExpr d Bool infix 4 Source #

(.==) :: forall {t1} {d :: GLDomain}. GLType t1 => GLExpr d t1 -> GLExpr d t1 -> GLExpr d Bool infix 4 Source #

(./=) :: forall {t1} {d :: GLDomain}. GLType t1 => GLExpr d t1 -> GLExpr d t1 -> GLExpr d Bool infix 4 Source #

(.&&) :: forall {d :: GLDomain}. GLExpr d Bool -> GLExpr d Bool -> GLExpr d Bool infixl 3 Source #

(.||) :: forall {d :: GLDomain}. GLExpr d Bool -> GLExpr d Bool -> GLExpr d Bool infixl 1 Source #

(.^^) :: forall {d :: GLDomain}. GLExpr d Bool -> GLExpr d Bool -> GLExpr d Bool infixl 2 Source #

nt :: forall {d :: GLDomain}. GLExpr d Bool -> GLExpr d Bool Source #

Logical not

cond :: forall {t} {d :: GLDomain}. GLType t => GLExpr d Bool -> GLExpr d t -> GLExpr d t -> GLExpr d t Source #

Conditional operator, evaluating and returning its second or third argument if the first evaluates to true or false, respectively

Bitwise operators

(.<<) :: forall {t} {d :: GLDomain}. GLSupportsBitwiseOps t => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 5 Source #

(.>>) :: forall {t} {d :: GLDomain}. GLSupportsBitwiseOps t => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 5 Source #

(.&) :: forall {t} {d :: GLDomain}. GLSupportsBitwiseOps t => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 3 Source #

(.|) :: forall {t} {d :: GLDomain}. GLSupportsBitwiseOps t => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 1 Source #

(.^) :: forall {t} {d :: GLDomain}. GLSupportsBitwiseOps t => GLExpr d t -> GLExpr d t -> GLExpr d t infixl 2 Source #

compl :: forall {t} {d :: GLDomain}. GLSupportsBitwiseOps t => GLExpr d t -> GLExpr d t Source #

One's complement

Angle and trigonometry functions

radians :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

degrees :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

sin :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

cos :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

tan :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

asin :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

acos :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

atan :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

sinh :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

cosh :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

tanh :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

asinh :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

acosh :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

atanh :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

Exponential functions

pow :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t Source #

exp :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

log :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

exp2 :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

log2 :: forall {t} {d :: GLDomain}. (GLElt t ~ Float, GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

sqrt :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

inversesqrt :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

Common functions

abs :: forall {t} {d :: GLDomain}. (GLSigned (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

sign :: forall {t} {d :: GLDomain}. (GLSigned (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

floor :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

trunc :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

round :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

roundEven :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

ceil :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

fract :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t Source #

mod :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t Source #

min :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t Source #

max :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t Source #

clamp :: forall {t} {d :: GLDomain}. (GLNumeric (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t -> GLExpr d t Source #

mix :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t -> GLExpr d t Source #

step :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t Source #

smoothstep :: forall {t} {d :: GLDomain}. (GLFloating (GLElt t), GLPrimOrVec t) => GLExpr d t -> GLExpr d t -> GLExpr d t -> GLExpr d t Source #

Geometric functions

length :: forall {t} {d :: GLDomain} {n :: Nat}. GLFloating t => GLExpr d (Vec n t) -> GLExpr d t Source #

distance :: forall {t} {d :: GLDomain} {n :: Nat}. GLFloating t => GLExpr d (Vec n t) -> GLExpr d (Vec n t) -> GLExpr d t Source #

dot :: forall {t} {n :: Nat} {d :: GLDomain}. (GLFloating t, GLType (Vec n t)) => GLExpr d (Vec n t) -> GLExpr d (Vec n t) -> GLExpr d t Source #

cross :: forall {t1} {d :: GLDomain}. (GLFloating t1, GLType (Mat 3 1 t1)) => GLExpr d (Vec 3 t1) -> GLExpr d (Vec 3 t1) -> GLExpr d (Mat 3 1 t1) Source #

normalize :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLFloating t1, GLType (Mat n 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 t1) Source #

faceforward :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLFloating t1, KnownNat n, GLType (Mat n 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 t1) Source #

reflect :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLFloating t1, KnownNat n, GLType (Mat n 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 t1) Source #

refract :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLFloating t1, KnownNat n, GLType (Mat n 1 t1)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d t1 -> GLExpr d (Mat n 1 t1) Source #

Matrix functions

matrixCompMult :: forall {t1} {p :: Nat} {q :: Nat} {d :: GLDomain}. (GLFloating t1, GLType (Mat p q t1)) => GLExpr d (Mat p q t1) -> GLExpr d (Mat p q t1) -> GLExpr d (Mat p q t1) Source #

outerProduct :: forall {t1} {p :: Nat} {q :: Nat} {d :: GLDomain}. (GLFloating t1, GLType (Mat p q t1), GLType (Vec q t1)) => GLExpr d (Vec p t1) -> GLExpr d (Vec q t1) -> GLExpr d (Mat p q t1) Source #

transpose :: forall {t1} {q :: Nat} {p :: Nat} {d :: GLDomain}. (GLFloating t1, GLType (Mat q p t1), GLType (Mat p q t1)) => GLExpr d (Mat p q t1) -> GLExpr d (Mat q p t1) Source #

determinant :: forall {p :: Nat} {d :: GLDomain}. GLType (Mat p p Float) => GLExpr d (Mat p p Float) -> GLExpr d Float Source #

inverse :: forall {p :: Nat} {d :: GLDomain}. GLType (Mat p p Float) => GLExpr d (Mat p p Float) -> GLExpr d (Mat p p Float) Source #

Vector relational functions

lessThan :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLSingleNumeric t1, KnownNat n, GLType (Mat n 1 Bool)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 Bool) Source #

lessThanEqual :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLSingleNumeric t1, KnownNat n, GLType (Mat n 1 Bool)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 Bool) Source #

greaterThan :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLSingleNumeric t1, KnownNat n, GLType (Mat n 1 Bool)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 Bool) Source #

greaterThanEqual :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLSingleNumeric t1, KnownNat n, GLType (Mat n 1 Bool)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 Bool) Source #

equal :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLSingle t1, KnownNat n, GLType (Mat n 1 Bool)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 Bool) Source #

notEqual :: forall {t1} {n :: Nat} {d :: GLDomain}. (GLSingle t1, KnownNat n, GLType (Mat n 1 Bool)) => GLExpr d (Vec n t1) -> GLExpr d (Vec n t1) -> GLExpr d (Mat n 1 Bool) Source #

any :: forall {n :: Nat} {d :: GLDomain}. GLType (Vec n Bool) => GLExpr d (Vec n Bool) -> GLExpr d Bool Source #

all :: forall {n :: Nat} {d :: GLDomain}. GLType (Vec n Bool) => GLExpr d (Vec n Bool) -> GLExpr d Bool Source #

not :: forall {n :: Nat} {d :: GLDomain}. GLType (Mat n 1 Bool) => GLExpr d (Vec n Bool) -> GLExpr d (Mat n 1 Bool) Source #

Custom function support

An n-ary f function on GLExpr's can be transported to an arbitrary domain using glFuncn. That is, glFuncn f will take in the same arguments as f but will be evaluated in the domain of its return type (in contrast to f, which being a native Haskell function, will always be evaluated on the CPU).

However, due to the fact that GLSL does not allow recursion, attempting to call glFuncn f, where f is defined recursively (or mutually recursively in terms of other functions) will generally result in an exception being thrown. The one case where this is permissible is that of tail-recursive functions of the form

f x1 x2 ... = cond c b (f y1 y2 ...)

where none of the expressions c, b, y1, y2, ... depend on f. Where applicable, such functions will be synthesized as GLSL loops. For example, the factorial function can be computed within a vertex shader as follows:

fact = glFunc1 $ \n -> fact' n 1 where
  fact' :: GLExpr VertexDomain Int -> GLExpr VertexDomain Int -> GLExpr VertexDomain Int
  fact' = glFunc2 $ \n a -> cond (n .== 0) a (fact' (n - 1) (a * n))

x :: GLExpr VertexDomain Int
x = fact 5

glFunc1 :: (GLType t, GLType t1) => (GLExpr d t1 -> GLExpr d t) -> GLExpr d t1 -> GLExpr d t Source #

glFunc2 :: (GLType t, GLType t1, GLType t2) => (GLExpr d t1 -> GLExpr d t2 -> GLExpr d t) -> GLExpr d t1 -> GLExpr d t2 -> GLExpr d t Source #

glFunc3 :: (GLType t, GLType t1, GLType t2, GLType t3) => (GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t) -> GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t Source #

glFunc4 :: (GLType t, GLType t1, GLType t2, GLType t3, GLType t4) => (GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t4 -> GLExpr d t) -> GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t4 -> GLExpr d t Source #

glFunc5 :: (GLType t, GLType t1, GLType t2, GLType t3, GLType t4, GLType t5) => (GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t4 -> GLExpr d t5 -> GLExpr d t) -> GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t4 -> GLExpr d t5 -> GLExpr d t Source #

glFunc6 :: (GLType t, GLType t1, GLType t2, GLType t3, GLType t4, GLType t5, GLType t6) => (GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t4 -> GLExpr d t5 -> GLExpr d t6 -> GLExpr d t) -> GLExpr d t1 -> GLExpr d t2 -> GLExpr d t3 -> GLExpr d t4 -> GLExpr d t5 -> GLExpr d t6 -> GLExpr d t Source #

Lifts from raw types

If the need arises to use an n-ary native function f that is not defined over GLExpr's (for instance, to dynamically update array contents using functions defined on lists), such a function can be lifted to the HostDomain using glLiftn. glLiftn f will then be defined over HostExprs that agree with respective argument types of f. For example, the two expressions below compute the same array:

a1 :: GLExpr HostDomain [Float]
a1 = (glLift2 $ \x y -> [x, y, x + y]) time time
a2 :: GLExpr HostDomain [Float]
a2 = array [time, 2 * time, 3 * time]

glLift1 :: (GLType t, GLType t1) => (t1 -> t) -> GLExpr 'HostDomain t1 -> GLExpr 'HostDomain t Source #

glLift2 :: (GLType t, GLType t1, GLType t2) => (t1 -> t2 -> t) -> GLExpr 'HostDomain t1 -> GLExpr 'HostDomain t2 -> GLExpr 'HostDomain t Source #

glLift3 :: (GLType t, GLType t1, GLType t2, GLType t3) => (t1 -> t2 -> t3 -> t) -> GLExpr 'HostDomain t1 -> GLExpr 'HostDomain t2 -> GLExpr 'HostDomain t3 -> GLExpr 'HostDomain t Source #

glLift4 :: (GLType t, GLType t1, GLType t2, GLType t3, GLType t4) => (t1 -> t2 -> t3 -> t4 -> t) -> GLExpr 'HostDomain t1 -> GLExpr 'HostDomain t2 -> GLExpr 'HostDomain t3 -> GLExpr 'HostDomain t4 -> GLExpr 'HostDomain t Source #

glLift5 :: (GLType t, GLType t1, GLType t2, GLType t3, GLType t4, GLType t5) => (t1 -> t2 -> t3 -> t4 -> t5 -> t) -> GLExpr 'HostDomain t1 -> GLExpr 'HostDomain t2 -> GLExpr 'HostDomain t3 -> GLExpr 'HostDomain t4 -> GLExpr 'HostDomain t5 -> GLExpr 'HostDomain t Source #

glLift6 :: (GLType t, GLType t1, GLType t2, GLType t3, GLType t4, GLType t5, GLType t6) => (t1 -> t2 -> t3 -> t4 -> t5 -> t6 -> t) -> GLExpr 'HostDomain t1 -> GLExpr 'HostDomain t2 -> GLExpr 'HostDomain t3 -> GLExpr 'HostDomain t4 -> GLExpr 'HostDomain t5 -> GLExpr 'HostDomain t6 -> GLExpr 'HostDomain t Source #

Built-in I/O variables

time :: HostExpr Float Source #

Seconds elapsed since an initial point in time

mouseLeft :: HostExpr Bool Source #

True if and only if the left mouse button is pressed

mouseRight :: HostExpr Bool Source #

True if and only if the right mouse button is pressed

mouseWheel :: HostExpr Float Source #

A pulse signal, equal to 1 at the moment the mouse wheel scrolls up, -1 when the mouse wheel scrolls down, and afterwards exponentially decaying to its otherwise default value of 0

mouseX :: HostExpr Float Source #

The horizontal position of the mouse, not necessarily within the window bounds

mouseY :: HostExpr Float Source #

The vertical position of the mouse, not necessarily within the window bounds

mousePos :: HostExpr (Vec 2 Float) Source #

Equal to vec2 mouseX mouseY

Drawables

class Drawable a where Source #

Anything that can be drawn using a given Backend

Methods

draw :: Backend -> a -> IO () Source #

Instances

Instances details
Drawable GLObj Source #

A GLObj is drawn by constructing primitives from its position and indices expressions, according to its primitiveMode, and coloring the resulting fragments according to its color expression.

Instance details

Defined in Graphics.HaGL

Methods

draw :: Backend -> GLObj -> IO () Source #

Drawable [GLObj] Source #

A set of GLObjs is drawn by drawing each GLObj individually and with the same blending mode as that used to draw a single GLObj.

Instance details

Defined in Graphics.HaGL

Methods

draw :: Backend -> [GLObj] -> IO () Source #

data GLObj Source #

A drawable object specified by a set of variables of type GLExpr and the PrimitiveMode according to which output vertices of the variable position, indexed by indices, should be interpreted.

When using the convenience functions points, triangles, etc., to define a GLObj with the corresponding PrimitiveMode, at the very minimum the fields position and color must be set before drawing the GLObj.

Constructors

GLObj 

Fields

Instances

Instances details
Drawable GLObj Source #

A GLObj is drawn by constructing primitives from its position and indices expressions, according to its primitiveMode, and coloring the resulting fragments according to its color expression.

Instance details

Defined in Graphics.HaGL

Methods

draw :: Backend -> GLObj -> IO () Source #

Drawable [GLObj] Source #

A set of GLObjs is drawn by drawing each GLObj individually and with the same blending mode as that used to draw a single GLObj.

Instance details

Defined in Graphics.HaGL

Methods

draw :: Backend -> [GLObj] -> IO () Source #

type PrimitiveMode = PrimitiveMode Source #

See Graphics.Rendering.OpenGL.GL.PrimitiveMode for a description of each PrimitiveMode

points :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to Points

lines :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to Lines

lineLoop :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to LineLoop

lineStrip :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to LineStrip

triangles :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to Triangles

triangleStrip :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to TriangleStrip

triangleFan :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to TriangleFan

quads :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to Quads

quadStrip :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to QuadStrip

polygon :: GLObj Source #

An incompletely specified object with PrimitiveMode equal to Polygon

Backends

data Backend Source #

A backend that can interpret (draw) a Drawable. Unless overridden the following OpenGL options are set by default in all backends:

  • Clear color equal to black
  • Depth testing enabled
  • Blending enabled with blend equation equal to GL_FUNC_ADD
  • Source blending factor equal to GL_SRC_ALPHA
  • Destination blending factor equal to GL_ONE_MINUS_SRC_ALPHA

Constructors

GlutBackend GlutOptions 

data GlutOptions Source #

Options specific to a GLUT window

Constructors

GlutOptions 

Fields

data GlutRunMode Source #

GlutRunMode specifies how to run the resulting application

Constructors

GlutNormal

Display the output in a window

GlutCaptureLatest String

Display the output in a window, saving the latest frame in the specified file location

GlutCaptureFrames String

Display the output in a window, saving all frames in the specified directory

GlutCaptureAndExit String

Display the output in a window for a brief period time, saving the latest frame in the specified file location

drawGlut :: Drawable a => a -> IO () Source #

Draw in a GLUT backend using default options

drawGlutCustom :: Drawable a => GlutOptions -> a -> IO () Source #

Draw in a GLUT backend using specified options

defaultGlutOptions :: GlutOptions Source #

Default options for a GLUT backend

  • winSize = (768, 768)
  • clearCol = (0, 0, 0, 0)
  • runMode = GlutNormal

Orphan instances

GLPrim t => Enum (ConstExpr t) Source # 
Instance details

(GLElt t ~ Float, GLPrimOrVec t, Fractional t) => Floating (GLExpr d t) Source # 
Instance details

Methods

pi :: GLExpr d t #

exp :: GLExpr d t -> GLExpr d t #

log :: GLExpr d t -> GLExpr d t #

sqrt :: GLExpr d t -> GLExpr d t #

(**) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

logBase :: GLExpr d t -> GLExpr d t -> GLExpr d t #

sin :: GLExpr d t -> GLExpr d t #

cos :: GLExpr d t -> GLExpr d t #

tan :: GLExpr d t -> GLExpr d t #

asin :: GLExpr d t -> GLExpr d t #

acos :: GLExpr d t -> GLExpr d t #

atan :: GLExpr d t -> GLExpr d t #

sinh :: GLExpr d t -> GLExpr d t #

cosh :: GLExpr d t -> GLExpr d t #

tanh :: GLExpr d t -> GLExpr d t #

asinh :: GLExpr d t -> GLExpr d t #

acosh :: GLExpr d t -> GLExpr d t #

atanh :: GLExpr d t -> GLExpr d t #

log1p :: GLExpr d t -> GLExpr d t #

expm1 :: GLExpr d t -> GLExpr d t #

log1pexp :: GLExpr d t -> GLExpr d t #

log1mexp :: GLExpr d t -> GLExpr d t #

Num (GLExpr d UInt) Source # 
Instance details

(GLType (Vec n UInt), GLType (Vec n Int), GLType (Vec n Bool), KnownNat n) => Num (GLExpr d (Vec n UInt)) Source # 
Instance details

Methods

(+) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

(-) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

(*) :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

negate :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

abs :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

signum :: GLExpr d (Vec n UInt) -> GLExpr d (Vec n UInt) #

fromInteger :: Integer -> GLExpr d (Vec n UInt) #

(GLSigned (GLElt t), GLPrimOrVec t, Num t) => Num (GLExpr d t) Source # 
Instance details

Methods

(+) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

(-) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

(*) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

negate :: GLExpr d t -> GLExpr d t #

abs :: GLExpr d t -> GLExpr d t #

signum :: GLExpr d t -> GLExpr d t #

fromInteger :: Integer -> GLExpr d t #

(GLFloating (GLElt t), GLPrimOrVec t, Fractional t) => Fractional (GLExpr d t) Source # 
Instance details

Methods

(/) :: GLExpr d t -> GLExpr d t -> GLExpr d t #

recip :: GLExpr d t -> GLExpr d t #

fromRational :: Rational -> GLExpr d t #