[HOpenGL] GL utilities, toolkits, and questions..

C.Reinke C.Reinke@ukc.ac.uk
Mon, 22 Jul 2002 20:41:38 +0100


> Well, I guess the size itself is not a bug, but a feature of GLUT. But
> there is an inconsistency: The spec for glutStrokeCharacter
> 
>     http://www.opengl.org/developers/documentation/glut/spec3/node78.html
> 
> talks about "units" (of magnitude 100, as you've already noticed),
> while the spec for glutStrokeWidth
> 
>     http://www.opengl.org/developers/documentation/glut/spec3/node79.html
> 
> talks about "pixels". The latter is probably a cut-n-paste bug from
> the spec for glutBitmapWidth.

Just as I suspected. And here's what the glutStrokeWidth and
glutStrokeLength man pages in the GLUT sources say:

  int glutStrokeWidth(void *font, int character);
  int glutStrokeLength(void *font, const unsigned char *string);

  glutStrokeWidth returns the width in modeling units of a stroke
  character in a supported stroke font

  glutStrokeLength returns the length in modeling units of a string
  (8-bit characters).  This length is equivalent to summing all the
  widths returned by glutStrokeWidth for each character in the string.

So the "int" return type (instead of GLdouble, as I expected) seems
possible because of that "units" talk, and the "pixel" talk doesn't
seem to belong there in the spec. Sigh, one just needs to know how
to read the spec (and the source)..

Okay, that gives me another chance to try silly things (centered or
right-justified text blocks, in this case;-). Looking forward to
"real" font add-ons to HOpenGL, of course, if Vincenzo gets round 
to it.


Btw, while we are sharing tricks and plans - using feedback to
output vectorized snapshots wasn't as difficult as I thought (as
usual, the redbook_HS examples, here "Feedback.hs", were helpful). 
A dummy fragment for exporting SVG (http://www.w3.org/TR/SVG/) from
HOpenGL is appended (just dealing with lines and polygons, just
output the polygons as they come -> possibly incorrect output), 
and the more complete original for exporting EPS from OpenGL 
(output polygons in back-to-front order and emulate flat shading)
can be found at:

  Mark Kilgard
  Achieving Quality PostScript output for OpenGL
  http://www.opengl.org/developers/code/mjktips/Feedback.html

Unfortunately, the resulting vector graphics can be quite large,
certainly larger that a JPEG snapshot:-(. They are scalable, which
is nice, and with a bit of hacking, one could put several of them
into an SVG file, and animate through the snapshots, but then the
size problem becomes a real headache. Haven't tried compression yet,
nor hidden polygon removal, but I'm currently not inclined to fill
in the missing bits in the code, simply because I'm not using it -
it was worth a try, though..

Cheers,
Claus


----------------------------------- a little HOpenGL to SVG hack

import Numeric(showGFloat)

..

-- extract x and y coordinates from feedback info, ignore rest
svgXYproject (ThreeDColor (Vertex3 x y z) (Prelude.Right (Color4 r g b a))) =
  (showGFloat (Just 2) x . showString "," . 
   showGFloat (Just 2) (-y) . showString " ") ""

-- extract rgb values from feedback info, ignore rest
svgRGBproject (ThreeDColor (Vertex3 x y z) (Prelude.Right (Color4 r g b a))) =
  (showGFloat Nothing (r*100) . showString "%," . 
   showGFloat Nothing (g*100) . showString "%, " .
   showGFloat Nothing (b*100) . showString "%") ""

-- incomplete, as usual..
-- svg (PassThroughToken (PassThroughValue n)) =
-- svg (PointToken i) = 
svg (LineToken i j) =
  "<polyline stroke=\"rgb("++svgRGBproject i++")\" "
  ++"points=\""++(concatMap svgXYproject [i,j])++"\"/>"
-- what's this?
svg (LineResetToken i j) =
  "<polyline stroke=\"rgb("++svgRGBproject i++")\" "
  ++"points=\""++(concatMap svgXYproject [i,j])++"\"/>"
-- colour the polygon by its first vertex..
svg (PolygonToken is) =
  "<polygon fill=\"rgb("++svgRGBproject (head is)++")\" "
  ++"points=\""++(concatMap svgXYproject is)++"\"/>"
svg _ =
  error "Author is too lazy for a complete svg FeedbackToken"

-- Write contents of entire buffer.
printBuffer :: GLint -> FeedbackBuffer -> IO ()
printBuffer size buffer = do
   Just tokens <- getFeedbackTokens size buffer
   (WindowPosition x y, WindowSize w h) <- get VarViewport

   putStrLn "<?xml version=\"1.0\" standalone=\"no\"?>"
   putStrLn "<!DOCTYPE svg PUBLIC \"-//W3C//DTD SVG 20010904//EN\"" 
   putStrLn " \"http://www.w3.org/TR/2001/REC-SVG-20010904/DTD/svg10.dtd\">"
   putStrLn $ "<svg width=\""++show ((fromIntegral w)/50)++"cm\" "
                 ++"height=\""++show ((fromIntegral h)/50)++"cm\" "
                 ++"viewBox=\"0 0 "++show w++" "++show h++"\""
   putStrLn " xmlns=\"http://www.w3.org/2000/svg\""
   putStrLn " xmlns:xlink=\"http://www.w3.org/1999/xlink\">"
   putStrLn $ "<g transform=\"translate(0,"++show h++")\">"

   mapM_ (putStrLn . svg) tokens

   putStrLn "</g>"
   putStrLn "</svg>"


-- main function, call this in your display callback instead of
-- the direct rendering part (here assumed to be executing a 
-- display list) when you want to output a single scene as SVG.
-- feedback buffer overflow tends to be the main error source,
-- but I've got no idea how to estimate the size correctly..
printDisplay ::  DisplayList -> DisplayAction
printDisplay dl = do
   feedBuffer <- makeFeedbackBuffer 1048576 ThreeDColor'
   feedbackBuffer feedBuffer
   renderMode Feedback

   callList dl

   size <- renderMode Render
   printBuffer size feedBuffer
   freeFeedbackBuffer feedBuffer