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

Graphics.GPipe.Internal.Texture

Synopsis

Documentation

type Size1 = Int 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 #

useTex :: Integral a => TexName -> GLenum -> a -> IO Int Source #

type Level = Int 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 #

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 #

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 #

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 #

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 #

genMips :: forall ctx (m :: Type -> Type) os. (ContextHandler ctx, MonadIO m) => TexName -> GLenum -> ContextT ctx os m () Source #

data Filter Source #

Constructors

Nearest 
Linear 

Instances

Instances details
Enum Filter Source # 
Instance details

Defined in Graphics.GPipe.Internal.Texture

Eq Filter Source # 
Instance details

Defined in Graphics.GPipe.Internal.Texture

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

data SamplerFilter c where Source #

A GADT for sample filters, where SamplerFilter cannot be used for integer textures.

newSampler1D :: forall os s c. ColorSampleable c => (s -> (Texture1D os (Format c), SamplerFilter c, (EdgeMode, BorderColor c))) -> Shader os s (Sampler1D (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 #

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 #

doForSampler :: Int -> (s -> Binding -> IO Int) -> ShaderM s () Source #

data Shadow Source #

Used instead of Format for shadow samplers. These samplers have specialized sampler values, see sample1DShadow and friends.

data Sampler1D f Source #

Constructors

Sampler1D Int Bool String 

data Sampler2D f Source #

Constructors

Sampler2D Int Bool String 

data Sampler3D f Source #

Constructors

Sampler3D Int Bool String 

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 FragmentStreams.

Constructors

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.

Constructors

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 #

type ColorSample x f = Color f (S x (ColorElement f)) Source #

The type of a color sample made by a texture t

sample2D :: forall c x. ColorSampleable c => Sampler2D (Format c) -> SampleLod2 x -> SampleProj x -> SampleOffset2 x -> V2 (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 #

t1t3 :: S x Float -> S x Float -> V3 (S x Float) Source #

t2t3 :: V2 t -> t -> V3 t Source #

t3t4 :: V3 t -> t -> V4 t Source #

texelFetch1D :: forall c x. ColorSampleable c => Sampler1D (Format c) -> SampleOffset1 x -> S x Level -> 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 #

texelFetch3D :: forall c x. ColorSampleable c => Sampler3D (Format c) -> SampleOffset3 x -> S x Level -> V3 (S x Int) -> ColorSample x c 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 #

offParam :: Maybe t -> (t -> String) -> String Source #

data Image f 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.

Constructors

Image TexName Int Int (V2 Int) (GLuint -> IO ()) 

Instances

Instances details
Eq (Image f) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Texture

Methods

(==) :: Image f -> Image f -> Bool #

(/=) :: Image f -> Image f -> Bool #

imageEquals :: Image a -> Image b -> Bool Source #

Compare two images that doesn't necessarily has same type

imageSize :: Image f -> V2 Int Source #

Retrieve the 2D size an image