I have a strange problem, which is so elementary that I think I must be missing something...

In GTK2HS, when I draw text using using textPath, the text is located at different locations depending on which backend is used. I'm not talking about a difference of a couple of pixels , but in my case it's half a page off. The PNG and Win32 backend work fine, but the PDF/PS backends get it wrong.

For example, I modified the Text.hs demo in the demos/Cairo subdirectory so it also outputs PDF. Here the text is also at different locations, so I guess it's not just my code. Code is pasted below.

I'm using Windows, and GTK2HS version 0.9.12 from http://www.haskell.org/gtk2hs

Maybe someone could give this a quick test on Linux?

I guess this is most likely a Cairo problem, and has nothing to do with the Haskell wrapper? Still this is hard to believe, since these kinds of bugs would be quickly found.

Thanks,
Peter

----------------------------------------

import Graphics.Rendering.Cairo
import qualified Graphics.Rendering.Cairo.Matrix as M

boxText :: String -> Double -> Double -> Render ()
boxText text x y = do
 save

 lineWidth <- getLineWidth

 (TextExtents xb yb w h _ _) <- textExtents text

 rectangle (x + xb - lineWidth)
           (y + yb - lineWidth)
           (w + 2 * lineWidth)
           (h + 2 * lineWidth)
 stroke
 moveTo x y
 textPath text
 fillPreserve
 setSourceRGBA 0 0 1 0.5
 setLineWidth 3.0
 stroke

 restore

transpSurface :: Double -> Double -> Render ()
transpSurface w h = do
 save
 rectangle 0 0 w h
 setSourceRGBA 0 0 0 0
 setOperator OperatorSource
 fill
 restore

width = 400
height = 300

main :: IO ()
main = withImageSurface FormatARGB32 width height $ \surface -> do

 let render = do
       setSourceRGB 0.0 0.0 0.0
       setLineWidth 2.0

       transpSurface (fromIntegral width) (fromIntegral height)

       selectFontFace "sans" FontSlantNormal FontWeightNormal
       setFontSize 40
extents <- fontExtents
       let fontHeight = fontExtentsHeight extents

       boxText "Howdy, world!" 10 fontHeight

       translate 0 fontHeight

       save
       translate 10 fontHeight
       rotate (10.0 * pi / 180.0)
       boxText "Yay for Haskell!" 0 0
       restore

       translate 0 (3 * fontHeight)

       save
setFontMatrix $ M.rotate ((-10.0) * pi / 180.0) $ M.scale 40.0 40.0 M.identity
       boxText "...and Cairo!" 10 fontHeight
       restore
renderWith surface render

 surfaceWriteToPNG surface "Text.png"

withPDFSurface "Text.pdf" (realToFrac width) (realToFrac height) (flip renderWith $ render >> showPage)

 return ()




_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to