
[I'd be surprised if no-one else has encountered this yet, but I
haven't seen it reported in the list archives.]
The value which GLUT passes as the first argument to the mouse
callback isn't restricted to 0, 1 and 2, corresponding to the manifest
constants GLUT_{LEFT,MIDDLE,RIGHT}_BUTTON respectively.
On a system with a wheel mouse, the mouse callback may also be passed
the values 3 or 4; this causes the program to terminate with e.g.
Fail: unmarshall_MouseButton: unknown value (3)
AFAICT, this can't be trapped.
--
Glynn Clements

Glynn Clements wrote:
[I'd be surprised if no-one else has encountered this yet, ...]
Well, almost...: :-) http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/libraries/GLUT/Graphics/UI/GLUT/Callbacks/Window.hs.diff?r1=1.5&r2=1.6 The new GLUT binding (including extensive documentation) will be included in the next HOpenGL release, which I *really* hope to get out of the door soon. Apart from that, the GLU API will be much nicer, e.g. tessellation basically looks like "polygon in, triangles/contours/primitives out", without any need for silly callbacks. While I'm at it: I really like to hear opinions and improvements of the API, e.g. the vertex specification stuff like class Vertex a where vertex :: a -> IO () data Vertex2 a = Vertex2 a a instance Vertex (Vertex2 GLshort) where -- complex instance head!!! vertex (Vertex2 x y) = vertex2s x y %fun glVertex2s :: GLshort -> GLshort -> IO () is not Haskell98. How can we do better, i.e. unify 1D/2D/3D/4D vertices with differing component types in pure Haskell98? Cheers, S.

On Wed, 08 Jan 2003 09:00:56 +0100
Sven Panne
How can we do better, i.e. unify 1D/2D/3D/4D vertices with differing component types in pure Haskell98?
Are we sure we want it? Depending on the motivation, it might help to define just "Vector4", or to use vertexes as fixed arrays. V.

--Last weeks I've played with ObjectIO-GUIs (until I realised the
one-button-mouse implementation and that it still runs only on Win). They
are very fascinating designed.
--Inspired by them...
--To unify 1D/2D/3D/4D vectors/vertices, I would try to implement the
following:
--(I did not test it - I hope this is Haskell98 and "%precompiler" conform.)
class VectorClass v where
dotVec :: (VectorTyp a) => v a -> v a -> a
class VectorTyp va where
addVec :: va -> va -> va
subVec :: va -> va -> va
negVec :: va -> va
data Vector b a = (VectorContainer b) => Vector (b a)
instance VectorClass (Vector b) where
dotVec :: (VectorTyp a) => Vector b a -> Vector b a -> a
dotVec (Vector ba1) (Vector ba2) = dotVecCont ba1 ba2
instance VectorTyp (Vector b a) where
addVec :: Vector b a -> Vector b a -> Vector b a
addVec (Vector ba1) (Vector ba2) = addVecCont ba1 ba2
....
instance (Num v) => VectorTyp v where
addVec = (+)
...
class VectorContainer b where
addVecCont :: (VectorTyp a) => b a -> b a -> b a
subVecCont :: (VectorTyp a) => b a -> b a -> b a
negVecCont :: (VectorTyp a) => b a -> b a
dotVecCont :: (VectorTyp a) => b a -> b a -> a
infixr 8 `VSep`, `VEnd`
-- (Vector $ x `VSep` y `VSep` z `VEnd`)
data VectorContainerPart b a = (VectorContainer b,VectorTyp a) => VSep a (b
a)
data VectorContainerEnd a = (VectorTyp a) => VEnd a
instance VectorContainer VectorContainerEnd where
addVecCont :: (VectorTyp a) => VectorContainerEnd a ->
VectorContainerEnd a -> VectorContainerEnd a
addVecCont (a1 `VEnd`) (a2 `VEnd`) = (a1 `addVec` a2) `VEnd`
...
instance (VectorContainer b) => VectorContainer (VectorContainerPart b)
where
addVecCont :: (VectorTyp a) => VectorContainerPart b a ->
VectorContainerPart b a -> VectorContainerPart b a
addVecCont (a1 `VSep` ba1) (a2 `VSep` ba2) = (a1 àddVec` a2) `VSep` (ba1
`addVecCont` ba2)
...
type Vector1 a = Vector (VectorContainerEnd a) a
type Vector2 a = Vector (VectorContainerPart (VectorContainerEnd a) a) a
type Vector3 a = Vector (VectorContainerPart (VectorContainerPart
(VectorContainerEnd a) a) a) a
type Vector4 a = Vector (VectorContainerPart (VectorContainerPart
(VectorContainerPart (VectorContainerEnd a) a) a) a) a
class GLVector v where
glVector :: v -> IO ()
%fun glVector1s :: GLshort -> IO ()
%fun glVector2s :: GLshort -> GLshort -> IO ()
%fun glVector3s :: GLshort -> GLshort -> GLshort -> IO ()
%fun glVector4s :: GLshort -> GLshort -> GLshort -> GLshort -> IO ()
instance GLVector (Vector1 GLShort) where
glVector (Vector (x `VEnd`)) = glVector1s x
instance GLVector (Vector2 GLShort) where
glVector (Vector (x `VSep` y `VEnd`)) = glVector2s x y
instance GLVector (Vector3 GLShort) where
glVector (Vector (x `VSep` y `VSep` z `VEnd`)) = glVector3s x y z
instance GLVector (Vector4 GLShort) where
glVector (Vector (x `VSep` y `VSep` z `VSep` w `VEnd`)) = glVector4s x y
z w
vector1 :: (VectorTyp a) => a -> (Vector1 a)
vector2 :: (VectorTyp a) => a -> a -> (Vector2 a)
vector3 :: (VectorTyp a) => a -> a -> a -> (Vector3 a)
vector4 :: (VectorTyp a) => a -> a -> a -> a -> (Vector4 a)
vector1 x = (Vector $ x `VEnd`)
vector2 x y = (Vector $ x `VSep` y `VEnd`)
vector3 x y z = (Vector $ x `VSep` y `VSep` z `VEnd`)
vector4 x y z w = (Vector $ x `VSep` y `VSep` z `VSep` w `VEnd`)
glVector1 :: GLShort -> IO ()
glVector2 :: GLShort -> GLShort -> IO ()
glVector3 :: GLShort -> GLShort -> GLShort -> IO ()
glVector4 :: GLShort -> GLShort -> GLShort -> GLShort -> IO ()
glVector1 x = (glVector . vector1)
glVector2 x = (glVector . vector2)
glVector3 x = (glVector . vector3)
glVector4 x = (glVector . vector4)
-- examples:
-- glVector (vector3 x y z)
-- glVector3 x y z
----- Original Message -----
From: "Sven Panne"
While I'm at it: I really like to hear opinions and improvements of the API, e.g. the vertex specification stuff like
class Vertex a where vertex :: a -> IO ()
data Vertex2 a = Vertex2 a a
instance Vertex (Vertex2 GLshort) where -- complex instance head!!! vertex (Vertex2 x y) = vertex2s x y
%fun glVertex2s :: GLshort -> GLshort -> IO ()
is not Haskell98. How can we do better, i.e. unify 1D/2D/3D/4D vertices with differing component types in pure Haskell98?

--Last weeks I've played with ObjectIO-GUIs (until I realised the one-button-mouse implementation and that it still runs only on
Win). They are very fascinating designed.
--Inspired by them...
--To unify 1D/2D/3D/4D vectors/vertices, I would try to implement the following:
--(I did not test it - I hope this is Haskell98 and "%precompiler" conform.)
class VectorClass v where
dotVec :: (VectorTyp a) => v a -> v a -> a
class VectorTyp va where
addVec :: va -> va -> va
subVec :: va -> va -> va
negVec :: va -> va
data Vector b a = (VectorContainer b) => Vector (b a)
instance VectorClass (Vector b) where
dotVec :: (VectorTyp a) => Vector b a -> Vector b a -> a
dotVec (Vector ba1) (Vector ba2) = dotVecCont ba1 ba2
instance VectorTyp (Vector b a) where
addVec :: Vector b a -> Vector b a -> Vector b a
addVec (Vector ba1) (Vector ba2) = addVecCont ba1 ba2
....
instance (Num v) => VectorTyp v where
addVec = (+)
...
class VectorContainer b where
addVecCont :: (VectorTyp a) => b a -> b a -> b a
subVecCont :: (VectorTyp a) => b a -> b a -> b a
negVecCont :: (VectorTyp a) => b a -> b a
dotVecCont :: (VectorTyp a) => b a -> b a -> a
infixr 8 `VSep`, `VEnd`
-- (Vector $ x `VSep` y `VSep` z `VEnd`)
data VectorContainerPart b a = (VectorContainer b,VectorTyp a) => VSep a (b a)
data VectorContainerEnd a = (VectorTyp a) => VEnd a
instance VectorContainer VectorContainerEnd where
addVecCont :: (VectorTyp a) => VectorContainerEnd a -> VectorContainerEnd a -> VectorContainerEnd a
addVecCont (a1 `VEnd`) (a2 `VEnd`) = (a1 `addVec` a2) `VEnd`
...
instance (VectorContainer b) => VectorContainer (VectorContainerPart b) where
addVecCont :: (VectorTyp a) => VectorContainerPart b a -> VectorContainerPart b a -> VectorContainerPart b a
addVecCont (a1 `VSep` ba1) (a2 `VSep` ba2) = (a1 àddVec` a2) `VSep` (ba1 `addVecCont` ba2)
...
type Vector1 a = Vector (VectorContainerEnd a) a
type Vector2 a = Vector (VectorContainerPart (VectorContainerEnd a) a) a
type Vector3 a = Vector (VectorContainerPart (VectorContainerPart (VectorContainerEnd a) a) a) a
type Vector4 a = Vector (VectorContainerPart (VectorContainerPart (VectorContainerPart (VectorContainerEnd a) a) a) a) a
class GLVertex v where
glVertex :: v -> IO ()
%fun glVertex1s :: GLshort -> IO ()
%fun glVertex2s :: GLshort -> GLshort -> IO ()
%fun glVertex3s :: GLshort -> GLshort -> GLshort -> IO ()
%fun glVertex4s :: GLshort -> GLshort -> GLshort -> GLshort -> IO ()
instance GLVertex (Vector1 GLShort) where
glVertex (Vector (x `VEnd`)) = glVertex1s x
instance GLVertex (Vector2 GLShort) where
glVertex (Vector (x `VSep` y `VEnd`)) = glVertex2s x y
instance GLVertex (Vector3 GLShort) where
glVertex (Vector (x `VSep` y `VSep` z `VEnd`)) = glVertex3s x y z
instance GLVertex (Vector4 GLShort) where
glVertex (Vector (x `VSep` y `VSep` z `VSep` w `VEnd`)) = glVertex4s x y z w
vector1 :: (VectorTyp a) => a -> (Vector1 a)
vector2 :: (VectorTyp a) => a -> a -> (Vector2 a)
vector3 :: (VectorTyp a) => a -> a -> a -> (Vector3 a)
vector4 :: (VectorTyp a) => a -> a -> a -> a -> (Vector4 a)
vector1 x = (Vector $ x `VEnd`)
vector2 x y = (Vector $ x `VSep` y `VEnd`)
vector3 x y z = (Vector $ x `VSep` y `VSep` z `VEnd`)
vector4 x y z w = (Vector $ x `VSep` y `VSep` z `VSep` w `VEnd`)
glVertex1 :: GLShort -> IO ()
glVertex2 :: GLShort -> GLShort -> IO ()
glVertex3 :: GLShort -> GLShort -> GLShort -> IO ()
glVertex4 :: GLShort -> GLShort -> GLShort -> GLShort -> IO ()
glVertex1 x = glVertex $ vector1 x
glVertex2 x y = glVertex $ vector2 x y
glVertex3 x y z = glVertex $ vector3 x y z
glVertex4 x y z w = glVertex $ vector4 x y z w
-- examples:
-- glVertex (vector3 x y z)
-- glVertex3 x y z
----- Original Message -----
From: "Sven Panne"
While I'm at it: I really like to hear opinions and improvements of the API, e.g. the vertex specification stuff like
class Vertex a where vertex :: a -> IO ()
data Vertex2 a = Vertex2 a a
instance Vertex (Vertex2 GLshort) where -- complex instance head!!! vertex (Vertex2 x y) = vertex2s x y
%fun glVertex2s :: GLshort -> GLshort -> IO ()
is not Haskell98. How can we do better, i.e. unify 1D/2D/3D/4D vertices with differing component types in pure Haskell98?

Hey, Marc. *confused* Why did I/you do that ?!? :
%fun glVertex1s :: GLshort -> IO () %fun glVertex2s :: GLshort -> GLshort -> IO () %fun glVertex3s :: GLshort -> GLshort -> GLshort -> IO () %fun glVertex4s :: GLshort -> GLshort -> GLshort -> GLshort -> IO () ... glVertex1 :: GLShort -> IO () glVertex2 :: GLShort -> GLShort -> IO () glVertex3 :: GLShort -> GLShort -> GLShort -> IO () glVertex4 :: GLShort -> GLShort -> GLShort -> GLShort -> IO ()
glVertex1 x = glVertex $ vector1 x glVertex2 x y = glVertex $ vector2 x y glVertex3 x y z = glVertex $ vector3 x y z glVertex4 x y z w = glVertex $ vector4 x y z w
- Marc

Sven Panne wrote:
While I'm at it: I really like to hear opinions and improvements of the API
Some of the data types should be a little less abstract. E.g. TextureName should implement Eq, types which consist solely of nullary constructurs should implement Enum (and maybe Bounded, Ix); implementing Show is useful for debugging. Functions which operate upon arrays (e.g. texImage?D, build?DMipmaps, scaleImage etc) shouldn't require the user to perform the [un]marshalling.
API, e.g. the vertex specification stuff like
I find the current interface to be, in general, an improvement over
C's myriad type-specific variants.
It might be useful to have classes to unify the different types of
"vector" (Vector*, Vertex*, Normal*; maybe TexCoord* and Color*) of a
given dimension; this would allow utility functions (e.g. dot-product)
to work on any of them.
--
Glynn Clements
participants (4)
-
Glynn Clements
-
Marc Ziegert
-
Nick Name
-
Sven Panne