Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Texture1D os a = Texture1D TexName Size1 MaxLevels
- data Texture1DArray os a = Texture1DArray TexName Size2 MaxLevels
- data Texture2D os a
- data Texture2DArray os a = Texture2DArray TexName Size3 MaxLevels
- data Texture3D os a = Texture3D TexName Size3 MaxLevels
- data TextureCube os a = TextureCube TexName Size1 MaxLevels
- type MaxLevels = Int
- type Size1 = Int
- type Size2 = V2 Int
- type Size3 = V3 Int
- newTexture1D :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size1 -> MaxLevels -> ContextT ctx os m (Texture1D os (Format c))
- newTexture1DArray :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size2 -> MaxLevels -> ContextT ctx os m (Texture1DArray os (Format c))
- newTexture2D :: forall ctx w os f c m. (ContextHandler ctx, TextureFormat c, MonadIO m) => Format c -> Size2 -> MaxLevels -> ContextT ctx os m (Texture2D os (Format c))
- newTexture2DArray :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size3 -> MaxLevels -> ContextT ctx os m (Texture2DArray os (Format c))
- newTexture3D :: forall ctx w os f c m. (ContextHandler ctx, ColorRenderable c, MonadIO m) => Format c -> Size3 -> MaxLevels -> ContextT ctx os m (Texture3D os (Format c))
- newTextureCube :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size1 -> MaxLevels -> ContextT ctx os m (TextureCube os (Format c))
- getGlValue :: (ContextHandler ctx, MonadIO m) => GLenum -> ContextT ctx os m Int
- setDefaultTexParams :: GLenum -> Int -> IO ()
- texture1DLevels :: Texture1D os f -> Int
- texture1DArrayLevels :: Texture1DArray os f -> Int
- texture2DLevels :: Texture2D os f -> Int
- texture2DArrayLevels :: Texture2DArray os f -> Int
- texture3DLevels :: Texture3D os f -> Int
- textureCubeLevels :: TextureCube os f -> Int
- texture1DSizes :: Texture1D os f -> [Size1]
- texture1DArraySizes :: Texture1DArray os f -> [Size2]
- texture2DSizes :: Texture2D os f -> [Size2]
- texture2DArraySizes :: Texture2DArray os f -> [Size3]
- texture3DSizes :: Texture3D os f -> [Size3]
- textureCubeSizes :: TextureCube os f -> [Size1]
- calcLevelSize :: Int -> Int -> Int
- calcMaxLevels :: Int -> Int
- type TexName = IORef GLuint
- makeTex :: (ContextHandler ctx, MonadIO m) => ContextT ctx os m TexName
- makeRenderBuff :: (ContextHandler ctx, MonadIO m) => ContextT ctx os m TexName
- useTex :: Integral a => TexName -> GLenum -> a -> IO Int
- useTexSync :: TexName -> GLenum -> IO ()
- type Level = Int
- data CubeSide
- type StartPos1 = Int
- type StartPos2 = V2 Int
- type StartPos3 = V3 Int
- writeTexture1D :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> [h] -> ContextT ctx os m ()
- writeTexture1DArray :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size2 -> [h] -> ContextT ctx os m ()
- writeTexture2D :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> [h] -> ContextT ctx os m ()
- writeTexture2DArray :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size3 -> [h] -> ContextT ctx os m ()
- writeTexture3D :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size3 -> [h] -> ContextT ctx os m ()
- writeTextureCube :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> [h] -> ContextT ctx os m ()
- writeTexture1DFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- writeTexture1DArrayFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- writeTexture2DFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- writeTexture2DArrayFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size3 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- writeTexture3DFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size3 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- writeTextureCubeFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- readTexture1D :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a
- readTexture1DArray :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size1 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a
- readTexture2D :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a
- readTexture2DArray :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a
- readTexture3D :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a
- readTextureCube :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a
- readTexture1DToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- readTexture1DArrayToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size1 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- readTexture2DToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- readTexture2DArrayToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- readTexture3DToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- readTextureCubeToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m ()
- getGlColorFormat :: (TextureFormat f, BufferFormat b) => f -> b -> GLenum
- setGlPixelStoreRange :: Int -> Int -> Int -> Int -> Int -> IO ()
- generateTexture1DMipmap :: (ContextHandler ctx, MonadIO m) => Texture1D os f -> ContextT ctx os m ()
- generateTexture1DArrayMipmap :: (ContextHandler ctx, MonadIO m) => Texture1DArray os f -> ContextT ctx os m ()
- generateTexture2DMipmap :: (ContextHandler ctx, MonadIO m) => Texture2D os f -> ContextT ctx os m ()
- generateTexture2DArrayMipmap :: (ContextHandler ctx, MonadIO m) => Texture2DArray os f -> ContextT ctx os m ()
- generateTexture3DMipmap :: (ContextHandler ctx, MonadIO m) => Texture3D os f -> ContextT ctx os m ()
- generateTextureCubeMipmap :: (ContextHandler ctx, MonadIO m) => TextureCube os f -> ContextT ctx os m ()
- genMips :: forall ctx (m :: Type -> Type) os. (ContextHandler ctx, MonadIO m) => TexName -> GLenum -> ContextT ctx os m ()
- data Filter
- data EdgeMode
- type BorderColor c = Color c (ColorElement c)
- type Anisotropy = Maybe Float
- type MinFilter = Filter
- type MagFilter = Filter
- type LodFilter = Filter
- data SamplerFilter c where
- SamplerFilter :: ColorElement c ~ Float => MagFilter -> MinFilter -> LodFilter -> Anisotropy -> SamplerFilter c
- SamplerNearest :: SamplerFilter c
- type EdgeMode2 = V2 EdgeMode
- type EdgeMode3 = V3 EdgeMode
- data ComparisonFunction
- getGlCompFunc :: (Num a, Eq a) => ComparisonFunction -> a
- newSampler1D :: forall os s c. ColorSampleable c => (s -> (Texture1D os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1D (Format c))
- newSampler1DArray :: forall os s c. ColorSampleable c => (s -> (Texture1DArray os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1DArray (Format c))
- newSampler2D :: forall os s c. ColorSampleable c => (s -> (Texture2D os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2D (Format c))
- newSampler2DArray :: forall os s c. ColorSampleable c => (s -> (Texture2DArray os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2DArray (Format c))
- newSampler3D :: forall os s c. ColorRenderable c => (s -> (Texture3D os (Format c), SamplerFilter c, (EdgeMode3, BorderColor c))) -> Shader os s (Sampler3D (Format c))
- newSamplerCube :: forall os s c. ColorSampleable c => (s -> (TextureCube os (Format c), SamplerFilter c)) -> Shader os s (SamplerCube (Format c))
- newSampler1DShadow :: forall os s d. DepthRenderable d => (s -> (Texture1D os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1D Shadow)
- newSampler1DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture1DArray os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1DArray Shadow)
- newSampler2DShadow :: forall os s d. DepthRenderable d => (s -> (Texture2D os d, SamplerFilter (Format d), (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2D Shadow)
- newSampler2DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture2DArray os (Format d), SamplerFilter d, (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2DArray Shadow)
- newSamplerCubeShadow :: forall os s d. DepthRenderable d => (s -> (TextureCube os (Format d), SamplerFilter d, ComparisonFunction)) -> Shader os s (SamplerCube Shadow)
- setNoShadowMode :: GLenum -> IO ()
- setShadowFunc :: GLenum -> ComparisonFunction -> IO ()
- setEdgeMode :: GLenum -> (Maybe EdgeMode, Maybe EdgeMode, Maybe EdgeMode) -> IO () -> IO ()
- setSamplerFilter :: GLenum -> SamplerFilter a -> IO ()
- setSamplerFilter' :: GLenum -> MagFilter -> MinFilter -> LodFilter -> Anisotropy -> IO ()
- doForSampler :: Int -> (s -> Binding -> IO Int) -> ShaderM s ()
- data Shadow
- data Sampler1D f = Sampler1D Int Bool String
- data Sampler1DArray f = Sampler1DArray Int Bool String
- data Sampler2D f = Sampler2D Int Bool String
- data Sampler2DArray f = Sampler2DArray Int Bool String
- data Sampler3D f = Sampler3D Int Bool String
- data SamplerCube f = SamplerCube Int Bool String
- data SampleLod vx x where
- SampleAuto :: SampleLod v F
- SampleBias :: FFloat -> SampleLod vx F
- SampleLod :: S x Float -> SampleLod vx x
- SampleGrad :: vx -> vx -> SampleLod vx x
- data SampleLod' vx x where
- SampleAuto' :: SampleLod' v F
- SampleBias' :: FFloat -> SampleLod' vx F
- SampleGrad' :: vx -> vx -> SampleLod' vx x
- type SampleLod1 x = SampleLod (S x Float) x
- type SampleLod2 x = SampleLod (V2 (S x Float)) x
- type SampleLod3 x = SampleLod (V3 (S x Float)) x
- type SampleLod2' x = SampleLod' (V2 (S x Float)) x
- type SampleLod3' x = SampleLod' (V3 (S x Float)) x
- fromLod' :: SampleLod' v x -> SampleLod v x
- type SampleProj x = Maybe (S x Float)
- type SampleOffset1 x = Maybe Int
- type SampleOffset2 x = Maybe (V2 Int)
- type SampleOffset3 x = Maybe (V3 Int)
- type ColorSample x f = Color f (S x (ColorElement f))
- type ReferenceValue x = S x Float
- sample1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> S x Float -> ColorSample x c
- sample1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleLod1 x -> SampleOffset1 x -> V2 (S x Float) -> ColorSample x c
- sample2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> V2 (S x Float) -> ColorSample x c
- sample2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleLod2 x -> SampleOffset2 x -> V3 (S x Float) -> ColorSample x c
- sample3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleLod3 x -> SampleProj x -> SampleOffset3 x -> V3 (S x Float) -> ColorSample x c
- sampleCube :: forall c x. ColorSampleable c => SamplerCube (Format c) -> SampleLod3 x -> V3 (S x Float) -> ColorSample x c
- sample1DShadow :: forall x. Sampler1D Shadow -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> ReferenceValue x -> S x Float -> S x Float
- sample1DArrayShadow :: forall x. Sampler1DArray Shadow -> SampleLod1 x -> SampleOffset1 x -> ReferenceValue x -> V2 (S x Float) -> S x Float
- sample2DShadow :: forall x. Sampler2D Shadow -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> ReferenceValue x -> V2 (S x Float) -> S x Float
- sample2DArrayShadow :: forall x. Sampler2DArray Shadow -> SampleLod2' x -> SampleOffset2 x -> ReferenceValue x -> V3 (S x Float) -> S x Float
- sampleCubeShadow :: forall x. SamplerCube Shadow -> SampleLod3' x -> ReferenceValue x -> V3 (S x Float) -> S x Float
- t1t3 :: S x Float -> S x Float -> V3 (S x Float)
- t2t3 :: V2 t -> t -> V3 t
- t3t4 :: V3 t -> t -> V4 t
- texelFetch1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleOffset1 x -> S x Level -> S x Int -> ColorSample x c
- texelFetch1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleOffset1 x -> S x Level -> V2 (S x Int) -> ColorSample x c
- texelFetch2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleOffset2 x -> S x Level -> V2 (S x Int) -> ColorSample x c
- texelFetch2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleOffset2 x -> S x Level -> V3 (S x Int) -> ColorSample x c
- texelFetch3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleOffset3 x -> S x Level -> V3 (S x Int) -> ColorSample x c
- sampler1DSize :: Sampler1D f -> S x Level -> S x Int
- sampler1DArraySize :: Sampler1DArray f -> S x Level -> V2 (S x Int)
- sampler2DSize :: Sampler2D f -> S x Level -> V2 (S x Int)
- sampler2DArraySize :: Sampler2DArray f -> S x Level -> V3 (S x Int)
- sampler3DSize :: Sampler3D f -> S x Level -> V3 (S x Int)
- samplerCubeSize :: SamplerCube f -> S x Level -> S x Int
- addShadowPrefix :: Bool -> String -> String
- getTextureSize :: String -> Int -> String -> S c Int -> ExprM String
- sample :: e -> String -> String -> String -> Int -> SampleLod lcoord x -> SampleProj x -> Maybe off -> coord -> (coord -> ExprM String) -> (lcoord -> ExprM String) -> (off -> String) -> (coord -> S x Float -> ExprM String) -> V4 (S x e)
- sampleShadow :: String -> Int -> SampleLod lcoord x -> SampleProj x -> Maybe off -> coord -> (coord -> ExprM String) -> (lcoord -> ExprM String) -> (off -> String) -> (coord -> S x Float -> ExprM String) -> S x Float
- fetch :: e -> String -> String -> String -> Int -> S x Int -> Maybe off -> coord -> (coord -> ExprM String) -> (off -> String) -> V4 (S x e)
- v1toF :: S c Float -> ExprM String
- v2toF :: V2 (S c Float) -> ExprM String
- v3toF :: V3 (S c Float) -> ExprM String
- v4toF :: V4 (S c Float) -> ExprM String
- iv1toF :: S c Int -> ExprM String
- iv2toF :: V2 (S c Int) -> ExprM String
- iv3toF :: V3 (S c Int) -> ExprM String
- civ1toF :: Int -> String
- civ2toF :: V2 Int -> String
- civ3toF :: V3 Int -> String
- pv1toF :: S c Float -> S c Float -> ExprM String
- pv2toF :: V2 (S c Float) -> S c Float -> ExprM String
- pv3toF :: V3 (S c Float) -> S c Float -> ExprM String
- sampleFunc :: [Char] -> Maybe a -> SampleLod vx x -> Maybe t1 -> t2 -> (t2 -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> (vx -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> (t1 -> String) -> (t2 -> a -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]
- fetchFunc :: [Char] -> Maybe t1 -> t2 -> S x a -> (t2 -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> (t1 -> String) -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]
- offParam :: Maybe t -> (t -> String) -> String
- offName :: Maybe t -> String
- data Image f = Image TexName Int Int (V2 Int) (GLuint -> IO ())
- imageEquals :: Image a -> Image b -> Bool
- getImageBinding :: Image t -> GLuint -> IO ()
- getImageFBOKey :: Image t -> IO FBOKey
- imageSize :: Image f -> V2 Int
- getTexture1DImage :: Texture1D os f -> Level -> Render os (Image f)
- getTexture1DArrayImage :: Texture1DArray os f -> Level -> Int -> Render os (Image f)
- getTexture2DImage :: Texture2D os f -> Level -> Render os (Image f)
- getTexture2DArrayImage :: Texture2DArray os f -> Level -> Int -> Render os (Image f)
- getTexture3DImage :: Texture3D os f -> Level -> Int -> Render os (Image f)
- getTextureCubeImage :: TextureCube os f -> Level -> CubeSide -> Render os (Image f)
- getLayeredTextureImage :: Texture3D os f -> MaxLevels -> Render os (Image f)
- registerRenderWriteTextureName :: Integral a => IORef a -> Render os ()
- getGlCubeSide :: CubeSide -> GLenum
Documentation
data Texture1DArray os a Source #
data Texture2DArray os a Source #
data TextureCube os a Source #
newTexture1D :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size1 -> MaxLevels -> ContextT ctx os m (Texture1D os (Format c)) Source #
newTexture1DArray :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size2 -> MaxLevels -> ContextT ctx os m (Texture1DArray os (Format c)) Source #
newTexture2D :: forall ctx w os f c m. (ContextHandler ctx, TextureFormat c, MonadIO m) => Format c -> Size2 -> MaxLevels -> ContextT ctx os m (Texture2D os (Format c)) Source #
newTexture2DArray :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size3 -> MaxLevels -> ContextT ctx os m (Texture2DArray os (Format c)) Source #
newTexture3D :: forall ctx w os f c m. (ContextHandler ctx, ColorRenderable c, MonadIO m) => Format c -> Size3 -> MaxLevels -> ContextT ctx os m (Texture3D os (Format c)) Source #
newTextureCube :: forall ctx w os f c m. (ContextHandler ctx, ColorSampleable c, MonadIO m) => Format c -> Size1 -> MaxLevels -> ContextT ctx os m (TextureCube os (Format c)) Source #
getGlValue :: (ContextHandler ctx, MonadIO m) => GLenum -> ContextT ctx os m Int Source #
texture1DLevels :: Texture1D os f -> Int Source #
texture1DArrayLevels :: Texture1DArray os f -> Int Source #
texture2DLevels :: Texture2D os f -> Int Source #
texture2DArrayLevels :: Texture2DArray os f -> Int Source #
texture3DLevels :: Texture3D os f -> Int Source #
textureCubeLevels :: TextureCube os f -> Int Source #
texture1DSizes :: Texture1D os f -> [Size1] Source #
texture1DArraySizes :: Texture1DArray os f -> [Size2] Source #
texture2DSizes :: Texture2D os f -> [Size2] Source #
texture2DArraySizes :: Texture2DArray os f -> [Size3] Source #
texture3DSizes :: Texture3D os f -> [Size3] Source #
textureCubeSizes :: TextureCube os f -> [Size1] Source #
calcMaxLevels :: Int -> Int Source #
makeRenderBuff :: (ContextHandler ctx, MonadIO m) => ContextT ctx os m TexName Source #
Instances
Bounded CubeSide Source # | |
Enum CubeSide Source # | |
Defined in Graphics.GPipe.Internal.Texture | |
Eq CubeSide Source # | |
writeTexture1D :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> [h] -> ContextT ctx os m () Source #
writeTexture1DArray :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size2 -> [h] -> ContextT ctx os m () Source #
writeTexture2D :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> [h] -> ContextT ctx os m () Source #
writeTexture2DArray :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size3 -> [h] -> ContextT ctx os m () Source #
writeTexture3D :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size3 -> [h] -> ContextT ctx os m () Source #
writeTextureCube :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> [h] -> ContextT ctx os m () Source #
writeTexture1DFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
writeTexture1DArrayFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
writeTexture2DFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
writeTexture2DArrayFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size3 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
writeTexture3DFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size3 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
writeTextureCubeFromBuffer :: forall ctx b c h w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
readTexture1D :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a Source #
readTexture1DArray :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size1 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a Source #
readTexture2D :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a Source #
readTexture2DArray :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a Source #
readTexture3D :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a Source #
readTextureCube :: forall ctx a b c h w os f m. (ContextHandler ctx, MonadAsyncException m, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) h ~ b, h ~ HostFormat b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> (a -> h -> ContextT ctx os m a) -> a -> ContextT ctx os m a Source #
readTexture1DToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1D os (Format c) -> Level -> StartPos1 -> Size1 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
readTexture1DArrayToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture1DArray os (Format c) -> Level -> StartPos2 -> Size1 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
readTexture2DToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2D os (Format c) -> Level -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
readTexture2DArrayToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture2DArray os (Format c) -> Level -> StartPos3 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
readTexture3DToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => Texture3D os (Format c) -> Level -> StartPos3 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
readTextureCubeToBuffer :: forall ctx b c w os f m. (ContextHandler ctx, MonadIO m, BufferFormat b, ColorSampleable c, BufferColor (Color c (ColorElement c)) (HostFormat b) ~ b) => TextureCube os (Format c) -> Level -> CubeSide -> StartPos2 -> Size2 -> Buffer os b -> BufferStartPos -> ContextT ctx os m () Source #
getGlColorFormat :: (TextureFormat f, BufferFormat b) => f -> b -> GLenum Source #
generateTexture1DMipmap :: (ContextHandler ctx, MonadIO m) => Texture1D os f -> ContextT ctx os m () Source #
generateTexture1DArrayMipmap :: (ContextHandler ctx, MonadIO m) => Texture1DArray os f -> ContextT ctx os m () Source #
generateTexture2DMipmap :: (ContextHandler ctx, MonadIO m) => Texture2D os f -> ContextT ctx os m () Source #
generateTexture2DArrayMipmap :: (ContextHandler ctx, MonadIO m) => Texture2DArray os f -> ContextT ctx os m () Source #
generateTexture3DMipmap :: (ContextHandler ctx, MonadIO m) => Texture3D os f -> ContextT ctx os m () Source #
generateTextureCubeMipmap :: (ContextHandler ctx, MonadIO m) => TextureCube os f -> ContextT ctx os m () Source #
genMips :: forall ctx (m :: Type -> Type) os. (ContextHandler ctx, MonadIO m) => TexName -> GLenum -> ContextT ctx os m () Source #
Instances
Enum EdgeMode Source # | |
Defined in Graphics.GPipe.Internal.Texture | |
Eq EdgeMode Source # | |
type BorderColor c = Color c (ColorElement c) Source #
type Anisotropy = Maybe Float Source #
data SamplerFilter c where Source #
A GADT for sample filters, where SamplerFilter
cannot be used for integer textures.
SamplerFilter :: ColorElement c ~ Float => MagFilter -> MinFilter -> LodFilter -> Anisotropy -> SamplerFilter c | |
SamplerNearest :: SamplerFilter c |
data ComparisonFunction Source #
Instances
Eq ComparisonFunction Source # | |
Defined in Graphics.GPipe.Internal.Texture (==) :: ComparisonFunction -> ComparisonFunction -> Bool # (/=) :: ComparisonFunction -> ComparisonFunction -> Bool # | |
Ord ComparisonFunction Source # | |
Defined in Graphics.GPipe.Internal.Texture compare :: ComparisonFunction -> ComparisonFunction -> Ordering # (<) :: ComparisonFunction -> ComparisonFunction -> Bool # (<=) :: ComparisonFunction -> ComparisonFunction -> Bool # (>) :: ComparisonFunction -> ComparisonFunction -> Bool # (>=) :: ComparisonFunction -> ComparisonFunction -> Bool # max :: ComparisonFunction -> ComparisonFunction -> ComparisonFunction # min :: ComparisonFunction -> ComparisonFunction -> ComparisonFunction # | |
Show ComparisonFunction Source # | |
Defined in Graphics.GPipe.Internal.Texture showsPrec :: Int -> ComparisonFunction -> ShowS # show :: ComparisonFunction -> String # showList :: [ComparisonFunction] -> ShowS # |
getGlCompFunc :: (Num a, Eq a) => ComparisonFunction -> a Source #
newSampler1D :: forall os s c. ColorSampleable c => (s -> (Texture1D os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1D (Format c)) Source #
newSampler1DArray :: forall os s c. ColorSampleable c => (s -> (Texture1DArray os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1DArray (Format c)) Source #
newSampler2D :: forall os s c. ColorSampleable c => (s -> (Texture2D os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2D (Format c)) Source #
newSampler2DArray :: forall os s c. ColorSampleable c => (s -> (Texture2DArray os (Format c), SamplerFilter c, (EdgeMode2, BorderColor c))) -> Shader os s (Sampler2DArray (Format c)) Source #
newSampler3D :: forall os s c. ColorRenderable c => (s -> (Texture3D os (Format c), SamplerFilter c, (EdgeMode3, BorderColor c))) -> Shader os s (Sampler3D (Format c)) Source #
newSamplerCube :: forall os s c. ColorSampleable c => (s -> (TextureCube os (Format c), SamplerFilter c)) -> Shader os s (SamplerCube (Format c)) Source #
newSampler1DShadow :: forall os s d. DepthRenderable d => (s -> (Texture1D os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1D Shadow) Source #
newSampler1DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture1DArray os (Format d), SamplerFilter d, (EdgeMode, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler1DArray Shadow) Source #
newSampler2DShadow :: forall os s d. DepthRenderable d => (s -> (Texture2D os d, SamplerFilter (Format d), (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2D Shadow) Source #
newSampler2DArrayShadow :: forall os s d. DepthRenderable d => (s -> (Texture2DArray os (Format d), SamplerFilter d, (EdgeMode2, BorderColor d), ComparisonFunction)) -> Shader os s (Sampler2DArray Shadow) Source #
newSamplerCubeShadow :: forall os s d. DepthRenderable d => (s -> (TextureCube os (Format d), SamplerFilter d, ComparisonFunction)) -> Shader os s (SamplerCube Shadow) Source #
setNoShadowMode :: GLenum -> IO () Source #
setShadowFunc :: GLenum -> ComparisonFunction -> IO () Source #
setEdgeMode :: GLenum -> (Maybe EdgeMode, Maybe EdgeMode, Maybe EdgeMode) -> IO () -> IO () Source #
setSamplerFilter :: GLenum -> SamplerFilter a -> IO () Source #
setSamplerFilter' :: GLenum -> MagFilter -> MinFilter -> LodFilter -> Anisotropy -> IO () Source #
Used instead of Format
for shadow samplers. These samplers have specialized sampler values, see sample1DShadow
and friends.
data Sampler1DArray f Source #
data Sampler2DArray f Source #
data SamplerCube f Source #
data SampleLod vx x where Source #
A GADT to specify where the level of detail and/or partial derivates should be taken from. Some values of this GADT are restricted to
only FragmentStream
s.
SampleAuto :: SampleLod v F | |
SampleBias :: FFloat -> SampleLod vx F | |
SampleLod :: S x Float -> SampleLod vx x | |
SampleGrad :: vx -> vx -> SampleLod vx x |
data SampleLod' vx x where Source #
For some reason, OpenGl doesnt allow explicit lod to be specified for some sampler types, hence this extra GADT.
SampleAuto' :: SampleLod' v F | |
SampleBias' :: FFloat -> SampleLod' vx F | |
SampleGrad' :: vx -> vx -> SampleLod' vx x |
type SampleLod2' x = SampleLod' (V2 (S x Float)) x Source #
type SampleLod3' x = SampleLod' (V3 (S x Float)) x Source #
fromLod' :: SampleLod' v x -> SampleLod v x Source #
type SampleOffset1 x = Maybe Int Source #
type ColorSample x f = Color f (S x (ColorElement f)) Source #
The type of a color sample made by a texture t
type ReferenceValue x = S x Float Source #
sample1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> S x Float -> ColorSample x c Source #
sample1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleLod1 x -> SampleOffset1 x -> V2 (S x Float) -> ColorSample x c Source #
sample2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> V2 (S x Float) -> ColorSample x c Source #
sample2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleLod2 x -> SampleOffset2 x -> V3 (S x Float) -> ColorSample x c Source #
sample3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleLod3 x -> SampleProj x -> SampleOffset3 x -> V3 (S x Float) -> ColorSample x c Source #
sampleCube :: forall c x. ColorSampleable c => SamplerCube (Format c) -> SampleLod3 x -> V3 (S x Float) -> ColorSample x c Source #
sample1DShadow :: forall x. Sampler1D Shadow -> SampleLod1 x -> SampleProj x -> SampleOffset1 x -> ReferenceValue x -> S x Float -> S x Float Source #
sample1DArrayShadow :: forall x. Sampler1DArray Shadow -> SampleLod1 x -> SampleOffset1 x -> ReferenceValue x -> V2 (S x Float) -> S x Float Source #
sample2DShadow :: forall x. Sampler2D Shadow -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> ReferenceValue x -> V2 (S x Float) -> S x Float Source #
sample2DArrayShadow :: forall x. Sampler2DArray Shadow -> SampleLod2' x -> SampleOffset2 x -> ReferenceValue x -> V3 (S x Float) -> S x Float Source #
sampleCubeShadow :: forall x. SamplerCube Shadow -> SampleLod3' x -> ReferenceValue x -> V3 (S x Float) -> S x Float Source #
texelFetch1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleOffset1 x -> S x Level -> S x Int -> ColorSample x c Source #
texelFetch1DArray :: forall c x. ColorSampleable c => Sampler1DArray (Format c) -> SampleOffset1 x -> S x Level -> V2 (S x Int) -> ColorSample x c Source #
texelFetch2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleOffset2 x -> S x Level -> V2 (S x Int) -> ColorSample x c Source #
texelFetch2DArray :: forall c x. ColorSampleable c => Sampler2DArray (Format c) -> SampleOffset2 x -> S x Level -> V3 (S x Int) -> ColorSample x c Source #
texelFetch3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleOffset3 x -> S x Level -> V3 (S x Int) -> ColorSample x c Source #
sampler1DArraySize :: Sampler1DArray f -> S x Level -> V2 (S x Int) Source #
sampler2DArraySize :: Sampler2DArray f -> S x Level -> V3 (S x Int) Source #
samplerCubeSize :: SamplerCube f -> S x Level -> S x Int Source #
sample :: e -> String -> String -> String -> Int -> SampleLod lcoord x -> SampleProj x -> Maybe off -> coord -> (coord -> ExprM String) -> (lcoord -> ExprM String) -> (off -> String) -> (coord -> S x Float -> ExprM String) -> V4 (S x e) Source #
sampleShadow :: String -> Int -> SampleLod lcoord x -> SampleProj x -> Maybe off -> coord -> (coord -> ExprM String) -> (lcoord -> ExprM String) -> (off -> String) -> (coord -> S x Float -> ExprM String) -> S x Float Source #
fetch :: e -> String -> String -> String -> Int -> S x Int -> Maybe off -> coord -> (coord -> ExprM String) -> (off -> String) -> V4 (S x e) Source #
sampleFunc :: [Char] -> Maybe a -> SampleLod vx x -> Maybe t1 -> t2 -> (t2 -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> (vx -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> (t1 -> String) -> (t2 -> a -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char] Source #
fetchFunc :: [Char] -> Maybe t1 -> t2 -> S x a -> (t2 -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char]) -> (t1 -> String) -> SNMapReaderT [String] (StateT ExprState (WriterT String (StateT NextTempVar IO))) [Char] Source #
A texture image is a reference to a 2D array of pixels in a texture. Some textures contain one Image
per level of detail while some contain several.
imageEquals :: Image a -> Image b -> Bool Source #
Compare two images that doesn't necessarily has same type
getTexture1DArrayImage :: Texture1DArray os f -> Level -> Int -> Render os (Image f) Source #
getTexture2DArrayImage :: Texture2DArray os f -> Level -> Int -> Render os (Image f) Source #
getTextureCubeImage :: TextureCube os f -> Level -> CubeSide -> Render os (Image f) Source #
getGlCubeSide :: CubeSide -> GLenum Source #