-- | This is Hieroglyph, a 2D scenegraph library similar in functionality to a barebones -- stripped down version of Processing, but written in a purely functional manner. -- -- See individual implementations (like the Graphics.Rendering.Hieroglyph.Cairo module) -- for more information on how to use this library. -- -- [@Author@] Jeff Heard -- -- [@Copyright@] © 2008 Renaissance Computing Institute -- -- [@License@] A LICENSE file should be included as part of this distribution -- -- [@Version@] 0.5 -- module Graphics.Rendering.Hieroglyph.Primitives where import qualified Graphics.Rendering.Cairo as Cairo -- | A 2D point data Point = Point Double Double deriving (Show, Read, Eq) data Rect = Rect Double Double Double Double deriving (Show, Read, Eq) -- | A 2D primitive in an arbitrary Cartesian 2d space data Primitive = -- | An arc Arc -- A possibly filled pie slice or arc { center :: Point -- ^ center of the arc , radius :: Double -- ^ radius of the arc , angle1 :: Double -- ^ begin angle , angle2 :: Double -- ^ end angle , negative :: Bool -- ^ whether or not to consider this a slice of or a slice out of the pie , filled :: Bool -- ^ pie, or just crust? , outlined :: Bool -- ^ crustless pie? , clipped :: Bool -- ^ add this to the clipping plane } -- | A cubic spline | Curve -- An arbitrary cubic spline { begin :: Point -- ^ starting point , curve_segments :: [(Point,Point,Point)] -- ^ A sequential list of curve segments. Note that the first two points are control points. , closed :: Bool -- ^ Whether or not to close this curve with a final line , filled :: Bool -- ^ Whether or not to fill the curve , outlined :: Bool -- ^ Whether or not to outline the curve , clipped :: Bool -- ^ Add the curve to the clipping plane } -- | A series of straight lines | Line -- An arbitrary series of line segments { begin :: Point -- ^ Starting Point , segments :: [Point] -- ^ Line segments. , closed :: Bool -- ^ Whether or not to finish this curve with a last line from the end segment to the begin point. , filled :: Bool -- ^ Whether or not to fill the curve , outlined :: Bool -- ^ Whether or not to draw the outline , clipped :: Bool -- ^ Add to the clipping plane } -- | Move the pen | Pen { moveto :: Point -- ^ Move the current point. Matters for arcs sometimes. May remove the begin point for Curve and Line in favor of this. } -- | A rectangle | Rectangle -- An possibly filled rectangle { topleft :: Point -- ^ The top left point , width :: Double -- ^ The width , height :: Double -- ^ The height , filled :: Bool -- ^ Fill the rectangle? , outlined :: Bool -- ^ Draw the outline? , clipped :: Bool -- ^ Add to the clipping plane? } -- | A simple text object | Text -- A simple text string { str :: String -- ^ The string to print , bottomleft :: Point -- ^ The anchor point for the text. Baseline, not bottom. , filled :: Bool -- ^ Fill the text? Usually you want this and not outline. , outlined :: Bool -- ^ Draw the outline? , clipped :: Bool -- ^ Add to the clipping plane? } -- | A compound object | Compound -- Use this to create an arbitrary shape before calling fill, stroke, and clip. { primitives :: [Primitive] -- ^ primitives to use , filled :: Bool -- ^ fill the result? , outlined :: Bool -- ^ outline the result? , clipped :: Bool -- ^ clip the result? } | Image { filename :: String , dimensions :: Either Point Rect , preserveaspect :: Bool } | Hidden deriving (Show,Read,Eq) -- | the origin point origin :: Point origin = Point 0 0 arc :: Primitive -- ^ A unit circle by default, modifiable with record syntax. arc = Arc origin 1 0 (2*pi) False False True False arcFilled :: Primitive -- ^ A filled unit circle by default, modifiable with record syntax. arcFilled = Arc origin 1 0 (2*pi) False True False False curve :: Primitive -- ^ A cubic spline with a starting point of the origin. curve = Curve origin [] False False True False curveFilled :: Primitive -- ^ A filled loop with a starting point at the origin. curveFilled = Curve origin [] True True False False line :: Primitive -- ^ A line starting at the origin. line = Line origin [] False False True False polygon :: Primitive -- ^ An arbitrary filled polygon starting at the origin. polygon = Line origin [] True True False False pen :: Primitive -- ^ move the pen to the origin pen = Pen origin rectangle :: Primitive -- ^ an outlined rectangle rectangle = Rectangle (Point 0 1) 1 1 False True False rectangleFilled :: Primitive -- ^ A filled, but not outlined rectanglee rectangleFilled = Rectangle (Point 0 1) 1 1 True False False text :: Primitive -- ^ A rendered string starting at the origin. text = Text [] origin True False False compound :: Primitive -- ^ An outlined compound object compound = Compound [] True False False degrees :: Double -> Double -- ^ Convert degrees to radians degrees x = x * 0.0174532925 hidden :: Primitive -- ^ A hidden object. hidden = Hidden image :: Primitive -- ^ An image. These are efficiently cached using weak references where possible image = Image "" (Left origin) False