
Hi, I've just written some code which uses 'tessellate' from Graphics.Rendering.OpenGL.GLU.Tessellation and whilst it works exactly as expected on simple data sets, it gives a bus error on larger ones (not that large - e.g. 150 points). This might be a bug in my OS's glu implementation, but I'm also inclined to suspect a bug in all the peeks and pokes HOpenGL uses to handle the data for the callbacks. I don't actually use the callback data (I've set all the data to (0 :: Int) only because there is no storable instance for ()). Does anyone have a success story with this function? Has anyone used it successfully on larger polygons? Jules

Hello,
I can't reproduce this behaviour (though I didn't try very hard).
Could you send some specific code which produces bus error on your setup?
By the way, you make a Storable instance for () yourself:
instance Storable () where
alignment _ = 1
sizeOf _ = 0
poke _ _ = return ()
peek _ = return ()
Balazs
On Wed, Mar 11, 2009 at 7:15 PM, Jules Bean
Hi,
I've just written some code which uses 'tessellate' from Graphics.Rendering.OpenGL.GLU.Tessellation and whilst it works exactly as expected on simple data sets, it gives a bus error on larger ones (not that large - e.g. 150 points).
This might be a bug in my OS's glu implementation, but I'm also inclined to suspect a bug in all the peeks and pokes HOpenGL uses to handle the data for the callbacks. I don't actually use the callback data (I've set all the data to (0 :: Int) only because there is no storable instance for ()).
Does anyone have a success story with this function? Has anyone used it successfully on larger polygons?
Jules _______________________________________________ HOpenGL mailing list HOpenGL@haskell.org http://www.haskell.org/mailman/listinfo/hopengl

Balazs Komuves wrote:
Hello,
I can't reproduce this behaviour (though I didn't try very hard). Could you send some specific code which produces bus error on your setup?
Sure. Code attached below this message. After some playing around minimalising this example, I have come to a stronger conclusion: the code only crashes when the Combiner callback gets invoked. Since I have tolerance 0, that only happens if you have a duplicated vertex. If the vertex (200,200) appears twice (as in the simple example I attach) then you get the bus error, presumably when calling the Combiner. This makes me suspect that the nasty peeking and poking going on in the AnnotatedVertex Storable instance is not quite right, or something else is wrong in withCombineCallback or combineProperties (see http://hackage.haskell.org/packages/archive/OpenGL/2.2.1.1/doc/html/src/Grap... ) Code follows. I'd be interested to hear if it crashes for other people (could it be a bug in my OS's GLU?) Jules -- import Graphics.Rendering.OpenGL import Graphics.UI.GLUT import Control.Monad main = do (progName,args) <- getArgsAndInitialize initialDisplayMode $= [ DoubleBuffered, RGBAMode, WithDepthBuffer] createWindow progName windowSize $= (Size 640 480) blend $= Enabled blendFunc $= (SrcAlpha,OneMinusSrcAlpha) multisample $= Enabled --lineSmooth $= Enabled lineWidth $= 1 reshapeCallback $= Just reshape displayCallback $= display postRedisplay Nothing addTimerCallback 50 (idle) mainLoop idle = do postRedisplay Nothing addTimerCallback 50 (idle) display = do loadIdentity depthMask $= Enabled depthFunc $= Nothing -- Just Lequal clear [ColorBuffer,DepthBuffer] polygonMode $= (Line,Line) let pts = (figure8) -- let pts = (circle 27) pp <- tessRegion pts color $ Color4 1 1 0 (1::GLfloat) renderSimplePolygon pp swapBuffers -- n-point approximation to a circle (does not cause crash whatever n -- you use) circle n = map (\t -> (200 + 200 * sin (t*2*pi), 200 + 200 * cos (t*2*pi))) [0,1/n..1] -- causes crash, presumably because of the duplicated point (200,200) figure8 = [(200,0),(100,100),(200,200),(300,300),(200,400),(100,300),(200,200),(300,100)] -- does not crash, as it has no duplicated point figure8' = [(200,0),(100,100),(200,200),(300,300),(200,400),(100,300),(201,201),(300,100)] -- 2D projection reshape screenSize@(Size w h) = do viewport $= ((Position 0 0), screenSize) matrixMode $= Projection loadIdentity ortho2D 0 (fromIntegral w) 0 (fromIntegral h) matrixMode $= Modelview 0 -- this appears to give a bus error with sufficiently complex input tessRegion :: [(GLfloat,GLfloat)] -> IO (SimplePolygon Int) tessRegion pp = tessellate TessWindingOdd 0 (Normal3 0 0 0) (\vv (WeightedProperties (_,p) _ _ _) -> p) $ ComplexPolygon [ComplexContour (map (\(x,y) -> AnnotatedVertex (Vertex3 (realToFrac x) (realToFrac y) 0) (0::Int)) pp)] renderSimplePolygon (SimplePolygon pp) = mapM_ renderSimplePrimitive pp renderSimplePrimitive (Primitive pm vv) = renderPrimitive pm . forM_ vv $ \(AnnotatedVertex v _) -> vertex v

Hi, Indeed, your example code crashes here too, on both OS X 10.5 and Windows XP (though I would guess that the GLU code is platform-independent). Since I have tolerance 0, that only happens if you have a duplicated vertex.
If the vertex (200,200) appears twice (as in the simple example I attach) then you get the bus error, presumably when calling the Combiner.
This makes me suspect that the nasty peeking and poking going on in the AnnotatedVertex Storable instance is not quite right, or something else is wrong in withCombineCallback or combineProperties (see
I checked the Storable instance for AnnotatedVertex already, and while the code looks somewhat strange, it appears to behave correctly. I will try and look into what happens... Balazs

Hi, I found the cause of the crashes. A patch which should solve the problem (but changes the API, see below) is attached. The problem is that the GLU documentation and the GLU implementation is inconsistent. The GLU documentation claims that:
The "combine" or "combineData" callback is invoked to create a new vertex when the algorithm detects an intersection, or wishes to merge features. The vertex is defined as a linear combination of up to 4 existing vertices, referenced by data[0..3]. The coefficients of the linear combination are given by weight[0..3]; these weights always sum to 1.0. All vertex pointers are valid even when some of the weights are zero.
(emphasis on the last sentence); but the GLU implementation sets some of those pointers to 0: static void SpliceMergeVertices( GLUtesselator *tess, GLUhalfEdge *e1,
GLUhalfEdge *e2 ) /* * Two vertices with idential coordinates are combined into one. * e1->Org is kept, while e2->Org is discarded. */ { void *data[4] = { NULL, NULL, NULL, NULL }; GLfloat weights[4] = { 0.5, 0.5, 0.0, 0.0 };
data[0] = e1->Org->data; data[1] = e2->Org->data; CallCombine( tess, e1->Org, data, weights, FALSE ); if ( !__gl_meshSplice( e1, e2 ) ) longjmp(tess->env,1); }
(this is from the SGI GLU code, libtess/sweep.c). By the way, the the example combiner function in the documentation should crash, too. Since the vertex annotations are of arbitrary type, there is no default value we could supply when GLU gives us zero pointers; thus I changed the type WeightedProperties to data WeightedProperties v =
WeightedProperties (GLclampf, v) (GLclampf, v) (Maybe (GLclampf, v)) (Maybe (GLclampf, v))
Maybe some other solution, like WeightedProperties2 ... |
WeightedProperties4 ...
would be better...
Balazs
On Wed, Mar 11, 2009 at 7:15 PM, Jules Bean
Hi,
I've just written some code which uses 'tessellate' from Graphics.Rendering.OpenGL.GLU.Tessellation and whilst it works exactly as expected on simple data sets, it gives a bus error on larger ones (not that large - e.g. 150 points).
This might be a bug in my OS's glu implementation, but I'm also inclined to suspect a bug in all the peeks and pokes HOpenGL uses to handle the data for the callbacks. I don't actually use the callback data (I've set all the data to (0 :: Int) only because there is no storable instance for ()).
Does anyone have a success story with this function? Has anyone used it successfully on larger polygons?
Jules _______________________________________________ HOpenGL mailing list HOpenGL@haskell.org http://www.haskell.org/mailman/listinfo/hopengl

Balazs Komuves wrote:
I found the cause of the crashes. A patch which should solve the problem (but changes the API, see below) is attached.
[snip]
...but the GLU implementation sets some of those pointers to 0:
How stupid! Good catch.
Since the vertex annotations are of arbitrary type, there is no default value we could supply when GLU gives us zero pointers; thus I changed the type WeightedProperties to
data WeightedProperties v = WeightedProperties (GLclampf, v) (GLclampf, v) (Maybe (GLclampf, v)) (Maybe (GLclampf, v))
Maybe some other solution, like WeightedProperties2 ... | WeightedProperties4 ... would be better...
Maybe just [(GLclampf, v)] ? The docs could note that the list will in practice probably be of length 2 or 4, but most of the situations I can imagine you would treat it more uniformly as a list anyway. Jules

On Fri, Mar 13, 2009 at 8:28 AM, Jules Bean
Maybe some other solution, like WeightedProperties2 ... |
WeightedProperties4 ... would be better...
Maybe just [(GLclampf, v)] ? The docs could note that the list will in practice probably be of length 2 or 4, but most of the situations I can imagine you would treat it more uniformly as a list anyway.
Ah, I missed the obvious... The updated patch is in the attachment. Balazs

Am Freitag, 13. März 2009 00:39:49 schrieb Balazs Komuves:
I found the cause of the crashes. A patch which should solve the problem (but changes the API, see below) is attached. [...] Since the vertex annotations are of arbitrary type, there is no default value we could supply when GLU gives us zero pointers; [...]
Well spotted! The SGI tessellator is the de facto standard, so we should really handle this bug. Although a list of (weight, property) pairs might really be better, I am extremely reluctant to change the API, but it turns out that we don't have to: We *have* a default value, namely the first vertex passed to the combiner. This is never NULL and the weights for the NULL vertices are always zero, so we can happily use this. A corresponding patch has been committed. Cheers, S.
participants (3)
-
Balazs Komuves
-
Jules Bean
-
Sven Panne