lambdacube-core-0.1.0: LambdaCube 3D is a domain specific language and library that makes it possible to program GPUs in a purely functional style.

Safe HaskellNone

LC_T_APIType

Documentation

data NatNum whereSource

Constructors

N0 :: NatNum 0 
N1 :: NatNum 1 
N2 :: NatNum 2 
N3 :: NatNum 3 
N4 :: NatNum 4 
N5 :: NatNum 5 
N6 :: NatNum 6 
N7 :: NatNum 7 
N8 :: NatNum 8 
N9 :: NatNum 9 

class InputTuple tup whereSource

Associated Types

type InputTupleRepr tup Source

Methods

toInputList :: tup -> [(ByteString, InputType)]Source

Instances

data VertexStream primitive t Source

data PrimitiveStream primitive clipDistances layerCount freq t Source

data FragmentStream layerCount t Source

data ZZ Source

Constructors

ZZ 

data tail :+: head Source

Constructors

!tail :+: !head 

Instances

data FlatTuple c a t whereSource

Constructors

ZT :: FlatTuple c a ZZ 
:. :: c t => a t -> FlatTuple c a t' -> FlatTuple c a (t :+: t') 

data Interpolated e a whereSource

Constructors

Flat :: e a -> Interpolated e a 
Smooth :: IsFloating a => e a -> Interpolated e a 
NoPerspective :: IsFloating a => e a -> Interpolated e a 

data Color a Source

data Depth a Source

Instances

type family PrimitiveVertices primitive a Source

class NoConstraint a Source

Instances

type FrameBuffer layerCount t = FlatTuple NoConstraint (Image layerCount) tSource

data Image layerCount t whereSource

Constructors

DepthImage :: SingI layerCount => NatNum layerCount -> Float -> Image layerCount (Depth Float) 
StencilImage :: SingI layerCount => NatNum layerCount -> Int32 -> Image layerCount (Stencil Int32) 
ColorImage :: (IsNum t, IsVecScalar d color t, IsScalar color, SingI layerCount) => NatNum layerCount -> color -> Image layerCount (Color color) 

type family FTRepr a :: *Source

type family FTRepr' a :: *Source

type family ColorRepr a :: *Source

type family NoStencilRepr a :: *Source

data TextureMipMap Source

Constructors

TexMip 
TexNoMip 

data MipMap t whereSource

Constructors

NoMip :: MipMap TexNoMip 
Mip :: Int -> Int -> MipMap TexMip 
AutoMip :: Int -> Int -> MipMap TexMip 

type family TexDataRepr arity t Source

data TextureType whereSource

Constructors

Texture1D :: SingI layerCount => TextureDataType t ar -> NatNum layerCount -> TextureType Tex1D TexMip (TexArrRepr layerCount) layerCount t ar 
Texture2D :: SingI layerCount => TextureDataType t ar -> NatNum layerCount -> TextureType Tex2D TexMip (TexArrRepr layerCount) layerCount t ar 
Texture3D :: TextureDataType (Regular t) ar -> TextureType Tex3D TexMip SingleTex 1 (Regular t) ar 
TextureCube :: TextureDataType t ar -> TextureType Tex2D TexMip CubeTex 6 t ar 
TextureRect :: TextureDataType t ar -> TextureType TexRect TexNoMip SingleTex 1 t ar 
Texture2DMS :: SingI layerCount => TextureDataType (Regular t) ar -> NatNum layerCount -> TextureType Tex2D TexNoMip (TexArrRepr layerCount) layerCount (MultiSample t) ar 
TextureBuffer :: TextureDataType (Regular t) ar -> TextureType Tex1D TexNoMip SingleTex 1 (Buffer t) ar 

data Texture gp dim arr t ar whereSource

Constructors

TextureSlot :: IsValidTextureSlot t => ByteString -> TextureType dim mip arr layerCount t ar -> Texture gp dim arr t ar 
Texture :: (IsScalar (TexSizeRepr dim), IsMipValid canMip mip) => TextureType dim canMip arr layerCount t ar -> TexSizeRepr dim -> MipMap mip -> [gp (Image layerCount (TexDataRepr ar t))] -> Texture gp dim arr t ar 

type family TexSizeRepr a Source

data Frequency Source

Constructors

Obj 
V 
G 
F