GPipe-Core-0.2.3.2: Typesafe functional GPU graphics programming
Safe HaskellNone
LanguageHaskell2010

Graphics.GPipe.Expr

Description

This module provides the DSL for shader operations in GPipe. The type S x a is an opaque type that represents a value of type a in a shader stage x, eg S F Float means a floating point value in a fragment stream.

Synopsis

Atomic shader type

data S x a Source #

Instances

Instances details
FragmentInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VBool Source #

FragmentInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VWord Source #

FragmentInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VInt Source #

FragmentInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VFloat Source #

FragmentCreator VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

FragmentCreator VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

FragmentCreator VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

FragmentCreator VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

ResultValue (V4 (S x Float)) Source # 
Instance details

Defined in Graphics.GPipe.Debugger.Compile

ResultValue (V3 (S x Float)) Source # 
Instance details

Defined in Graphics.GPipe.Debugger.Compile

ResultValue (V2 (S x Float)) Source # 
Instance details

Defined in Graphics.GPipe.Debugger.Compile

Floating (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

pi :: S x Float #

exp :: S x Float -> S x Float #

log :: S x Float -> S x Float #

sqrt :: S x Float -> S x Float #

(**) :: S x Float -> S x Float -> S x Float #

logBase :: S x Float -> S x Float -> S x Float #

sin :: S x Float -> S x Float #

cos :: S x Float -> S x Float #

tan :: S x Float -> S x Float #

asin :: S x Float -> S x Float #

acos :: S x Float -> S x Float #

atan :: S x Float -> S x Float #

sinh :: S x Float -> S x Float #

cosh :: S x Float -> S x Float #

tanh :: S x Float -> S x Float #

asinh :: S x Float -> S x Float #

acosh :: S x Float -> S x Float #

atanh :: S x Float -> S x Float #

log1p :: S x Float -> S x Float #

expm1 :: S x Float -> S x Float #

log1pexp :: S x Float -> S x Float #

log1mexp :: S x Float -> S x Float #

Fractional (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

(/) :: S x Float -> S x Float -> S x Float #

recip :: S x Float -> S x Float #

fromRational :: Rational -> S x Float #

Num (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

(+) :: S x Word -> S x Word -> S x Word #

(-) :: S x Word -> S x Word -> S x Word #

(*) :: S x Word -> S x Word -> S x Word #

negate :: S x Word -> S x Word #

abs :: S x Word -> S x Word #

signum :: S x Word -> S x Word #

fromInteger :: Integer -> S x Word #

Num (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

(+) :: S x Int -> S x Int -> S x Int #

(-) :: S x Int -> S x Int -> S x Int #

(*) :: S x Int -> S x Int -> S x Int #

negate :: S x Int -> S x Int #

abs :: S x Int -> S x Int #

signum :: S x Int -> S x Int #

fromInteger :: Integer -> S x Int #

Num (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

(+) :: S x Float -> S x Float -> S x Float #

(-) :: S x Float -> S x Float -> S x Float #

(*) :: S x Float -> S x Float -> S x Float #

negate :: S x Float -> S x Float #

abs :: S x Float -> S x Float #

signum :: S x Float -> S x Float #

fromInteger :: Integer -> S x Float #

Boolean (S x Bool) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

true :: S x Bool #

false :: S x Bool #

notB :: S x Bool -> S x Bool #

(&&*) :: S x Bool -> S x Bool -> S x Bool #

(||*) :: S x Bool -> S x Bool -> S x Bool #

IfB (S x (GenerativeGeometry p b)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

ifB :: bool ~ BooleanOf (S x (GenerativeGeometry p b)) => bool -> S x (GenerativeGeometry p b) -> S x (GenerativeGeometry p b) -> S x (GenerativeGeometry p b) #

IfB (S x Bool) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

ifB :: bool ~ BooleanOf (S x Bool) => bool -> S x Bool -> S x Bool -> S x Bool #

IfB (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

ifB :: bool ~ BooleanOf (S x Word) => bool -> S x Word -> S x Word -> S x Word #

IfB (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

ifB :: bool ~ BooleanOf (S x Int) => bool -> S x Int -> S x Int -> S x Int #

IfB (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

ifB :: bool ~ BooleanOf (S x Float) => bool -> S x Float -> S x Float -> S x Float #

Eq a => EqB (S x a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

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

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

Ord a => OrdB (S x a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

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

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

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

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

Conjugate (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

conjugate :: S x Word -> S x Word #

Conjugate (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

conjugate :: S x Int -> S x Int #

Conjugate (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

conjugate :: S x Float -> S x Float #

TrivialConjugate (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

TrivialConjugate (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

TrivialConjugate (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Convert (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ConvertFloat (S x Word) Source #

type ConvertInt (S x Word) Source #

type ConvertWord (S x Word) Source #

Convert (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ConvertFloat (S x Int) Source #

type ConvertInt (S x Int) Source #

type ConvertWord (S x Int) Source #

Methods

toFloat :: S x Int -> ConvertFloat (S x Int) Source #

toInt :: S x Int -> ConvertInt (S x Int) Source #

toWord :: S x Int -> ConvertWord (S x Int) Source #

Convert (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ConvertFloat (S x Float) Source #

type ConvertInt (S x Float) Source #

type ConvertWord (S x Float) Source #

FloatingOrd (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

clamp :: S x Float -> S x Float -> S x Float -> S x Float Source #

saturate :: S x Float -> S x Float Source #

step :: S x Float -> S x Float -> S x Float Source #

smoothstep :: S x Float -> S x Float -> S x Float -> S x Float Source #

Real' (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

rsqrt :: S x Float -> S x Float Source #

exp2 :: S x Float -> S x Float Source #

log2 :: S x Float -> S x Float Source #

floor' :: S x Float -> S x Float Source #

ceiling' :: S x Float -> S x Float Source #

fract' :: S x Float -> S x Float Source #

mod'' :: S x Float -> S x Float -> S x Float Source #

mix :: S x Float -> S x Float -> S x Float -> S x Float Source #

atan2' :: S x Float -> S x Float -> S x Float Source #

Bits' (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

and' :: S x Word -> S x Word -> S x Word Source #

or' :: S x Word -> S x Word -> S x Word Source #

xor' :: S x Word -> S x Word -> S x Word Source #

complement' :: S x Word -> S x Word Source #

shiftL' :: S x Word -> S x Word -> S x Word Source #

shiftR' :: S x Word -> S x Word -> S x Word Source #

bitSize' :: S x Word -> Int Source #

Bits' (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

and' :: S x Int -> S x Int -> S x Int Source #

or' :: S x Int -> S x Int -> S x Int Source #

xor' :: S x Int -> S x Int -> S x Int Source #

complement' :: S x Int -> S x Int Source #

shiftL' :: S x Int -> S x Int -> S x Int Source #

shiftR' :: S x Int -> S x Int -> S x Int Source #

bitSize' :: S x Int -> Int Source #

Integral' (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: S x Word -> S x Word -> S x Word Source #

mod' :: S x Word -> S x Word -> S x Word Source #

Integral' (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: S x Int -> S x Int -> S x Int Source #

mod' :: S x Int -> S x Int -> S x Int Source #

ResultValue (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Debugger.Compile

ShaderType (S x (GenerativeGeometry p a)) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x (GenerativeGeometry p a)) Source #

ShaderType (S x Bool) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Bool) Source #

Methods

toBase :: x -> S x Bool -> ShaderBase (ShaderBaseType (S x Bool)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (S x Bool)) x -> S x Bool Source #

ShaderType (S x Word) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Word) Source #

Methods

toBase :: x -> S x Word -> ShaderBase (ShaderBaseType (S x Word)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (S x Word)) x -> S x Word Source #

ShaderType (S x Int) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Int) Source #

Methods

toBase :: x -> S x Int -> ShaderBase (ShaderBaseType (S x Int)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (S x Int)) x -> S x Int Source #

ShaderType (S x Float) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Float) Source #

type FragmentFormat VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

type FragmentFormat VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

type FragmentFormat VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

type FragmentFormat VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

type BooleanOf (S x a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type BooleanOf (S x a) = S x Bool
type ConvertFloat (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertFloat (S x Word) = S x Float
type ConvertFloat (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertFloat (S x Int) = S x Float
type ConvertFloat (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertFloat (S x Float) = S x Float
type ConvertInt (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertInt (S x Word) = S x Int
type ConvertInt (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertInt (S x Int) = S x Int
type ConvertInt (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertInt (S x Float) = S x Int
type ConvertWord (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertWord (S x Word) = S x Word
type ConvertWord (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertWord (S x Int) = S x Word
type ConvertWord (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ConvertWord (S x Float) = S x Word
type ShaderBaseType (S x (GenerativeGeometry p a)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ShaderBaseType (S x Bool) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ShaderBaseType (S x Bool) = S x Bool
type ShaderBaseType (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ShaderBaseType (S x Word) = S x Word
type ShaderBaseType (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

type ShaderBaseType (S x Int) = S x Int
type ShaderBaseType (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

data V Source #

Phantom type used as first argument in S V a that denotes that the shader value is a vertex value

Instances

Instances details
FragmentInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VBool Source #

FragmentInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VWord Source #

FragmentInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VInt Source #

FragmentInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VFloat Source #

FragmentCreator VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

FragmentCreator VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

FragmentCreator VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

FragmentCreator VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherFragmentInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

GeometryExplosive VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

AnotherVertexInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.GeometryStream

type FragmentFormat VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

type FragmentFormat VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

type FragmentFormat VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

type FragmentFormat VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

data F Source #

Phantom type used as first argument in S F a that denotes that the shader value is a fragment value

type VInt = S V Int Source #

type VWord = S V Word Source #

type VBool = S V Bool Source #

type FInt = S F Int Source #

type FWord = S F Word Source #

type FBool = S F Bool Source #

Type classes where the Prelude ones are lacking

class Convert a where Source #

Provides a common way to convert numeric types to integer and floating point representations.

Associated Types

type ConvertFloat a Source #

type ConvertInt a Source #

type ConvertWord a Source #

Methods

toFloat :: a -> ConvertFloat a Source #

Convert to a floating point number.

toInt :: a -> ConvertInt a Source #

Convert to an integral number, using truncation if necessary.

toWord :: a -> ConvertWord a Source #

Convert to an unsigned integral number, using truncation if necessary.

Instances

Instances details
Convert Float Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Convert Int Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Convert Word Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Convert (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ConvertFloat (S x Word) Source #

type ConvertInt (S x Word) Source #

type ConvertWord (S x Word) Source #

Convert (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ConvertFloat (S x Int) Source #

type ConvertInt (S x Int) Source #

type ConvertWord (S x Int) Source #

Methods

toFloat :: S x Int -> ConvertFloat (S x Int) Source #

toInt :: S x Int -> ConvertInt (S x Int) Source #

toWord :: S x Int -> ConvertWord (S x Int) Source #

Convert (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ConvertFloat (S x Float) Source #

type ConvertInt (S x Float) Source #

type ConvertWord (S x Float) Source #

class Integral' a where Source #

Methods

div' :: a -> a -> a Source #

mod' :: a -> a -> a Source #

Instances

Instances details
Integral' Int Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: Int -> Int -> Int Source #

mod' :: Int -> Int -> Int Source #

Integral' Int8 Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: Int8 -> Int8 -> Int8 Source #

mod' :: Int8 -> Int8 -> Int8 Source #

Integral' Int16 Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: Int16 -> Int16 -> Int16 Source #

mod' :: Int16 -> Int16 -> Int16 Source #

Integral' Int32 Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: Int32 -> Int32 -> Int32 Source #

mod' :: Int32 -> Int32 -> Int32 Source #

Integral' Word Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: Word -> Word -> Word Source #

mod' :: Word -> Word -> Word Source #

Integral' Word8 Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: Word8 -> Word8 -> Word8 Source #

mod' :: Word8 -> Word8 -> Word8 Source #

Integral' Word16 Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Integral' Word32 Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Integral' a => Integral' (V0 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: V0 a -> V0 a -> V0 a Source #

mod' :: V0 a -> V0 a -> V0 a Source #

Integral' a => Integral' (V4 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: V4 a -> V4 a -> V4 a Source #

mod' :: V4 a -> V4 a -> V4 a Source #

Integral' a => Integral' (V3 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: V3 a -> V3 a -> V3 a Source #

mod' :: V3 a -> V3 a -> V3 a Source #

Integral' a => Integral' (V2 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: V2 a -> V2 a -> V2 a Source #

mod' :: V2 a -> V2 a -> V2 a Source #

Integral' a => Integral' (V1 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: V1 a -> V1 a -> V1 a Source #

mod' :: V1 a -> V1 a -> V1 a Source #

Integral' (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: S x Word -> S x Word -> S x Word Source #

mod' :: S x Word -> S x Word -> S x Word Source #

Integral' (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

div' :: S x Int -> S x Int -> S x Int Source #

mod' :: S x Int -> S x Int -> S x Int Source #

class Bits' a where Source #

Methods

and' :: a -> a -> a Source #

or' :: a -> a -> a Source #

xor' :: a -> a -> a Source #

complement' :: a -> a Source #

shiftL' :: a -> a -> a Source #

shiftR' :: a -> a -> a Source #

bitSize' :: a -> Int Source #

Instances

Instances details
Bits' (S x Word) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

and' :: S x Word -> S x Word -> S x Word Source #

or' :: S x Word -> S x Word -> S x Word Source #

xor' :: S x Word -> S x Word -> S x Word Source #

complement' :: S x Word -> S x Word Source #

shiftL' :: S x Word -> S x Word -> S x Word Source #

shiftR' :: S x Word -> S x Word -> S x Word Source #

bitSize' :: S x Word -> Int Source #

Bits' (S x Int) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

and' :: S x Int -> S x Int -> S x Int Source #

or' :: S x Int -> S x Int -> S x Int Source #

xor' :: S x Int -> S x Int -> S x Int Source #

complement' :: S x Int -> S x Int Source #

shiftL' :: S x Int -> S x Int -> S x Int Source #

shiftR' :: S x Int -> S x Int -> S x Int Source #

bitSize' :: S x Int -> Int Source #

class Floating a => Real' a where Source #

This class provides the GPU functions either not found in Prelude's numerical classes, or that has wrong types. Instances are also provided for normal Floats and Doubles.

Minimal complete definition

(floor' | ceiling'), atan2'

Methods

rsqrt :: a -> a Source #

exp2 :: a -> a Source #

log2 :: a -> a Source #

floor' :: a -> a Source #

ceiling' :: a -> a Source #

fract' :: a -> a Source #

mod'' :: a -> a -> a Source #

mix :: a -> a -> a -> a Source #

atan2' :: a -> a -> a Source #

Instances

Instances details
Real' Double Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Real' Float Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Real' a => Real' (V0 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

rsqrt :: V0 a -> V0 a Source #

exp2 :: V0 a -> V0 a Source #

log2 :: V0 a -> V0 a Source #

floor' :: V0 a -> V0 a Source #

ceiling' :: V0 a -> V0 a Source #

fract' :: V0 a -> V0 a Source #

mod'' :: V0 a -> V0 a -> V0 a Source #

mix :: V0 a -> V0 a -> V0 a -> V0 a Source #

atan2' :: V0 a -> V0 a -> V0 a Source #

Real' a => Real' (V4 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

rsqrt :: V4 a -> V4 a Source #

exp2 :: V4 a -> V4 a Source #

log2 :: V4 a -> V4 a Source #

floor' :: V4 a -> V4 a Source #

ceiling' :: V4 a -> V4 a Source #

fract' :: V4 a -> V4 a Source #

mod'' :: V4 a -> V4 a -> V4 a Source #

mix :: V4 a -> V4 a -> V4 a -> V4 a Source #

atan2' :: V4 a -> V4 a -> V4 a Source #

Real' a => Real' (V3 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

rsqrt :: V3 a -> V3 a Source #

exp2 :: V3 a -> V3 a Source #

log2 :: V3 a -> V3 a Source #

floor' :: V3 a -> V3 a Source #

ceiling' :: V3 a -> V3 a Source #

fract' :: V3 a -> V3 a Source #

mod'' :: V3 a -> V3 a -> V3 a Source #

mix :: V3 a -> V3 a -> V3 a -> V3 a Source #

atan2' :: V3 a -> V3 a -> V3 a Source #

Real' a => Real' (V2 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

rsqrt :: V2 a -> V2 a Source #

exp2 :: V2 a -> V2 a Source #

log2 :: V2 a -> V2 a Source #

floor' :: V2 a -> V2 a Source #

ceiling' :: V2 a -> V2 a Source #

fract' :: V2 a -> V2 a Source #

mod'' :: V2 a -> V2 a -> V2 a Source #

mix :: V2 a -> V2 a -> V2 a -> V2 a Source #

atan2' :: V2 a -> V2 a -> V2 a Source #

Real' a => Real' (V1 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

rsqrt :: V1 a -> V1 a Source #

exp2 :: V1 a -> V1 a Source #

log2 :: V1 a -> V1 a Source #

floor' :: V1 a -> V1 a Source #

ceiling' :: V1 a -> V1 a Source #

fract' :: V1 a -> V1 a Source #

mod'' :: V1 a -> V1 a -> V1 a Source #

mix :: V1 a -> V1 a -> V1 a -> V1 a Source #

atan2' :: V1 a -> V1 a -> V1 a Source #

Real' (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

rsqrt :: S x Float -> S x Float Source #

exp2 :: S x Float -> S x Float Source #

log2 :: S x Float -> S x Float Source #

floor' :: S x Float -> S x Float Source #

ceiling' :: S x Float -> S x Float Source #

fract' :: S x Float -> S x Float Source #

mod'' :: S x Float -> S x Float -> S x Float Source #

mix :: S x Float -> S x Float -> S x Float -> S x Float Source #

atan2' :: S x Float -> S x Float -> S x Float Source #

class (IfB a, OrdB a, Floating a) => FloatingOrd a where Source #

This class provides various order comparing functions

Minimal complete definition

Nothing

Methods

clamp :: a -> a -> a -> a Source #

saturate :: a -> a Source #

step :: a -> a -> a Source #

smoothstep :: a -> a -> a -> a Source #

Instances

Instances details
FloatingOrd Double Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

FloatingOrd Float Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

FloatingOrd (S x Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Methods

clamp :: S x Float -> S x Float -> S x Float -> S x Float Source #

saturate :: S x Float -> S x Float Source #

step :: S x Float -> S x Float -> S x Float Source #

smoothstep :: S x Float -> S x Float -> S x Float -> S x Float Source #

Additional functions

dFdx :: FFloat -> FFloat Source #

The derivative in x using local differencing of the rasterized value.

dFdy :: FFloat -> FFloat Source #

The derivative in y using local differencing of the rasterized value.

fwidth :: FFloat -> FFloat Source #

The sum of the absolute derivative in x and y using local differencing of the rasterized value.

Shader control structures

while :: forall a x. ShaderType a x => (a -> S x Bool) -> (a -> a) -> a -> a Source #

while f g x will iteratively transform x with g as long as f generates true.

ifThen :: forall a x. ShaderType a x => S x Bool -> (a -> a) -> a -> a Source #

ifThen c f x will return f x if c evaluates to true or x otherwise.

In most cases functionally equivalent to ifThenElse' but usually generate smaller shader code since the last argument is not inlined into the two branches, which also would affect implicit derivates (e.g. dFdx, dFdy or sampling using SampleAuto)

ifThenElse :: forall a b x. (ShaderType a x, ShaderType b x) => S x Bool -> (a -> b) -> (a -> b) -> a -> b Source #

ifThenElse c f g x will return f x if c evaluates to true or g x otherwise.

In most cases functionally equivalent to ifThenElse' but usually generate smaller shader code since the last argument is not inlined into the two branches, which also would affect implicit derivates (e.g. dFdx, dFdy or sampling using SampleAuto)

ifThenElse' :: forall a x. ShaderType a x => S x Bool -> a -> a -> a Source #

Works just like ifB, return second argument if first is true otherwise return third argument.

The difference from ifB is that it in most cases generate more efficient code when a is a compound type (e.g. a tuple or a vector). For simple types such as S x Float, ifThenElse' == ifB.

data ShaderBase a x Source #

An opaque type

class ShaderType a x where Source #

Constraint for types that may pass in and out of shader control structures. Define your own instances in terms of others and make sure to make toBase as lazy as possible.

Associated Types

type ShaderBaseType a Source #

A base type that this type can convert into. Use the ShaderBaseType function on an existing instance of ShaderType to define this in your instance.

Methods

toBase :: x -> a -> ShaderBase (ShaderBaseType a) x Source #

Convert this type to the shader base type. Make sure this is as lazy as possible (e.g. use tilde (~) on each pattern match).

fromBase :: x -> ShaderBase (ShaderBaseType a) x -> a Source #

Convert back from the shader base type to this type.

Instances

Instances details
ShaderType () x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType () Source #

Methods

toBase :: x -> () -> ShaderBase (ShaderBaseType ()) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType ()) x -> () Source #

ShaderType a x => ShaderType (V0 a) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (V0 a) Source #

Methods

toBase :: x -> V0 a -> ShaderBase (ShaderBaseType (V0 a)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (V0 a)) x -> V0 a Source #

ShaderType a x => ShaderType (V4 a) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (V4 a) Source #

Methods

toBase :: x -> V4 a -> ShaderBase (ShaderBaseType (V4 a)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (V4 a)) x -> V4 a Source #

ShaderType a x => ShaderType (V3 a) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (V3 a) Source #

Methods

toBase :: x -> V3 a -> ShaderBase (ShaderBaseType (V3 a)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (V3 a)) x -> V3 a Source #

ShaderType a x => ShaderType (V2 a) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (V2 a) Source #

Methods

toBase :: x -> V2 a -> ShaderBase (ShaderBaseType (V2 a)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (V2 a)) x -> V2 a Source #

ShaderType a x => ShaderType (V1 a) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (V1 a) Source #

Methods

toBase :: x -> V1 a -> ShaderBase (ShaderBaseType (V1 a)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (V1 a)) x -> V1 a Source #

(ShaderType a x, ShaderType b x) => ShaderType (a, b) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (a, b) Source #

Methods

toBase :: x -> (a, b) -> ShaderBase (ShaderBaseType (a, b)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (a, b)) x -> (a, b) Source #

ShaderType (S x (GenerativeGeometry p a)) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x (GenerativeGeometry p a)) Source #

ShaderType (S x Bool) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Bool) Source #

Methods

toBase :: x -> S x Bool -> ShaderBase (ShaderBaseType (S x Bool)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (S x Bool)) x -> S x Bool Source #

ShaderType (S x Word) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Word) Source #

Methods

toBase :: x -> S x Word -> ShaderBase (ShaderBaseType (S x Word)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (S x Word)) x -> S x Word Source #

ShaderType (S x Int) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Int) Source #

Methods

toBase :: x -> S x Int -> ShaderBase (ShaderBaseType (S x Int)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (S x Int)) x -> S x Int Source #

ShaderType (S x Float) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (S x Float) Source #

(ShaderType a x, ShaderType b x, ShaderType c x) => ShaderType (a, b, c) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (a, b, c) Source #

Methods

toBase :: x -> (a, b, c) -> ShaderBase (ShaderBaseType (a, b, c)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (a, b, c)) x -> (a, b, c) Source #

(ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x) => ShaderType (a, b, c, d) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (a, b, c, d) Source #

Methods

toBase :: x -> (a, b, c, d) -> ShaderBase (ShaderBaseType (a, b, c, d)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (a, b, c, d)) x -> (a, b, c, d) Source #

(ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x, ShaderType e x) => ShaderType (a, b, c, d, e) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (a, b, c, d, e) Source #

Methods

toBase :: x -> (a, b, c, d, e) -> ShaderBase (ShaderBaseType (a, b, c, d, e)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (a, b, c, d, e)) x -> (a, b, c, d, e) Source #

(ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x, ShaderType e x, ShaderType f x) => ShaderType (a, b, c, d, e, f) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (a, b, c, d, e, f) Source #

Methods

toBase :: x -> (a, b, c, d, e, f) -> ShaderBase (ShaderBaseType (a, b, c, d, e, f)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (a, b, c, d, e, f)) x -> (a, b, c, d, e, f) Source #

(ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x, ShaderType e x, ShaderType f x, ShaderType g x) => ShaderType (a, b, c, d, e, f, g) x Source # 
Instance details

Defined in Graphics.GPipe.Internal.Expr

Associated Types

type ShaderBaseType (a, b, c, d, e, f, g) Source #

Methods

toBase :: x -> (a, b, c, d, e, f, g) -> ShaderBase (ShaderBaseType (a, b, c, d, e, f, g)) x Source #

fromBase :: x -> ShaderBase (ShaderBaseType (a, b, c, d, e, f, g)) x -> (a, b, c, d, e, f, g) Source #