---------------------------------------------------------
-- |
-- Copyright   : (c) 2006-2016, alpheccar.org
-- License     : BSD-style
--
-- Maintainer  : misc@NOSPAMalpheccar.org
-- Stability   : experimental
-- Portability : portable
--
-- PDF Shapes
---------------------------------------------------------

module Graphics.PDF.Shapes(
   -- * Shapes
   -- ** Paths
     moveto
   , lineto
   , arcto
   , curveto
   , beginPath
   , closePath
   , addBezierCubic
   , addPolygonToPath
   , addLineToPath
   , strokePath
   , fillPath
   , fillAndStrokePath
   , fillPathEO
   , fillAndStrokePathEO
   , setAsClipPath
   , setAsClipPathEO
   -- ** Usual shapes
   , Shape(..)
   , Line(..)
   , Rectangle(..)
   , Polygon(..)
   , Arc(..)
   , Ellipse(..)
   , Circle(..)
   , RoundRectangle(..)
   -- ** Style
   , CapStyle(..)
   , JoinStyle(..)
   , DashPattern(..)
   , setWidth
   , setLineCap
   , setLineJoin
   , setDash
   , setNoDash
   , setMiterLimit
 ) where

import Graphics.PDF.LowLevel.Types
import Graphics.PDF.Coordinates
import Graphics.PDF.Draw
import Control.Monad.Writer
import Graphics.PDF.LowLevel.Serializer

class Shape a where
    addShape :: a -> Draw ()
    stroke :: a -> Draw ()
    fill :: a -> Draw ()
    fillAndStroke :: a -> Draw ()
    fillEO :: a -> Draw ()
    fillAndStrokeEO :: a -> Draw ()
    stroke a
r = do
        a -> Draw ()
forall a. Shape a => a -> Draw ()
addShape a
r
        Draw ()
strokePath
    fill a
r = do
        a -> Draw ()
forall a. Shape a => a -> Draw ()
addShape a
r
        Draw ()
fillPath
    fillAndStroke a
r = do
        a -> Draw ()
forall a. Shape a => a -> Draw ()
addShape a
r
        Draw ()
fillAndStrokePath
    fillEO a
r = do
        a -> Draw ()
forall a. Shape a => a -> Draw ()
addShape a
r
        Draw ()
fillPathEO
    fillAndStrokeEO a
r = do
        a -> Draw ()
forall a. Shape a => a -> Draw ()
addShape a
r
        Draw ()
fillAndStrokePathEO
    
data Line = Line PDFFloat PDFFloat PDFFloat PDFFloat deriving(Line -> Line -> Bool
(Line -> Line -> Bool) -> (Line -> Line -> Bool) -> Eq Line
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Line -> Line -> Bool
$c/= :: Line -> Line -> Bool
== :: Line -> Line -> Bool
$c== :: Line -> Line -> Bool
Eq)
instance Shape Line where
    addShape :: Line -> Draw ()
addShape (Line PDFFloat
x0 PDFFloat
y0 PDFFloat
x1 PDFFloat
y1)= do
        Point -> Draw ()
moveto (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)
        Point -> Draw ()
lineto (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1)
    fill :: Line -> Draw ()
fill Line
_ = [Char] -> Draw ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Can't fill a line !"
    fillAndStroke :: Line -> Draw ()
fillAndStroke Line
_ = [Char] -> Draw ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Can't fill a line !"
    fillEO :: Line -> Draw ()
fillEO Line
_ = [Char] -> Draw ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Can't fill a line !"
    fillAndStrokeEO :: Line -> Draw ()
fillAndStrokeEO Line
_ = [Char] -> Draw ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Can't fill a line !"
    
data Rectangle = Rectangle !Point !Point deriving (Rectangle -> Rectangle -> Bool
(Rectangle -> Rectangle -> Bool)
-> (Rectangle -> Rectangle -> Bool) -> Eq Rectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rectangle -> Rectangle -> Bool
$c/= :: Rectangle -> Rectangle -> Bool
== :: Rectangle -> Rectangle -> Bool
$c== :: Rectangle -> Rectangle -> Bool
Eq) 
instance Shape Rectangle where
 addShape :: Rectangle -> Draw ()
addShape (Rectangle Point
a Point
b) 
     = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ())
-> ([Builder] -> Builder) -> [Builder] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Draw ()) -> [Builder] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [ Char -> Builder
forall s a. SerializeValue s a => a -> s
serialize Char
'\n'
                        , Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
a
                        , Char -> Builder
forall s a. SerializeValue s a => a -> s
serialize Char
' '
                        , Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF (Point
b Point -> Point -> Point
forall a. Num a => a -> a -> a
- Point
a)
                        , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" re" ]
 
data Arc = Arc PDFFloat PDFFloat PDFFloat PDFFloat deriving(Arc -> Arc -> Bool
(Arc -> Arc -> Bool) -> (Arc -> Arc -> Bool) -> Eq Arc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Arc -> Arc -> Bool
$c/= :: Arc -> Arc -> Bool
== :: Arc -> Arc -> Bool
$c== :: Arc -> Arc -> Bool
Eq)
instance Shape Arc where
    addShape :: Arc -> Draw ()
addShape (Arc PDFFloat
x0 PDFFloat
y0 PDFFloat
x1 PDFFloat
y1) = do
        let height :: PDFFloat
height = PDFFloat
y1 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
y0
            width :: PDFFloat
width = PDFFloat
x1 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
x0
            kappa :: PDFFloat
kappa = PDFFloat
0.5522847498
        Point -> Draw ()
beginPath (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)
        Point -> Point -> Point -> Draw ()
addBezierCubic ((PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
widthPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
kappa) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0) (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
heightPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
kappa)) (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1)
               
data Ellipse = Ellipse PDFFloat PDFFloat PDFFloat PDFFloat deriving(Ellipse -> Ellipse -> Bool
(Ellipse -> Ellipse -> Bool)
-> (Ellipse -> Ellipse -> Bool) -> Eq Ellipse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ellipse -> Ellipse -> Bool
$c/= :: Ellipse -> Ellipse -> Bool
== :: Ellipse -> Ellipse -> Bool
$c== :: Ellipse -> Ellipse -> Bool
Eq)
instance Shape Ellipse where
    addShape :: Ellipse -> Draw ()
addShape (Ellipse PDFFloat
x0 PDFFloat
y0 PDFFloat
x1 PDFFloat
y1) = do
        let xm :: PDFFloat
xm = (PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
x1)PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/PDFFloat
2.0
            ym :: PDFFloat
ym = (PDFFloat
y0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
y1)PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/PDFFloat
2.0
            k :: PDFFloat
k = PDFFloat
0.5522847498
            h :: PDFFloat
h = PDFFloat
kPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*(PDFFloat -> PDFFloat
forall a. Num a => a -> a
abs (PDFFloat
y1 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
y0)PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/PDFFloat
2.0)
            w :: PDFFloat
w = PDFFloat
kPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*(PDFFloat -> PDFFloat
forall a. Num a => a -> a
abs (PDFFloat
x1 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
x0)PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/PDFFloat
2.0)

        Point -> Draw ()
beginPath (PDFFloat
xm PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)
        Point -> Point -> Point -> Draw ()
addBezierCubic ((PDFFloat
xm PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0) (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
ym PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
h)) (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
ym)
        Point -> Point -> Point -> Draw ()
addBezierCubic (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
ym PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
h)) ((PDFFloat
xm PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1) (PDFFloat
xm PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1)
        Point -> Point -> Point -> Draw ()
addBezierCubic ((PDFFloat
xm PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1) (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
ym PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
h)) (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
ym)
        Point -> Point -> Point -> Draw ()
addBezierCubic (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
ym PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
h)) ((PDFFloat
xm PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0) (PDFFloat
xm PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)

data RoundRectangle = RoundRectangle PDFFloat PDFFloat PDFFloat PDFFloat PDFFloat PDFFloat deriving(RoundRectangle -> RoundRectangle -> Bool
(RoundRectangle -> RoundRectangle -> Bool)
-> (RoundRectangle -> RoundRectangle -> Bool) -> Eq RoundRectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoundRectangle -> RoundRectangle -> Bool
$c/= :: RoundRectangle -> RoundRectangle -> Bool
== :: RoundRectangle -> RoundRectangle -> Bool
$c== :: RoundRectangle -> RoundRectangle -> Bool
Eq)
instance Shape RoundRectangle where
    addShape :: RoundRectangle -> Draw ()
addShape (RoundRectangle PDFFloat
rw PDFFloat
rh PDFFloat
x0 PDFFloat
y0 PDFFloat
x1 PDFFloat
y1) = do
        let k :: PDFFloat
k = PDFFloat
0.5522847498
            h :: PDFFloat
h = PDFFloat
kPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
rw
            w :: PDFFloat
w = PDFFloat
kPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
rh

        Point -> Draw ()
beginPath ((PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rw) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)
        Point -> Draw ()
addLineToPath ((PDFFloat
x1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rw) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)
        Point -> Point -> Point -> Draw ()
addBezierCubic ((PDFFloat
x1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rw PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0) (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rh PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
h)) (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rh))
        Point -> Draw ()
addLineToPath (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rh))
        Point -> Point -> Point -> Draw ()
addBezierCubic (PDFFloat
x1 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rh PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
h)) ((PDFFloat
x1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rw PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1) ((PDFFloat
x1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rw) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1)
        Point -> Draw ()
addLineToPath ((PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rw) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1)
        Point -> Point -> Point -> Draw ()
addBezierCubic ((PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rw PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y1) (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rh PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
h)) (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rh))
        Point -> Draw ()
addLineToPath (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rh))
        Point -> Point -> Point -> Draw ()
addBezierCubic (PDFFloat
x0 PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rh PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
h)) ((PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rw PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
w) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0) ((PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
rw) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)
        Point -> Draw ()
addLineToPath ((PDFFloat
x1PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
rw) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y0)
        
data Circle = Circle PDFFloat PDFFloat PDFFloat deriving(Circle -> Circle -> Bool
(Circle -> Circle -> Bool)
-> (Circle -> Circle -> Bool) -> Eq Circle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Circle -> Circle -> Bool
$c/= :: Circle -> Circle -> Bool
== :: Circle -> Circle -> Bool
$c== :: Circle -> Circle -> Bool
Eq)
instance Shape Circle where
    addShape :: Circle -> Draw ()
addShape (Circle PDFFloat
x0 PDFFloat
y0 PDFFloat
r) = Ellipse -> Draw ()
forall a. Shape a => a -> Draw ()
addShape (PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> Ellipse
Ellipse (PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
r) (PDFFloat
y0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
r) (PDFFloat
x0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
r) (PDFFloat
y0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
r) )
                
newtype Polygon = Polygon [Point]
instance Shape Polygon where
    addShape :: Polygon -> Draw ()
addShape (Polygon [Point]
l) = [Point] -> Draw ()
addPolygonToPath [Point]
l


-- | Set pen width
setWidth :: MonadPath m => PDFFloat -> m ()
setWidth :: PDFFloat -> m ()
setWidth PDFFloat
w = Builder -> m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> m ()) -> ([Builder] -> Builder) -> [Builder] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> m ()) -> [Builder] -> m ()
forall a b. (a -> b) -> a -> b
$[ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n" 
                             , PDFFloat -> Builder
forall a. PdfObject a => a -> Builder
toPDF PDFFloat
w
                             , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" w"
                             ]

-- | Set pen width
setMiterLimit :: MonadPath m => PDFFloat -> m ()
setMiterLimit :: PDFFloat -> m ()
setMiterLimit PDFFloat
w = Builder -> m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> m ()) -> ([Builder] -> Builder) -> [Builder] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> m ()) -> [Builder] -> m ()
forall a b. (a -> b) -> a -> b
$[ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n" 
                                  , PDFFloat -> Builder
forall a. PdfObject a => a -> Builder
toPDF PDFFloat
w
                                  , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" M"
                                  ]

-- | Line cap styles
data CapStyle = ButtCap
              | RoundCap
              | SquareCap
              deriving(CapStyle -> CapStyle -> Bool
(CapStyle -> CapStyle -> Bool)
-> (CapStyle -> CapStyle -> Bool) -> Eq CapStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CapStyle -> CapStyle -> Bool
$c/= :: CapStyle -> CapStyle -> Bool
== :: CapStyle -> CapStyle -> Bool
$c== :: CapStyle -> CapStyle -> Bool
Eq,Int -> CapStyle
CapStyle -> Int
CapStyle -> [CapStyle]
CapStyle -> CapStyle
CapStyle -> CapStyle -> [CapStyle]
CapStyle -> CapStyle -> CapStyle -> [CapStyle]
(CapStyle -> CapStyle)
-> (CapStyle -> CapStyle)
-> (Int -> CapStyle)
-> (CapStyle -> Int)
-> (CapStyle -> [CapStyle])
-> (CapStyle -> CapStyle -> [CapStyle])
-> (CapStyle -> CapStyle -> [CapStyle])
-> (CapStyle -> CapStyle -> CapStyle -> [CapStyle])
-> Enum CapStyle
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CapStyle -> CapStyle -> CapStyle -> [CapStyle]
$cenumFromThenTo :: CapStyle -> CapStyle -> CapStyle -> [CapStyle]
enumFromTo :: CapStyle -> CapStyle -> [CapStyle]
$cenumFromTo :: CapStyle -> CapStyle -> [CapStyle]
enumFromThen :: CapStyle -> CapStyle -> [CapStyle]
$cenumFromThen :: CapStyle -> CapStyle -> [CapStyle]
enumFrom :: CapStyle -> [CapStyle]
$cenumFrom :: CapStyle -> [CapStyle]
fromEnum :: CapStyle -> Int
$cfromEnum :: CapStyle -> Int
toEnum :: Int -> CapStyle
$ctoEnum :: Int -> CapStyle
pred :: CapStyle -> CapStyle
$cpred :: CapStyle -> CapStyle
succ :: CapStyle -> CapStyle
$csucc :: CapStyle -> CapStyle
Enum)
              
-- | Line join styles
data JoinStyle = MiterJoin
               | RoundJoin
               | BevelJoin
               deriving(JoinStyle -> JoinStyle -> Bool
(JoinStyle -> JoinStyle -> Bool)
-> (JoinStyle -> JoinStyle -> Bool) -> Eq JoinStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinStyle -> JoinStyle -> Bool
$c/= :: JoinStyle -> JoinStyle -> Bool
== :: JoinStyle -> JoinStyle -> Bool
$c== :: JoinStyle -> JoinStyle -> Bool
Eq,Int -> JoinStyle
JoinStyle -> Int
JoinStyle -> [JoinStyle]
JoinStyle -> JoinStyle
JoinStyle -> JoinStyle -> [JoinStyle]
JoinStyle -> JoinStyle -> JoinStyle -> [JoinStyle]
(JoinStyle -> JoinStyle)
-> (JoinStyle -> JoinStyle)
-> (Int -> JoinStyle)
-> (JoinStyle -> Int)
-> (JoinStyle -> [JoinStyle])
-> (JoinStyle -> JoinStyle -> [JoinStyle])
-> (JoinStyle -> JoinStyle -> [JoinStyle])
-> (JoinStyle -> JoinStyle -> JoinStyle -> [JoinStyle])
-> Enum JoinStyle
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: JoinStyle -> JoinStyle -> JoinStyle -> [JoinStyle]
$cenumFromThenTo :: JoinStyle -> JoinStyle -> JoinStyle -> [JoinStyle]
enumFromTo :: JoinStyle -> JoinStyle -> [JoinStyle]
$cenumFromTo :: JoinStyle -> JoinStyle -> [JoinStyle]
enumFromThen :: JoinStyle -> JoinStyle -> [JoinStyle]
$cenumFromThen :: JoinStyle -> JoinStyle -> [JoinStyle]
enumFrom :: JoinStyle -> [JoinStyle]
$cenumFrom :: JoinStyle -> [JoinStyle]
fromEnum :: JoinStyle -> Int
$cfromEnum :: JoinStyle -> Int
toEnum :: Int -> JoinStyle
$ctoEnum :: Int -> JoinStyle
pred :: JoinStyle -> JoinStyle
$cpred :: JoinStyle -> JoinStyle
succ :: JoinStyle -> JoinStyle
$csucc :: JoinStyle -> JoinStyle
Enum)
                            
-- | Set line cap
setLineCap :: MonadPath m => CapStyle -> m ()
setLineCap :: CapStyle -> m ()
setLineCap CapStyle
w = Builder -> m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> m ()) -> ([Builder] -> Builder) -> [Builder] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> m ()) -> [Builder] -> m ()
forall a b. (a -> b) -> a -> b
$[ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n " 
                               , Int -> Builder
forall a. PdfObject a => a -> Builder
toPDF (CapStyle -> Int
forall a. Enum a => a -> Int
fromEnum  CapStyle
w)
                               , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" J"
                               ]

-- | Set line join
setLineJoin :: MonadPath m => JoinStyle -> m ()
setLineJoin :: JoinStyle -> m ()
setLineJoin JoinStyle
w = Builder -> m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> m ()) -> ([Builder] -> Builder) -> [Builder] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> m ()) -> [Builder] -> m ()
forall a b. (a -> b) -> a -> b
$[ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n " 
                                , Int -> Builder
forall a. PdfObject a => a -> Builder
toPDF (JoinStyle -> Int
forall a. Enum a => a -> Int
fromEnum  JoinStyle
w)
                                , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" j"
                                ]

data DashPattern = DashPattern ![PDFFloat] PDFFloat deriving(DashPattern -> DashPattern -> Bool
(DashPattern -> DashPattern -> Bool)
-> (DashPattern -> DashPattern -> Bool) -> Eq DashPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DashPattern -> DashPattern -> Bool
$c/= :: DashPattern -> DashPattern -> Bool
== :: DashPattern -> DashPattern -> Bool
$c== :: DashPattern -> DashPattern -> Bool
Eq)

-- | Set the dash pattern
setDash :: MonadPath m => DashPattern -> m()
setDash :: DashPattern -> m ()
setDash (DashPattern [PDFFloat]
a PDFFloat
p) = 
    Builder -> m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> m ()) -> ([Builder] -> Builder) -> [Builder] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat([Builder] -> m ()) -> [Builder] -> m ()
forall a b. (a -> b) -> a -> b
$ [ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n " 
                    , [PDFFloat] -> Builder
forall a. PdfObject a => a -> Builder
toPDF [PDFFloat]
a
                    , Char -> Builder
forall s a. SerializeValue s a => a -> s
serialize Char
' '
                    , PDFFloat -> Builder
forall a. PdfObject a => a -> Builder
toPDF PDFFloat
p
                    , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" d"
                    ]

-- | No dash pattern
setNoDash :: MonadPath m => m ()
setNoDash :: m ()
setNoDash = DashPattern -> m ()
forall (m :: * -> *). MonadPath m => DashPattern -> m ()
setDash ([PDFFloat] -> PDFFloat -> DashPattern
DashPattern [] PDFFloat
0)
    
-- | Begin a new path at a position
beginPath :: Point 
          -> Draw ()
beginPath :: Point -> Draw ()
beginPath = Point -> Draw ()
moveto

-- | Close current path 
closePath :: Draw ()
closePath :: Draw ()
closePath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nh"


-- | 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
addBezierCubic :: Point
               -> Point
               -> Point
               -> Draw ()
addBezierCubic :: Point -> Point -> Point -> Draw ()
addBezierCubic Point
b Point
c Point
d = do
    Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ())
-> ([Builder] -> Builder) -> [Builder] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Draw ()) -> [Builder] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n" 
                     , Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
b
                     , Char -> Builder
forall s a. SerializeValue s a => a -> s
serialize Char
' '
                     , Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
c
                     , Char -> Builder
forall s a. SerializeValue s a => a -> s
serialize Char
' '
                     , Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
d
                     , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" c"
                     ]
    (forall s. DrawTuple s -> STRef s Point) -> Point -> Draw ()
forall a. (forall s. DrawTuple s -> STRef s a) -> a -> Draw ()
writeDrawST forall s. DrawTuple s -> STRef s Point
penPosition Point
d
                    
-- | Move pen to a given point without drawing anything
moveto :: Point 
       -> Draw ()
moveto :: Point -> Draw ()
moveto Point
a = do 
    Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ())
-> ([Builder] -> Builder) -> [Builder] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Draw ()) -> [Builder] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n" 
                     , Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
a
                     , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" m"
                     ]
    (forall s. DrawTuple s -> STRef s Point) -> Point -> Draw ()
forall a. (forall s. DrawTuple s -> STRef s a) -> a -> Draw ()
writeDrawST forall s. DrawTuple s -> STRef s Point
penPosition Point
a

-- | Draw a line from current point to the one specified by lineto
lineto :: Point 
       -> Draw () 
lineto :: Point -> Draw ()
lineto Point
a = do
    Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ())
-> ([Builder] -> Builder) -> [Builder] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Draw ()) -> [Builder] -> Draw ()
forall a b. (a -> b) -> a -> b
$[ [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
"\n" 
                    , Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
a
                    , [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize [Char]
" l"
                    ]
    (forall s. DrawTuple s -> STRef s Point) -> Point -> Draw ()
forall a. (forall s. DrawTuple s -> STRef s a) -> a -> Draw ()
writeDrawST forall s. DrawTuple s -> STRef s Point
penPosition Point
a

curveto :: Point -> Point -> Point -> Draw ()
curveto :: Point -> Point -> Point -> Draw ()
curveto = Point -> Point -> Point -> Draw ()
addBezierCubic

-- | Approximate a circular arc by one cubic bezier curve.
-- larger arc angles mean larger distortions
arcto :: Angle   -- ^ Extent of arc
      -> Point   -- ^ Center of arc
      -> Draw ()
arcto :: Angle -> Point -> Draw ()
arcto Angle
extent 
    = let theta :: PDFFloat
theta = Angle -> PDFFloat
toRadian Angle
extent
          kappa :: PDFFloat
kappa = PDFFloat
4 PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/ PDFFloat
3 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
* PDFFloat -> PDFFloat
forall a. Floating a => a -> a
tan (PDFFloat
theta PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/ PDFFloat
4)
          cis_theta :: Point
cis_theta = PDFFloat -> Point
forall a. Floating a => a -> Complex a
cis PDFFloat
theta
          rot90 :: Complex a -> Complex a
rot90 (a
x :+ a
y) = ((-a
y) a -> a -> Complex a
forall a. a -> a -> Complex a
:+ a
x)
       in if PDFFloat
theta PDFFloat -> PDFFloat -> Bool
forall a. Eq a => a -> a -> Bool
== PDFFloat
0
          then \Point
_center -> () -> Draw ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          else \Point
center -> do
            Point
a <- (forall s. DrawTuple s -> STRef s Point) -> Draw Point
forall a. (forall s. DrawTuple s -> STRef s a) -> Draw a
readDrawST forall s. DrawTuple s -> STRef s Point
penPosition
            let delta :: Point
delta  = Point
a Point -> Point -> Point
forall a. Num a => a -> a -> a
- Point
center
                delta' :: Point
delta' = PDFFloat -> Point -> Point
forall t. RealFloat t => t -> Complex t -> Complex t
scalePt PDFFloat
kappa (Point -> Point
forall a. Num a => Complex a -> Complex a
rot90 Point
delta)
                d :: Point
d = Point
center Point -> Point -> Point
forall a. Num a => a -> a -> a
+ Point
delta Point -> Point -> Point
forall a. Num a => a -> a -> a
* Point
cis_theta
                c :: Point
c = Point
d Point -> Point -> Point
forall a. Num a => a -> a -> a
- Point
delta' Point -> Point -> Point
forall a. Num a => a -> a -> a
* Point
cis_theta
                b :: Point
b = Point
a Point -> Point -> Point
forall a. Num a => a -> a -> a
+ Point
delta'
            Point -> Point -> Point -> Draw ()
curveto Point
b Point
c Point
d

addLineToPath :: Point 
              -> Draw ()
addLineToPath :: Point -> Draw ()
addLineToPath = Point -> Draw ()
lineto

-- | Add a polygon to current path
addPolygonToPath :: [Point]
                 -> Draw ()
addPolygonToPath :: [Point] -> Draw ()
addPolygonToPath []  = () -> Draw ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
addPolygonToPath (Point
l : [Point]
ls) =  do
    Point -> Draw ()
moveto Point
l
    (Point -> Draw ()) -> [Point] -> Draw ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Point -> Draw ()
addLineToPath [Point]
ls  
    
-- | Draw current path
strokePath :: Draw ()             
strokePath :: Draw ()
strokePath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nS"

-- | Fill current path
fillPath :: Draw ()             
fillPath :: Draw ()
fillPath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nf"

-- | Fill current path
fillAndStrokePath :: Draw ()             
fillAndStrokePath :: Draw ()
fillAndStrokePath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nB"

-- | Set clipping path
setAsClipPathEO :: Draw ()             
setAsClipPathEO :: Draw ()
setAsClipPathEO = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nW* n"

-- | Set clipping path
setAsClipPath :: Draw ()             
setAsClipPath :: Draw ()
setAsClipPath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nW n"

-- | Fill current path using even odd rule
fillPathEO :: Draw ()             
fillPathEO :: Draw ()
fillPathEO = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nf*"

-- | Fill current path using even odd rule
fillAndStrokePathEO :: Draw ()             
fillAndStrokePathEO :: Draw ()
fillAndStrokePathEO = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> ([Char] -> Builder) -> [Char] -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Builder
forall s a. SerializeValue s a => a -> s
serialize ([Char] -> Draw ()) -> [Char] -> Draw ()
forall a b. (a -> b) -> a -> b
$ [Char]
"\nB*"