[diagrams] Ellipse bounds problem

Walck, Scott walck at lvc.edu
Tue May 25 06:39:07 EDT 2010


Diagramers,

Here's an example of "beside" that results in intersection.  I don't know whether it's the Ellipse code that has a problem or the bounds calculation.

Also, when I uncomment d3 or d5, I get a type error that I don't understand.

If anyone makes progress on these issues, please let me know.

Cheers,

Scott



{-# LANGUAGE PackageImports #-}

import "diagrams-core" Graphics.Rendering.Diagrams
import Graphics.Rendering.Diagrams.Transform

import Diagrams.TwoD

import Diagrams.Backend.Cairo
import Diagrams.Combinators

d :: Diagram Cairo
d = translate (30,30) $ scale 10 (beside (2,1) box box `atop` circle)

d' :: Diagram Cairo
d' = translate (30,30) $ scale 10 (beside (2,1) box box `atop` ell1)

ell1 = rotate (-pi/6) $ horizontalScale 2 $ verticalScale 0.5 circle

d2 = translate (30,30) $ scale 10 (beside (2,1) box ell1)  -- intersects
--d3 = translate (30,30) $ scale 10 (beside (2,1) box circle)  -- worked, but now gives a type error
--d4 = translate (30,30) $ scale 10 (beside (50,50) box circle)  -- gives a type error
--d5 = translate (30,30) $ scale 10 (beside (2,2) box circle)  -- worked, but now gives a type error

e :: Diagram Cairo
e = translate (50,70) $ rotate (pi/6) $ horizontalScale 30 $ verticalScale 10 circle

ell = rotate (pi/6) $ horizontalScale 30 $ verticalScale 10 circle
box10 = scale 10 box

f :: Diagram Cairo
f = translate (50,70) $ beside (1,0) box10 ell

main = renderDia Cairo [] d2




More information about the diagrams mailing list