GPipe-1.1.2: A functional graphics API for programmable GPUsSource codeContentsIndex
Graphics.GPipe.Stream
Contents
Common classes
Reexports
Description

A GPipe program mainly consits of creating and manipulating streams of primitives and fragments. The modules Graphics.GPipe.Stream.Primitive and Graphics.GPipe.Stream.Fragment defines those streams.

All atomic values except textures in streams uses the Vertex or Fragment type constructors. Composite types are created by composing the atomic Vertex or Fragment types, rather than wrapping the composite type in any of those type constructors. This module provides the common classes for those atomic types, as well as reexports of imported common types and modules.

Synopsis
class GPU a where
type CPU a
toGPU :: CPU a -> a
class (Ord a, Floating a) => Real' a where
rsqrt :: a -> a
exp2 :: a -> a
log2 :: a -> a
floor' :: a -> a
ceiling' :: a -> a
fract' :: a -> a
mod' :: a -> a -> a
clamp :: a -> a -> a -> a
saturate :: a -> a
mix :: a -> a -> a -> a
step :: a -> a -> a
smoothstep :: a -> a -> a -> a
class Convert a where
type ConvertFloat a
type ConvertInt a
toFloat :: a -> ConvertFloat a
toInt :: a -> ConvertInt a
:. (:.)
Vec2
Vec3
Vec4
module Data.Vec.LinAlg
module Data.Boolean
Common classes
class GPU a whereSource
Denotes a type on the GPU, that can be moved there from the CPU (through the internal use of uniforms). Use the existing instances of this class to create new ones. Note that toGPU should not be strict on its argument. Its definition should also always use the same series of toGPU calls to convert values of the same type. This unfortunatly rules out ordinary lists (but instances for fixed length lists from the Vec package are however provided).
Associated Types
type CPU a Source
The type on the CPU.
Methods
toGPU :: CPU a -> aSource
Converts a value from the CPU to the GPU.
show/hide Instances
GPU ()
GPU (Fragment Bool)
GPU (Fragment Float)
GPU (Fragment Int)
GPU (Vertex Bool)
GPU (Vertex Float)
GPU (Vertex Int)
(GPU a, GPU b) => GPU ((,) a b)
(GPU a, GPU b) => GPU (a :. b)
(GPU a, GPU b, GPU c) => GPU ((,,) a b c)
(GPU a, GPU b, GPU c, GPU d) => GPU ((,,,) a b c d)
class (Ord a, Floating a) => Real' a whereSource
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' and ceiling'.
Methods
rsqrt :: a -> aSource
exp2 :: a -> aSource
log2 :: a -> aSource
floor' :: a -> aSource
ceiling' :: a -> aSource
fract' :: a -> aSource
mod' :: a -> a -> aSource
clamp :: a -> a -> a -> aSource
saturate :: a -> aSource
mix :: a -> a -> a -> aSource
step :: a -> a -> aSource
smoothstep :: a -> a -> a -> aSource
show/hide Instances
class Convert a whereSource
Provides a common way to convert numeric types to integer and floating point representations.
Associated Types
type ConvertFloat a Source
type ConvertInt a Source
Methods
toFloat :: a -> ConvertFloat aSource
Convert to a floating point number.
toInt :: a -> ConvertInt aSource
Convert to an integral number, using truncation if necessary.
show/hide Instances
Reexports
:. (:.)
Vec2
Vec3
Vec4
module Data.Vec.LinAlg
module Data.Boolean
Produced by Haddock version 2.4.2