module Graphics.PDF.Shapes(
moveto
, lineto
, arcto
, curveto
, beginPath
, closePath
, addBezierCubic
, addPolygonToPath
, addLineToPath
, strokePath
, fillPath
, fillAndStrokePath
, fillPathEO
, fillAndStrokePathEO
, setAsClipPath
, setAsClipPathEO
, Shape(..)
, Line(..)
, Rectangle(..)
, Polygon(..)
, Arc(..)
, Ellipse(..)
, Circle(..)
, RoundRectangle(..)
, 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
$c== :: Line -> Line -> Bool
== :: Line -> Line -> Bool
$c/= :: Line -> Line -> Bool
/= :: 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
_ = String -> Draw ()
forall a. HasCallStack => String -> a
error String
"Can't fill a line !"
fillAndStroke :: Line -> Draw ()
fillAndStroke Line
_ = String -> Draw ()
forall a. HasCallStack => String -> a
error String
"Can't fill a line !"
fillEO :: Line -> Draw ()
fillEO Line
_ = String -> Draw ()
forall a. HasCallStack => String -> a
error String
"Can't fill a line !"
fillAndStrokeEO :: Line -> Draw ()
fillAndStrokeEO Line
_ = String -> Draw ()
forall a. HasCallStack => String -> a
error String
"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
$c== :: Rectangle -> Rectangle -> Bool
== :: Rectangle -> Rectangle -> Bool
$c/= :: Rectangle -> Rectangle -> Bool
/= :: 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)
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" 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
$c== :: Arc -> Arc -> Bool
== :: Arc -> Arc -> Bool
$c/= :: Arc -> Arc -> Bool
/= :: 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
$c== :: Ellipse -> Ellipse -> Bool
== :: Ellipse -> Ellipse -> Bool
$c/= :: Ellipse -> Ellipse -> Bool
/= :: 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
$c== :: RoundRectangle -> RoundRectangle -> Bool
== :: RoundRectangle -> RoundRectangle -> Bool
$c/= :: RoundRectangle -> RoundRectangle -> Bool
/= :: 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
$c== :: Circle -> Circle -> Bool
== :: Circle -> Circle -> Bool
$c/= :: Circle -> Circle -> Bool
/= :: 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
setWidth :: MonadPath m => PDFFloat -> m ()
setWidth :: forall (m :: * -> *). MonadPath m => 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
$[ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\n"
, PDFFloat -> Builder
forall a. PdfObject a => a -> Builder
toPDF PDFFloat
w
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" w"
]
setMiterLimit :: MonadPath m => PDFFloat -> m ()
setMiterLimit :: forall (m :: * -> *). MonadPath m => 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
$[ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\n"
, PDFFloat -> Builder
forall a. PdfObject a => a -> Builder
toPDF PDFFloat
w
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" M"
]
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
$c== :: CapStyle -> CapStyle -> Bool
== :: CapStyle -> CapStyle -> Bool
$c/= :: CapStyle -> CapStyle -> Bool
/= :: 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
$csucc :: CapStyle -> CapStyle
succ :: CapStyle -> CapStyle
$cpred :: CapStyle -> CapStyle
pred :: CapStyle -> CapStyle
$ctoEnum :: Int -> CapStyle
toEnum :: Int -> CapStyle
$cfromEnum :: CapStyle -> Int
fromEnum :: CapStyle -> Int
$cenumFrom :: CapStyle -> [CapStyle]
enumFrom :: CapStyle -> [CapStyle]
$cenumFromThen :: CapStyle -> CapStyle -> [CapStyle]
enumFromThen :: CapStyle -> CapStyle -> [CapStyle]
$cenumFromTo :: CapStyle -> CapStyle -> [CapStyle]
enumFromTo :: CapStyle -> CapStyle -> [CapStyle]
$cenumFromThenTo :: CapStyle -> CapStyle -> CapStyle -> [CapStyle]
enumFromThenTo :: CapStyle -> CapStyle -> CapStyle -> [CapStyle]
Enum)
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
$c== :: JoinStyle -> JoinStyle -> Bool
== :: JoinStyle -> JoinStyle -> Bool
$c/= :: JoinStyle -> JoinStyle -> Bool
/= :: 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
$csucc :: JoinStyle -> JoinStyle
succ :: JoinStyle -> JoinStyle
$cpred :: JoinStyle -> JoinStyle
pred :: JoinStyle -> JoinStyle
$ctoEnum :: Int -> JoinStyle
toEnum :: Int -> JoinStyle
$cfromEnum :: JoinStyle -> Int
fromEnum :: JoinStyle -> Int
$cenumFrom :: JoinStyle -> [JoinStyle]
enumFrom :: JoinStyle -> [JoinStyle]
$cenumFromThen :: JoinStyle -> JoinStyle -> [JoinStyle]
enumFromThen :: JoinStyle -> JoinStyle -> [JoinStyle]
$cenumFromTo :: JoinStyle -> JoinStyle -> [JoinStyle]
enumFromTo :: JoinStyle -> JoinStyle -> [JoinStyle]
$cenumFromThenTo :: JoinStyle -> JoinStyle -> JoinStyle -> [JoinStyle]
enumFromThenTo :: JoinStyle -> JoinStyle -> JoinStyle -> [JoinStyle]
Enum)
setLineCap :: MonadPath m => CapStyle -> m ()
setLineCap :: forall (m :: * -> *). MonadPath m => 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
$[ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\n "
, Int -> Builder
forall a. PdfObject a => a -> Builder
toPDF (CapStyle -> Int
forall a. Enum a => a -> Int
fromEnum CapStyle
w)
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" J"
]
setLineJoin :: MonadPath m => JoinStyle -> m ()
setLineJoin :: forall (m :: * -> *). MonadPath m => 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
$[ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\n "
, Int -> Builder
forall a. PdfObject a => a -> Builder
toPDF (JoinStyle -> Int
forall a. Enum a => a -> Int
fromEnum JoinStyle
w)
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" 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
$c== :: DashPattern -> DashPattern -> Bool
== :: DashPattern -> DashPattern -> Bool
$c/= :: DashPattern -> DashPattern -> Bool
/= :: DashPattern -> DashPattern -> Bool
Eq)
setDash :: MonadPath m => DashPattern -> m()
setDash :: forall (m :: * -> *). MonadPath m => 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
$ [ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\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
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" d"
]
setNoDash :: MonadPath m => m ()
setNoDash :: forall (m :: * -> *). MonadPath m => m ()
setNoDash = DashPattern -> m ()
forall (m :: * -> *). MonadPath m => DashPattern -> m ()
setDash ([PDFFloat] -> PDFFloat -> DashPattern
DashPattern [] PDFFloat
0)
beginPath :: Point
-> Draw ()
beginPath :: Point -> Draw ()
beginPath = Point -> Draw ()
moveto
closePath :: Draw ()
closePath :: Draw ()
closePath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nh"
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
$ [ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\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
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" c"
]
(forall s. DrawTuple s -> STRef s Point) -> Point -> Draw ()
forall a. (forall s. DrawTuple s -> STRef s a) -> a -> Draw ()
writeDrawST DrawTuple s -> STRef s Point
forall s. DrawTuple s -> STRef s Point
penPosition Point
d
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
$ [ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\n"
, Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
a
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" m"
]
(forall s. DrawTuple s -> STRef s Point) -> Point -> Draw ()
forall a. (forall s. DrawTuple s -> STRef s a) -> a -> Draw ()
writeDrawST DrawTuple s -> STRef s Point
forall s. DrawTuple s -> STRef s Point
penPosition Point
a
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
$[ String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
"\n"
, Point -> Builder
forall a. PdfObject a => a -> Builder
toPDF Point
a
, String -> Builder
forall s a. SerializeValue s a => a -> s
serialize String
" l"
]
(forall s. DrawTuple s -> STRef s Point) -> Point -> Draw ()
forall a. (forall s. DrawTuple s -> STRef s a) -> a -> Draw ()
writeDrawST DrawTuple s -> STRef s Point
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
arcto :: Angle
-> Point
-> 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 a. a -> Draw a
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 DrawTuple s -> STRef s Point
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
addPolygonToPath :: [Point]
-> Draw ()
addPolygonToPath :: [Point] -> Draw ()
addPolygonToPath [] = () -> Draw ()
forall a. a -> Draw a
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
strokePath :: Draw ()
strokePath :: Draw ()
strokePath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nS"
fillPath :: Draw ()
fillPath :: Draw ()
fillPath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nf"
fillAndStrokePath :: Draw ()
fillAndStrokePath :: Draw ()
fillAndStrokePath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nB"
setAsClipPathEO :: Draw ()
setAsClipPathEO :: Draw ()
setAsClipPathEO = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nW* n"
setAsClipPath :: Draw ()
setAsClipPath :: Draw ()
setAsClipPath = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nW n"
fillPathEO :: Draw ()
fillPathEO :: Draw ()
fillPathEO = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nf*"
fillAndStrokePathEO :: Draw ()
fillAndStrokePathEO :: Draw ()
fillAndStrokePathEO = Builder -> Draw ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (Builder -> Draw ()) -> (String -> Builder) -> String -> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
forall s a. SerializeValue s a => a -> s
serialize (String -> Draw ()) -> String -> Draw ()
forall a b. (a -> b) -> a -> b
$ String
"\nB*"