
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 )

On Sun, Jun 12, 2011 at 8:17 AM, L Corbijn
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.
Looks like no one has responded to your message yet. Thank you for pointing this out. It does indeed sound like a problem with the current implementation. I'll have to think about this a bit more. Do I understand you correctly that you would like there to be a more general interface for marshaling data in the OpenGL binding? Thanks! Jason

On Wed, Jun 15, 2011 at 4:54 PM, Jason Dagit
On Sun, Jun 12, 2011 at 8:17 AM, L Corbijn
wrote: 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.
Looks like no one has responded to your message yet.
Thank you for pointing this out. It does indeed sound like a problem with the current implementation.
I'll have to think about this a bit more. Do I understand you correctly that you would like there to be a more general interface for marshaling data in the OpenGL binding?
Thanks! Jason
Indeed I would like to have a bit more done on marshalling (especially after typing names like marshalGetFramebufferAttachmentPName). So I've been tinkering for some time about how to implementing it. Adding some marshaling functions would probably lead to adding class GLMarshal m where marshal :: m -> GLenum with for example the utility functions marshal1 :: GLMarshal m => (GLenum -> e) -> m -> e marshal2 :: GLMarshal m => (a -> GLenum -> e) -> a -> m -> e and of course we want to unmarshal some datatypes class GLMarshal m => GLUnmarshal m where unmarshal :: GLenum -> m Now having these two typeclasses might make life a bit earsier, but is also caused me to think about using type classes at some other points in HOpenGL. Though that last type class makes it all more difficult than expected. First of the ideas is to change some datatype, e.g. GetPName, into a type class, and refactor the constructors into (more) appropriate datatypes. You could group them for extra functionality or neater datatypes, some possibilities are 1 by target (Lighting, Shaders, etc.). 2 by return type (int1, int4, uint1, etc.), and then redefine GetInteger1 and others to only work on the correct enums. 3 by version of deprecation, this makes it easier to exclude unwanted constructors. 4 by source (GL-spec, or extension)... Though such splitting might be an improvement it has it's hard to do with datatypes that need unmarshaling. For those types there is the problem that the compiler can't chose from all the unmarshaling functions the one that can unmarhsal the returned value, without some help. Selecting an unmarshal function for the compiler (by explicitly specifying the type) is not wanted in some cases, so it should be done at runtime which comes possibly with some performance loss. Luckily unmarshalling is done far less than marshalling. Now the more radical/crazy ideas. Using option 4 on more datatypes could make making extensions to the OpenGL base package a whole lot easier. The setup would be like: class GLMarshal b => BufferTarget b where ... with default implementation data SpecBufferTarget = ArrayBuffer | ... instance BufferTarget SpecBufferTarget where ... and for adding the extension for uniformbuffer objects (of course with a lot of extra functions) data UniformExtBufferTarget = UniformBuffer instance BufferTarget UniformExtBufferTargett where ... It would reduce the work for adding an extension from editing the OpenGL package to making an extra module in which extra functions and datatypes (instances of the correct typeclass) are added. Though I think it's nice to make it possible to add extensions, there are serious problems with it. Most importantly there is the problem with unmarshalling again, as the function that does the unmarshaling must have the possibility to unmarshal datatypes from which it does not even know existence at compile time. The only sollution to this problem I've come up with is to register the extra marshal functions at some point (preferably start up). This would introduce not only a way to register these extensions, but also either an IO type or an unsafePerformIO to unmarshal function. Third and last idea, extend the GLMarshal to class GLMarshal s t | s -> t where marshal :: s -> t or class GLMarshal s where type Target s :: * marshal :: s -> Target s Then it would be possible to implement marshaling functions for buffer objects (and possibly more types) and therefore make utility functions more general. The disadvantage to this idea (or ideas like this) is that it needs some language extensions to work. Lars
participants (2)
-
Jason Dagit
-
L Corbijn