Copyright | (c) 2006-2016 alpheccar.org |
---|---|
License | BSD-style |
Maintainer | misc@NOSPAMalpheccar.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
PDF Shapes
Synopsis
- moveto :: Point -> Draw ()
- lineto :: Point -> Draw ()
- arcto :: Angle -> Point -> Draw ()
- curveto :: Point -> Point -> Point -> Draw ()
- beginPath :: Point -> Draw ()
- closePath :: Draw ()
- addBezierCubic :: Point -> Point -> Point -> Draw ()
- addPolygonToPath :: [Point] -> Draw ()
- addLineToPath :: Point -> Draw ()
- strokePath :: Draw ()
- fillPath :: Draw ()
- fillAndStrokePath :: Draw ()
- fillPathEO :: Draw ()
- fillAndStrokePathEO :: Draw ()
- setAsClipPath :: Draw ()
- setAsClipPathEO :: Draw ()
- class Shape a where
- data Line = Line PDFFloat PDFFloat PDFFloat PDFFloat
- data Rectangle = Rectangle !Point !Point
- newtype Polygon = Polygon [Point]
- data Arc = Arc PDFFloat PDFFloat PDFFloat PDFFloat
- data Ellipse = Ellipse PDFFloat PDFFloat PDFFloat PDFFloat
- data Circle = Circle PDFFloat PDFFloat PDFFloat
- data RoundRectangle = RoundRectangle PDFFloat PDFFloat PDFFloat PDFFloat PDFFloat PDFFloat
- data CapStyle
- data JoinStyle
- data DashPattern = DashPattern ![PDFFloat] PDFFloat
- setWidth :: MonadPath m => PDFFloat -> m ()
- setLineCap :: MonadPath m => CapStyle -> m ()
- setLineJoin :: MonadPath m => JoinStyle -> m ()
- setDash :: MonadPath m => DashPattern -> m ()
- setNoDash :: MonadPath m => m ()
- setMiterLimit :: MonadPath m => PDFFloat -> m ()
Shapes
Paths
Approximate a circular arc by one cubic bezier curve. larger arc angles mean larger distortions
addBezierCubic :: Point -> Point -> Point -> Draw () Source #
Append a cubic Bezier curve to the current path. The curve extends from the current point to the point (x3 , y3), using (x1 , y1 ) and (x2, y2) as the Bezier control points
addPolygonToPath :: [Point] -> Draw () Source #
Add a polygon to current path
addLineToPath :: Point -> Draw () Source #
strokePath :: Draw () Source #
Draw current path
fillAndStrokePath :: Draw () Source #
Fill current path
fillPathEO :: Draw () Source #
Fill current path using even odd rule
fillAndStrokePathEO :: Draw () Source #
Fill current path using even odd rule
setAsClipPath :: Draw () Source #
Set clipping path
setAsClipPathEO :: Draw () Source #
Set clipping path
Usual shapes
addShape :: a -> Draw () Source #
stroke :: a -> Draw () Source #
fillAndStroke :: a -> Draw () Source #
fillEO :: a -> Draw () Source #
fillAndStrokeEO :: a -> Draw () Source #
Instances
Shape Arc Source # | |
Shape Circle Source # | |
Shape Ellipse Source # | |
Shape Line Source # | |
Shape Polygon Source # | |
Shape Rectangle Source # | |
Shape RoundRectangle Source # | |
Defined in Graphics.PDF.Shapes addShape :: RoundRectangle -> Draw () Source # stroke :: RoundRectangle -> Draw () Source # fill :: RoundRectangle -> Draw () Source # fillAndStroke :: RoundRectangle -> Draw () Source # fillEO :: RoundRectangle -> Draw () Source # fillAndStrokeEO :: RoundRectangle -> Draw () Source # |
Instances
data RoundRectangle Source #
Instances
Shape RoundRectangle Source # | |
Defined in Graphics.PDF.Shapes addShape :: RoundRectangle -> Draw () Source # stroke :: RoundRectangle -> Draw () Source # fill :: RoundRectangle -> Draw () Source # fillAndStroke :: RoundRectangle -> Draw () Source # fillEO :: RoundRectangle -> Draw () Source # fillAndStrokeEO :: RoundRectangle -> Draw () Source # | |
Eq RoundRectangle Source # | |
Defined in Graphics.PDF.Shapes (==) :: RoundRectangle -> RoundRectangle -> Bool # (/=) :: RoundRectangle -> RoundRectangle -> Bool # |
Style
Line cap styles
Instances
Enum CapStyle Source # | |
Eq CapStyle Source # | |
Line join styles
Instances
Enum JoinStyle Source # | |
Defined in Graphics.PDF.Shapes succ :: JoinStyle -> JoinStyle # pred :: JoinStyle -> JoinStyle # fromEnum :: JoinStyle -> Int # enumFrom :: JoinStyle -> [JoinStyle] # enumFromThen :: JoinStyle -> JoinStyle -> [JoinStyle] # enumFromTo :: JoinStyle -> JoinStyle -> [JoinStyle] # enumFromThenTo :: JoinStyle -> JoinStyle -> JoinStyle -> [JoinStyle] # | |
Eq JoinStyle Source # | |
data DashPattern Source #
Instances
Eq DashPattern Source # | |
Defined in Graphics.PDF.Shapes (==) :: DashPattern -> DashPattern -> Bool # (/=) :: DashPattern -> DashPattern -> Bool # |
setLineCap :: MonadPath m => CapStyle -> m () Source #
Set line cap
setLineJoin :: MonadPath m => JoinStyle -> m () Source #
Set line join
setDash :: MonadPath m => DashPattern -> m () Source #
Set the dash pattern
setMiterLimit :: MonadPath m => PDFFloat -> m () Source #
Set pen width