Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides the DSL for shader operations in GPipe. The type
is an opaque type that represents a value of type S
x aa
in a shader stage x
, eg S F Float
means a
floating point value in a fragment stream.
Synopsis
- data S x a
- data V
- data F
- type VFloat = S V Float
- type VInt = S V Int
- type VWord = S V Word
- type VBool = S V Bool
- type FFloat = S F Float
- type FInt = S F Int
- type FWord = S F Word
- type FBool = S F Bool
- type GGenerativeGeometry p a = S G (GenerativeGeometry p a)
- class Convert a where
- type ConvertFloat a
- type ConvertInt a
- type ConvertWord a
- toFloat :: a -> ConvertFloat a
- toInt :: a -> ConvertInt a
- toWord :: a -> ConvertWord a
- class Integral' a where
- class Bits' a where
- class Floating a => Real' a where
- class (IfB a, OrdB a, Floating a) => FloatingOrd a where
- clamp :: a -> a -> a -> a
- saturate :: a -> a
- step :: a -> a -> a
- smoothstep :: a -> a -> a -> a
- dFdx :: FFloat -> FFloat
- dFdy :: FFloat -> FFloat
- fwidth :: FFloat -> FFloat
- while :: forall a x. ShaderType a x => (a -> S x Bool) -> (a -> a) -> a -> a
- ifThen :: forall a x. ShaderType a x => S x Bool -> (a -> a) -> a -> a
- ifThenElse :: forall a b x. (ShaderType a x, ShaderType b x) => S x Bool -> (a -> b) -> (a -> b) -> a -> b
- ifThenElse' :: forall a x. ShaderType a x => S x Bool -> a -> a -> a
- data ShaderBase a x
- class ShaderType a x where
- type ShaderBaseType a
- toBase :: x -> a -> ShaderBase (ShaderBaseType a) x
- fromBase :: x -> ShaderBase (ShaderBaseType a) x -> a
Atomic shader type
Instances
Instances
type GGenerativeGeometry p a = S G (GenerativeGeometry p a) 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.
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
Convert Float Source # | |
Defined in Graphics.GPipe.Internal.Expr | |
Convert Int Source # | |
Defined in Graphics.GPipe.Internal.Expr | |
Convert Word Source # | |
Defined in Graphics.GPipe.Internal.Expr | |
Convert (S x Word) Source # | |
Defined in Graphics.GPipe.Internal.Expr type ConvertFloat (S x Word) Source # type ConvertInt (S x Word) Source # type ConvertWord (S x Word) Source # | |
Convert (S x Int) Source # | |
Convert (S x Float) Source # | |
Defined in Graphics.GPipe.Internal.Expr type ConvertFloat (S x Float) Source # type ConvertInt (S x Float) Source # type ConvertWord (S x Float) Source # |
class Integral' a where Source #
Instances
Integral' Int Source # | |
Integral' Int8 Source # | |
Integral' Int16 Source # | |
Integral' Int32 Source # | |
Integral' Word Source # | |
Integral' Word8 Source # | |
Integral' Word16 Source # | |
Integral' Word32 Source # | |
Integral' a => Integral' (V0 a) Source # | |
Integral' a => Integral' (V4 a) Source # | |
Integral' a => Integral' (V3 a) Source # | |
Integral' a => Integral' (V2 a) Source # | |
Integral' a => Integral' (V1 a) Source # | |
Integral' (S x Word) Source # | |
Integral' (S x Int) Source # | |
Instances
Bits' (S x Word) Source # | |
Defined in Graphics.GPipe.Internal.Expr | |
Bits' (S x Int) Source # | |
Defined in Graphics.GPipe.Internal.Expr |
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 Float
s and Double
s.
Instances
Real' Double Source # | |
Defined in Graphics.GPipe.Internal.Expr rsqrt :: Double -> Double Source # exp2 :: Double -> Double Source # log2 :: Double -> Double Source # floor' :: Double -> Double Source # ceiling' :: Double -> Double Source # fract' :: Double -> Double Source # mod'' :: Double -> Double -> Double Source # | |
Real' Float Source # | |
Defined in Graphics.GPipe.Internal.Expr | |
Real' a => Real' (V0 a) Source # | |
Real' a => Real' (V4 a) Source # | |
Real' a => Real' (V3 a) Source # | |
Real' a => Real' (V2 a) Source # | |
Real' a => Real' (V1 a) Source # | |
Real' (S x Float) Source # | |
Defined in Graphics.GPipe.Internal.Expr 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 # |
class (IfB a, OrdB a, Floating a) => FloatingOrd a where Source #
This class provides various order comparing functions
Nothing
Instances
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 #
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.
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.
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.