Hello,
In my not so recent coding for the OpenGL library I’ve met a few difficulties and questions. The most important one is that the current implementation for textures is not scalable. It relies on the assumption that there are only certain amount of texture targets for each dimension (only one for 1D and 3D). As OpenGL 3.0 adds a few targets this would introduce some extra targets this would lead to breaking the api. It's probably best to introduce it in the 'summer release', though earlier might also be possible in some opt in way (extra import?). My proposal for the new implementation of texture target is at the bottom of this email, as I wasn't sure whether or not attachments would work with the mailing list.
Working with the texture targets I saw the constructor 'TextureRectangle', which to my knowledge is part of an extension. This lead to wonder what should we do with extensions, should their enumeration values and functions be included in the OpenGL package or should the be implemented in another separate package (or where you need them)? The current implementation makes the second possibility nearly impossible, try for example adding an extra InternalFormat (without editing OpenGL).
Furthermore, I was asking myself why there isn't any type class GLMarshalable for all those (frustratingly long named) marshal functions, that would lead to some nice utility functions that would make some implantations nicer/easier. If people want to know more about this send an email (it will probably quite a long message). As would I like if there are some negative sides too using typeclasses (less performace/optimization?).
Greetings,
Lars Corbijn
module Graphics.Rendering.OpenGL.GL.Texturing.NewTextureTarget where
class TextureTarget t where
marshal :: t -> GLenum
marshalProxy :: Proxy -> t -> GLenum
-- just one example, more for each target
data TextureTarget2D =
Texture2D
| TextureCubeMap CubeMapTarget -- definition is at the end
| Texture1Darray -- the new one
| TextureRectangle -- As far as I see this is never used in any of the texImage, copy or subData functions. It's part of the TEXTURE_RECTANGLE_ARB
deriving ( Eq, Ord, Show )
-- the normal implementation
instance TextureTarget TextureTarget2D where
marshal = undefined
marshalProxy = undefined
-- and then what it's all about, for the current function see below
texImage2D :: TextureTarget2D -> Proxy -> Level -> PixelInternalFormat -> TextureSize2D -> Border -> PixelData a -> IO ()
texImage2D tt proxy level int (TextureSize2D w h) border pd =
withPixelData pd $ glTexImage2D (marshalProxy proxy tt) level (marshalPixelInternalFormat int) w h border
-- one of the reasons for the TextureTarget typeclass, for the current function see below
getTexImage :: TextureTarget -> Level -> PixelData a -> IO ()
getTexImage t level pd =
withPixelData pd $ glGetTexImage (marshal t) level
--------------------
-- for refference --
--------------------
--The current implementation, it's the worst of the tree (1D, 2D and 3D)
texImage2D :: Maybe CubeMapTarget -> Proxy -> Level -> PixelInternalFormat -> TextureSize2D -> Border -> PixelData a -> IO ()
texImage2D mbCubeMap proxy level int (TextureSize2D w h) border pd =
withPixelData pd $
glTexImage2D
(maybe (marshalProxyTextureTarget proxy Texture2D)
(\c -> if proxy == Proxy then marshalProxyTextureTarget Proxy TextureCubeMap else marshalCubeMapTarget c)
mbCubeMap)
level (marshalPixelInternalFormat int) w h border
-- The current implemtation
getTexImage :: Either TextureTarget CubeMapTarget -> Level -> PixelData a -> IO ()
getTexImage t level pd =
withPixelData pd $
glGetTexImage (either marshalTextureTarget marshalCubeMapTarget t) level
data CubeMapTarget =
TextureCubeMapPositiveX
| TextureCubeMapNegativeX
| TextureCubeMapPositiveY
| TextureCubeMapNegativeY
| TextureCubeMapPositiveZ
| TextureCubeMapNegativeZ
deriving ( Eq, Ord, Show )