{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE TemplateHaskell #-}
module Data.Path.Parser
(
parsePath,
pathParser,
command,
manyComma,
svgToPathData,
pathDataToSvg,
PathCommand (..),
Origin (..),
toPathDatas,
)
where
import Chart.Data
import Control.Applicative hiding (many, optional, some, (<|>))
import Control.Monad.State.Lazy
import Data.ByteString (ByteString, intercalate)
import Data.FormatN
import Data.Path (ArcInfo (ArcInfo), PathData (..))
import Data.Text.Encoding (encodeUtf8)
import FlatParse.Basic (char, optional, (<|>))
import GHC.Generics
import GHC.OverloadedLabels
import MarkupParse.FlatParse
import NumHask.Prelude hiding (optional, (<|>))
import Optics.Core hiding ((<|))
parsePath :: ByteString -> Maybe [PathCommand]
parsePath :: ByteString -> Maybe [PathCommand]
parsePath = forall e a. Parser e a -> ByteString -> Maybe a
runParserMaybe forall e. Parser e [PathCommand]
pathParser
commaWsp :: Parser e (Maybe ())
commaWsp :: forall e. Parser e (Maybe ())
commaWsp = forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e (Maybe a)
optional forall e. Parser e ()
MarkupParse.FlatParse.comma forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e ()
ws_
num :: Parser e Double
num :: forall e. Parser e Double
num = forall b e. Num b => Parser e b -> Parser e b
signed forall e. Parser e Double
double
point :: Parser e (Point Double)
point :: forall e. Parser e (Point Double)
point = forall a. a -> a -> Point a
Point forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e. Parser e Double
num forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e Double
num
numComma :: Parser e Double
numComma :: forall e. Parser e Double
numComma = forall e. Parser e Double
num forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp
points :: Parser e [Point Double]
points :: forall e. Parser e [Point Double]
points = (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e. Parser e (Point Double)
point forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall e. Parser e (Maybe ())
commaWsp forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e (Point Double)
point) forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
pointPair :: Parser e (Point Double, Point Double)
pointPair :: forall e. Parser e (Point Double, Point Double)
pointPair = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e. Parser e (Point Double)
point forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e (Point Double)
point
pointPairs :: Parser e [(Point Double, Point Double)]
pointPairs :: forall e. Parser e [(Point Double, Point Double)]
pointPairs = (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e. Parser e (Point Double, Point Double)
pointPair forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall e. Parser e (Maybe ())
commaWsp forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e (Point Double, Point Double)
pointPair) forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
nums :: Parser e [Double]
nums :: forall e. Parser e [Double]
nums = (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e. Parser e Double
num forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall e. Parser e (Maybe ())
commaWsp forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e Double
num) forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
flag :: Parser e Bool
flag :: forall e. Parser e Bool
flag = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Eq a => a -> a -> Bool
/= Int
0) forall e. Parser e Int
digit
manyComma :: Parser e a -> Parser e [a]
manyComma :: forall e a. Parser e a -> Parser e [a]
manyComma Parser e a
a = (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser e a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall e. Parser e (Maybe ())
commaWsp forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser e a
a) forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
flagComma :: Parser e Bool
flagComma :: forall e. Parser e Bool
flagComma = forall e. Parser e Bool
flag forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp
curveToArgs ::
Parser
e
(Point Double, Point Double, Point Double)
curveToArgs :: forall e. Parser e (Point Double, Point Double, Point Double)
curveToArgs =
(,,)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall e. Parser e (Point Double)
point forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e (Point Double)
point forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e (Point Double)
point
ellipticalArgs ::
Parser
e
(Double, Double, Double, Bool, Bool, Point Double)
ellipticalArgs :: forall e.
Parser e (Double, Double, Double, Bool, Bool, Point Double)
ellipticalArgs =
(,,,,,)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e. Parser e Double
numComma
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e Double
numComma
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e Double
numComma
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e Bool
flagComma
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e Bool
flagComma
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e. Parser e (Point Double)
point
pathParser :: Parser e [PathCommand]
pathParser :: forall e. Parser e [PathCommand]
pathParser = forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e a. Parser e a -> Parser e [a]
manyComma forall e. Parser e PathCommand
command
command :: Parser e PathCommand
command :: forall e. Parser e PathCommand
command =
(Origin -> [Point Double] -> PathCommand
MoveTo Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'M') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Point Double]
points))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Point Double] -> PathCommand
MoveTo Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'm') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Point Double]
points))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Point Double] -> PathCommand
LineTo Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'L') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Point Double]
points))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Point Double] -> PathCommand
LineTo Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'l') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Point Double]
points))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Double] -> PathCommand
HorizontalTo Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'H') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Double]
nums))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Double] -> PathCommand
HorizontalTo Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'h') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Double]
nums))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Double] -> PathCommand
VerticalTo Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'V') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Double]
nums))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Double] -> PathCommand
VerticalTo Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'v') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Double]
nums))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin
-> [(Point Double, Point Double, Point Double)] -> PathCommand
CurveTo Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'C') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e a. Parser e a -> Parser e [a]
manyComma forall e. Parser e (Point Double, Point Double, Point Double)
curveToArgs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin
-> [(Point Double, Point Double, Point Double)] -> PathCommand
CurveTo Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'c') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e a. Parser e a -> Parser e [a]
manyComma forall e. Parser e (Point Double, Point Double, Point Double)
curveToArgs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [(Point Double, Point Double)] -> PathCommand
SmoothCurveTo Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'S') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [(Point Double, Point Double)]
pointPairs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [(Point Double, Point Double)] -> PathCommand
SmoothCurveTo Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 's') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [(Point Double, Point Double)]
pointPairs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [(Point Double, Point Double)] -> PathCommand
QuadraticBezier Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'Q') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [(Point Double, Point Double)]
pointPairs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [(Point Double, Point Double)] -> PathCommand
QuadraticBezier Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'q') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [(Point Double, Point Double)]
pointPairs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Point Double] -> PathCommand
SmoothQuadraticBezierCurveTo Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'T') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Point Double]
points))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin -> [Point Double] -> PathCommand
SmoothQuadraticBezierCurveTo Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 't') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e. Parser e [Point Double]
points))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin
-> [(Double, Double, Double, Bool, Bool, Point Double)]
-> PathCommand
EllipticalArc Origin
OriginAbsolute forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'A') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e a. Parser e a -> Parser e [a]
manyComma forall e.
Parser e (Double, Double, Double, Bool, Bool, Point Double)
ellipticalArgs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (Origin
-> [(Double, Double, Double, Bool, Bool, Point Double)]
-> PathCommand
EllipticalArc Origin
OriginRelative forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'a') forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall e. Parser e ()
ws_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall e a. Parser e a -> Parser e [a]
manyComma forall e.
Parser e (Double, Double, Double, Bool, Bool, Point Double)
ellipticalArgs))
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (PathCommand
EndPath forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'Z') forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp)
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> (PathCommand
EndPath forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ $(char 'z') forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall e. Parser e (Maybe ())
commaWsp)
data PathCommand
=
MoveTo !Origin ![Point Double]
|
LineTo !Origin ![Point Double]
|
HorizontalTo !Origin ![Double]
|
VerticalTo !Origin ![Double]
|
CurveTo !Origin ![(Point Double, Point Double, Point Double)]
|
SmoothCurveTo !Origin ![(Point Double, Point Double)]
|
QuadraticBezier !Origin ![(Point Double, Point Double)]
|
SmoothQuadraticBezierCurveTo !Origin ![Point Double]
|
EllipticalArc !Origin ![(Double, Double, Double, Bool, Bool, Point Double)]
|
EndPath
deriving (PathCommand -> PathCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PathCommand -> PathCommand -> Bool
$c/= :: PathCommand -> PathCommand -> Bool
== :: PathCommand -> PathCommand -> Bool
$c== :: PathCommand -> PathCommand -> Bool
Eq, Int -> PathCommand -> ShowS
[PathCommand] -> ShowS
PathCommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PathCommand] -> ShowS
$cshowList :: [PathCommand] -> ShowS
show :: PathCommand -> String
$cshow :: PathCommand -> String
showsPrec :: Int -> PathCommand -> ShowS
$cshowsPrec :: Int -> PathCommand -> ShowS
Show, forall x. Rep PathCommand x -> PathCommand
forall x. PathCommand -> Rep PathCommand x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PathCommand x -> PathCommand
$cfrom :: forall x. PathCommand -> Rep PathCommand x
Generic)
data Origin
=
OriginAbsolute
|
OriginRelative
deriving (Origin -> Origin -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Origin -> Origin -> Bool
$c/= :: Origin -> Origin -> Bool
== :: Origin -> Origin -> Bool
$c== :: Origin -> Origin -> Bool
Eq, Int -> Origin -> ShowS
[Origin] -> ShowS
Origin -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Origin] -> ShowS
$cshowList :: [Origin] -> ShowS
show :: Origin -> String
$cshow :: Origin -> String
showsPrec :: Int -> Origin -> ShowS
$cshowsPrec :: Int -> Origin -> ShowS
Show, forall x. Rep Origin x -> Origin
forall x. Origin -> Rep Origin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Origin x -> Origin
$cfrom :: forall x. Origin -> Rep Origin x
Generic)
pointToSvgCoords :: Point Double -> Point Double
pointToSvgCoords :: Point Double -> Point Double
pointToSvgCoords (Point Double
x Double
y) = forall a. a -> a -> Point a
Point Double
x (-Double
y)
svgCoords :: PathData Double -> PathData Double
svgCoords :: PathData Double -> PathData Double
svgCoords (CubicP Point Double
a Point Double
b Point Double
p) = forall a. Point a -> Point a -> Point a -> PathData a
CubicP (Point Double -> Point Double
pointToSvgCoords Point Double
a) (Point Double -> Point Double
pointToSvgCoords Point Double
b) (Point Double -> Point Double
pointToSvgCoords Point Double
p)
svgCoords (QuadP Point Double
a Point Double
p) = forall a. Point a -> Point a -> PathData a
QuadP (Point Double -> Point Double
pointToSvgCoords Point Double
a) (Point Double -> Point Double
pointToSvgCoords Point Double
p)
svgCoords (StartP Point Double
p) = forall a. Point a -> PathData a
StartP (Point Double -> Point Double
pointToSvgCoords Point Double
p)
svgCoords (LineP Point Double
p) = forall a. Point a -> PathData a
LineP (Point Double -> Point Double
pointToSvgCoords Point Double
p)
svgCoords (ArcP ArcInfo Double
i Point Double
p) = forall a. ArcInfo a -> Point a -> PathData a
ArcP ArcInfo Double
i (Point Double -> Point Double
pointToSvgCoords Point Double
p)
toPathAbsolute ::
PathData Double ->
ByteString
toPathAbsolute :: PathData Double -> ByteString
toPathAbsolute (StartP Point Double
p) = ByteString
"M " forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
p
toPathAbsolute (LineP Point Double
p) = ByteString
"L " forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
p
toPathAbsolute (CubicP Point Double
c1 Point Double
c2 Point Double
p) =
ByteString
"C "
forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
c1
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
c2
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
p
toPathAbsolute (QuadP Point Double
control Point Double
p) =
ByteString
"Q "
forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
control
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
p
toPathAbsolute (ArcP (ArcInfo (Point Double
x Double
y) Double
phi' Bool
l Bool
sw) Point Double
x2) =
ByteString
"A "
forall a. Semigroup a => a -> a -> a
<> Double -> ByteString
pv' Double
x
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> Double -> ByteString
pv' Double
y
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> Double -> ByteString
pv' (-(Double
phi' forall a. Multiplicative a => a -> a -> a
* Double
180 forall a. Divisive a => a -> a -> a
/ forall a. TrigField a => a
pi))
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> forall a. a -> a -> Bool -> a
bool ByteString
"0" ByteString
"1" Bool
l
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> forall a. a -> a -> Bool -> a
bool ByteString
"0" ByteString
"1" Bool
sw
forall a. Semigroup a => a -> a -> a
<> ByteString
" "
forall a. Semigroup a => a -> a -> a
<> Point Double -> ByteString
pp' Point Double
x2
pv' :: Double -> ByteString
pv' :: Double -> ByteString
pv' Double
x =
Text -> ByteString
encodeUtf8 forall a b. (a -> b) -> a -> b
$
FormatStyle -> Maybe Int -> Double -> Text
formatOrShow (Int -> FormatStyle
FixedStyle Int
4) forall a. Maybe a
Nothing Double
x
pp' :: Point Double -> ByteString
pp' :: Point Double -> ByteString
pp' (Point Double
x Double
y) =
Text -> ByteString
encodeUtf8 forall a b. (a -> b) -> a -> b
$
FormatStyle -> Maybe Int -> Double -> Text
formatOrShow (Int -> FormatStyle
FixedStyle Int
4) forall a. Maybe a
Nothing Double
x
forall a. Semigroup a => a -> a -> a
<> Text
","
forall a. Semigroup a => a -> a -> a
<> FormatStyle -> Maybe Int -> Double -> Text
formatOrShow (Int -> FormatStyle
FixedStyle Int
4) forall a. Maybe a
Nothing (forall a. a -> a -> Bool -> a
bool (-Double
y) Double
y (Double
y forall a. Eq a => a -> a -> Bool
== forall a. Additive a => a
zero))
data PathCursor = PathCursor
{
PathCursor -> Point Double
curPrevious :: Point Double,
PathCursor -> Point Double
curStart :: Point Double,
PathCursor -> Maybe (Point Double)
curControl :: Maybe (Point Double)
}
deriving (PathCursor -> PathCursor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PathCursor -> PathCursor -> Bool
$c/= :: PathCursor -> PathCursor -> Bool
== :: PathCursor -> PathCursor -> Bool
$c== :: PathCursor -> PathCursor -> Bool
Eq, Int -> PathCursor -> ShowS
[PathCursor] -> ShowS
PathCursor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PathCursor] -> ShowS
$cshowList :: [PathCursor] -> ShowS
show :: PathCursor -> String
$cshow :: PathCursor -> String
showsPrec :: Int -> PathCursor -> ShowS
$cshowsPrec :: Int -> PathCursor -> ShowS
Show, forall x. Rep PathCursor x -> PathCursor
forall x. PathCursor -> Rep PathCursor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PathCursor x -> PathCursor
$cfrom :: forall x. PathCursor -> Rep PathCursor x
Generic)
stateCur0 :: PathCursor
stateCur0 :: PathCursor
stateCur0 = Point Double -> Point Double -> Maybe (Point Double) -> PathCursor
PathCursor forall a. Additive a => a
zero forall a. Additive a => a
zero forall a. Maybe a
Nothing
svgToPathData :: ByteString -> [PathData Double]
svgToPathData :: ByteString -> [PathData Double]
svgToPathData = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap [PathCommand] -> [PathData Double]
toPathDatas forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Maybe [PathCommand]
parsePath
pathDataToSvg :: [PathData Double] -> ByteString
pathDataToSvg :: [PathData Double] -> ByteString
pathDataToSvg [PathData Double]
xs = ByteString -> [ByteString] -> ByteString
intercalate ByteString
" " forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathData Double -> ByteString
toPathAbsolute [PathData Double]
xs
toPathDatas :: [PathCommand] -> [PathData Double]
toPathDatas :: [PathCommand] -> [PathData Double]
toPathDatas [PathCommand]
xs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathData Double -> PathData Double
svgCoords forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> b -> a -> c
flip forall s a. State s a -> s -> a
evalState PathCursor
stateCur0 forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM PathCommand -> State PathCursor [PathData Double]
toPathData [PathCommand]
xs
relToAbs :: (Additive a) => a -> [a] -> [a]
relToAbs :: forall a. Additive a => a -> [a] -> [a]
relToAbs a
p [a]
xs = forall a (f :: * -> *). (Additive a, Traversable f) => f a -> f a
accsum (a
p forall a. a -> [a] -> [a]
: [a]
xs)
moveTo :: [Point Double] -> State PathCursor [PathData Double]
moveTo :: [Point Double] -> State PathCursor [PathData Double]
moveTo [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure []
moveTo (Point Double
x : [Point Double]
xs) = do
forall s (m :: * -> *). MonadState s m => s -> m ()
put (Point Double -> Point Double -> Maybe (Point Double) -> PathCursor
PathCursor (forall a. a -> Maybe a -> a
fromMaybe Point Double
x forall a b. (a -> b) -> a -> b
$ forall a. [a] -> Maybe a
listToMaybe forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [Point Double]
xs) Point Double
x forall a. Maybe a
Nothing)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Point a -> PathData a
StartP Point Double
x forall a. a -> [a] -> [a]
: (forall a. Point a -> PathData a
LineP forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double]
xs))
lineTo :: [Point Double] -> State PathCursor [PathData Double]
lineTo :: [Point Double] -> State PathCursor [PathData Double]
lineTo [Point Double]
xs = do
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curPrevious" a => a
#curPrevious (forall a. [a] -> a
last [Point Double]
xs) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curControl" a => a
#curControl forall a. Maybe a
Nothing)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Point a -> PathData a
LineP forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double]
xs
horTo :: [Double] -> State PathCursor [PathData Double]
horTo :: [Double] -> State PathCursor [PathData Double]
horTo [Double]
xs = do
(PathCursor (Point Double
_ Double
y) Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[Point Double] -> State PathCursor [PathData Double]
lineTo (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> a -> Point a
`Point` Double
y) [Double]
xs)
verTo :: [Double] -> State PathCursor [PathData Double]
verTo :: [Double] -> State PathCursor [PathData Double]
verTo [Double]
ys = do
(PathCursor (Point Double
x Double
_) Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[Point Double] -> State PathCursor [PathData Double]
lineTo (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> a -> Point a
Point Double
x) [Double]
ys)
curveTo :: [(Point Double, Point Double, Point Double)] -> State PathCursor [PathData Double]
curveTo :: [(Point Double, Point Double, Point Double)]
-> State PathCursor [PathData Double]
curveTo [(Point Double, Point Double, Point Double)]
xs = do
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify
( forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curPrevious" a => a
#curPrevious ((\(Point Double
_, Point Double
_, Point Double
p) -> Point Double
p) (forall a. [a] -> a
last [(Point Double, Point Double, Point Double)]
xs))
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (forall a. IsLabel "curControl" a => a
#curControl forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a (Maybe b) -> b -> s -> t
?~ (\(Point Double
_, Point Double
c2, Point Double
_) -> Point Double
c2) (forall a. [a] -> a
last [(Point Double, Point Double, Point Double)]
xs))
)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (\(Point Double
c1, Point Double
c2, Point Double
x2) -> forall a. Point a -> Point a -> Point a -> PathData a
CubicP Point Double
c1 Point Double
c2 Point Double
x2) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Point Double, Point Double, Point Double)]
xs
relToAbs3 :: (Additive a) => a -> [(a, a, a)] -> [(a, a, a)]
relToAbs3 :: forall a. Additive a => a -> [(a, a, a)] -> [(a, a, a)]
relToAbs3 a
p [(a, a, a)]
xs = [(a, a, a)]
xs'
where
x1 :: [a]
x1 = (\(a
x, a
_, a
_) -> a
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, a, a)]
xs
x2 :: [a]
x2 = (\(a
_, a
x, a
_) -> a
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, a, a)]
xs
x3 :: [a]
x3 = (\(a
_, a
_, a
x) -> a
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, a, a)]
xs
x1' :: [a]
x1' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a
p +) (forall a (f :: * -> *). (Additive a, Traversable f) => f a -> f a
accsum [a]
x1)
x2' :: [a]
x2' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a
p +) (forall a (f :: * -> *). (Additive a, Traversable f) => f a -> f a
accsum [a]
x2)
x3' :: [a]
x3' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a
p +) (forall a (f :: * -> *). (Additive a, Traversable f) => f a -> f a
accsum [a]
x3)
xs' :: [(a, a, a)]
xs' = forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [a]
x1' [a]
x2' [a]
x3'
reflControlPoint :: State PathCursor (Point Double)
reflControlPoint :: State PathCursor (Point Double)
reflControlPoint = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
c) <- forall s (m :: * -> *). MonadState s m => m s
get
case Maybe (Point Double)
c of
Maybe (Point Double)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Point Double
p
Just Point Double
c' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Point Double
p forall a. Subtractive a => a -> a -> a
- (Point Double
c' forall a. Subtractive a => a -> a -> a
- Point Double
p))
smoothCurveToStep :: (Point Double, Point Double) -> State PathCursor (PathData Double)
smoothCurveToStep :: (Point Double, Point Double) -> State PathCursor (PathData Double)
smoothCurveToStep (Point Double
c2, Point Double
x2) = do
Point Double
c1 <- State PathCursor (Point Double)
reflControlPoint
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((forall a. IsLabel "curControl" a => a
#curControl forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a (Maybe b) -> b -> s -> t
?~ Point Double
c2) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curPrevious" a => a
#curPrevious Point Double
x2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Point a -> Point a -> Point a -> PathData a
CubicP Point Double
c1 Point Double
c2 Point Double
x2)
smoothCurveTo :: [(Point Double, Point Double)] -> State PathCursor [PathData Double]
smoothCurveTo :: [(Point Double, Point Double)]
-> State PathCursor [PathData Double]
smoothCurveTo = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Point Double, Point Double) -> State PathCursor (PathData Double)
smoothCurveToStep
relToAbs2 :: (Additive a) => a -> [(a, a)] -> [(a, a)]
relToAbs2 :: forall a. Additive a => a -> [(a, a)] -> [(a, a)]
relToAbs2 a
p [(a, a)]
xs = [(a, a)]
xs'
where
x1 :: [a]
x1 = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, a)]
xs
x2 :: [a]
x2 = forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, a)]
xs
x1' :: [a]
x1' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a
p +) (forall a (f :: * -> *). (Additive a, Traversable f) => f a -> f a
accsum [a]
x1)
x2' :: [a]
x2' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a
p +) (forall a (f :: * -> *). (Additive a, Traversable f) => f a -> f a
accsum [a]
x2)
xs' :: [(a, a)]
xs' = forall a b. [a] -> [b] -> [(a, b)]
zip [a]
x1' [a]
x2'
quad :: [(Point Double, Point Double)] -> State PathCursor [PathData Double]
quad :: [(Point Double, Point Double)]
-> State PathCursor [PathData Double]
quad [(Point Double, Point Double)]
xs = do
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify
( forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curPrevious" a => a
#curPrevious (forall a b. (a, b) -> b
snd (forall a. [a] -> a
last [(Point Double, Point Double)]
xs))
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curControl" a => a
#curControl (forall a. a -> Maybe a
Just (forall a b. (a, b) -> a
fst (forall a. [a] -> a
last [(Point Double, Point Double)]
xs)))
)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Point a -> Point a -> PathData a
QuadP forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Point Double, Point Double)]
xs
smoothQuadStep :: Point Double -> State PathCursor (PathData Double)
smoothQuadStep :: Point Double -> State PathCursor (PathData Double)
smoothQuadStep Point Double
x2 = do
Point Double
c1 <- State PathCursor (Point Double)
reflControlPoint
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curControl" a => a
#curControl (forall a. a -> Maybe a
Just Point Double
c1) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curPrevious" a => a
#curPrevious Point Double
x2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Point a -> Point a -> PathData a
QuadP Point Double
c1 Point Double
x2)
smoothQuad :: [Point Double] -> State PathCursor [PathData Double]
smoothQuad :: [Point Double] -> State PathCursor [PathData Double]
smoothQuad = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Point Double -> State PathCursor (PathData Double)
smoothQuadStep
arcTo :: [(Double, Double, Double, Bool, Bool, Point Double)] -> State PathCursor [PathData Double]
arcTo :: [(Double, Double, Double, Bool, Bool, Point Double)]
-> State PathCursor [PathData Double]
arcTo [(Double, Double, Double, Bool, Bool, Point Double)]
xs = do
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curPrevious" a => a
#curPrevious ((\(Double
_, Double
_, Double
_, Bool
_, Bool
_, Point Double
p) -> Point Double
p) (forall a. [a] -> a
last [(Double, Double, Double, Bool, Bool, Point Double)]
xs)) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "curControl" a => a
#curControl forall a. Maybe a
Nothing)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. (a, a, a, Bool, Bool, Point a) -> PathData a
fromPathEllipticalArc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Double, Double, Double, Bool, Bool, Point Double)]
xs
fromPathEllipticalArc :: (a, a, a, Bool, Bool, Point a) -> PathData a
fromPathEllipticalArc :: forall a. (a, a, a, Bool, Bool, Point a) -> PathData a
fromPathEllipticalArc (a
x, a
y, a
r, Bool
l, Bool
s, Point a
p) = forall a. ArcInfo a -> Point a -> PathData a
ArcP (forall a. Point a -> a -> Bool -> Bool -> ArcInfo a
ArcInfo (forall a. a -> a -> Point a
Point a
x a
y) a
r Bool
l Bool
s) Point a
p
relToAbsArc :: (Additive a) => Point a -> [(a, a, a, Bool, Bool, Point a)] -> [(a, a, a, Bool, Bool, Point a)]
relToAbsArc :: forall a.
Additive a =>
Point a
-> [(a, a, a, Bool, Bool, Point a)]
-> [(a, a, a, Bool, Bool, Point a)]
relToAbsArc Point a
p [(a, a, a, Bool, Bool, Point a)]
xs = [(a, a, a, Bool, Bool, Point a)]
xs'
where
ps :: [Point a]
ps = (\(a
_, a
_, a
_, Bool
_, Bool
_, Point a
pt) -> Point a
pt) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, a, a, Bool, Bool, Point a)]
xs
ps' :: [Point a]
ps' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Point a
p +) (forall a (f :: * -> *). (Additive a, Traversable f) => f a -> f a
accsum [Point a]
ps)
xs' :: [(a, a, a, Bool, Bool, Point a)]
xs' = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\(a
x0, a
x1, a
x2, Bool
x3, Bool
x4, Point a
_) Point a
pt -> (a
x0, a
x1, a
x2, Bool
x3, Bool
x4, Point a
pt)) [(a, a, a, Bool, Bool, Point a)]
xs [Point a]
ps'
toPathData :: PathCommand -> State PathCursor [PathData Double]
toPathData :: PathCommand -> State PathCursor [PathData Double]
toPathData (MoveTo Origin
OriginAbsolute [Point Double]
xs) = [Point Double] -> State PathCursor [PathData Double]
moveTo [Point Double]
xs
toPathData (MoveTo Origin
OriginRelative [Point Double]
xs) = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[Point Double] -> State PathCursor [PathData Double]
moveTo (forall a. Additive a => a -> [a] -> [a]
relToAbs Point Double
p [Point Double]
xs)
toPathData PathCommand
EndPath = do
(PathCursor Point Double
_ Point Double
s Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
forall (f :: * -> *) a. Applicative f => a -> f a
pure [forall a. Point a -> PathData a
LineP Point Double
s]
toPathData (LineTo Origin
OriginAbsolute [Point Double]
xs) = [Point Double] -> State PathCursor [PathData Double]
lineTo [Point Double]
xs
toPathData (LineTo Origin
OriginRelative [Point Double]
xs) = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[Point Double] -> State PathCursor [PathData Double]
lineTo (forall a. Additive a => a -> [a] -> [a]
relToAbs Point Double
p [Point Double]
xs)
toPathData (HorizontalTo Origin
OriginAbsolute [Double]
xs) = [Double] -> State PathCursor [PathData Double]
horTo [Double]
xs
toPathData (HorizontalTo Origin
OriginRelative [Double]
xs) = do
(PathCursor (Point Double
x Double
_) Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[Double] -> State PathCursor [PathData Double]
horTo (forall a. Additive a => a -> [a] -> [a]
relToAbs Double
x [Double]
xs)
toPathData (VerticalTo Origin
OriginAbsolute [Double]
xs) = [Double] -> State PathCursor [PathData Double]
verTo [Double]
xs
toPathData (VerticalTo Origin
OriginRelative [Double]
ys) = do
(PathCursor (Point Double
_ Double
y) Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[Double] -> State PathCursor [PathData Double]
verTo (forall a. Additive a => a -> [a] -> [a]
relToAbs Double
y [Double]
ys)
toPathData (CurveTo Origin
OriginAbsolute [(Point Double, Point Double, Point Double)]
xs) = [(Point Double, Point Double, Point Double)]
-> State PathCursor [PathData Double]
curveTo [(Point Double, Point Double, Point Double)]
xs
toPathData (CurveTo Origin
OriginRelative [(Point Double, Point Double, Point Double)]
xs) = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[(Point Double, Point Double, Point Double)]
-> State PathCursor [PathData Double]
curveTo (forall a. Additive a => a -> [(a, a, a)] -> [(a, a, a)]
relToAbs3 Point Double
p [(Point Double, Point Double, Point Double)]
xs)
toPathData (SmoothCurveTo Origin
OriginAbsolute [(Point Double, Point Double)]
xs) = [(Point Double, Point Double)]
-> State PathCursor [PathData Double]
smoothCurveTo [(Point Double, Point Double)]
xs
toPathData (SmoothCurveTo Origin
OriginRelative [(Point Double, Point Double)]
xs) = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[(Point Double, Point Double)]
-> State PathCursor [PathData Double]
smoothCurveTo (forall a. Additive a => a -> [(a, a)] -> [(a, a)]
relToAbs2 Point Double
p [(Point Double, Point Double)]
xs)
toPathData (QuadraticBezier Origin
OriginAbsolute [(Point Double, Point Double)]
xs) = [(Point Double, Point Double)]
-> State PathCursor [PathData Double]
quad [(Point Double, Point Double)]
xs
toPathData (QuadraticBezier Origin
OriginRelative [(Point Double, Point Double)]
xs) = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[(Point Double, Point Double)]
-> State PathCursor [PathData Double]
quad (forall a. Additive a => a -> [(a, a)] -> [(a, a)]
relToAbs2 Point Double
p [(Point Double, Point Double)]
xs)
toPathData (SmoothQuadraticBezierCurveTo Origin
OriginAbsolute [Point Double]
xs) = [Point Double] -> State PathCursor [PathData Double]
smoothQuad [Point Double]
xs
toPathData (SmoothQuadraticBezierCurveTo Origin
OriginRelative [Point Double]
xs) = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[Point Double] -> State PathCursor [PathData Double]
smoothQuad (forall a. Additive a => a -> [a] -> [a]
relToAbs Point Double
p [Point Double]
xs)
toPathData (EllipticalArc Origin
OriginAbsolute [(Double, Double, Double, Bool, Bool, Point Double)]
xs) = [(Double, Double, Double, Bool, Bool, Point Double)]
-> State PathCursor [PathData Double]
arcTo [(Double, Double, Double, Bool, Bool, Point Double)]
xs
toPathData (EllipticalArc Origin
OriginRelative [(Double, Double, Double, Bool, Bool, Point Double)]
xs) = do
(PathCursor Point Double
p Point Double
_ Maybe (Point Double)
_) <- forall s (m :: * -> *). MonadState s m => m s
get
[(Double, Double, Double, Bool, Bool, Point Double)]
-> State PathCursor [PathData Double]
arcTo (forall a.
Additive a =>
Point a
-> [(a, a, a, Bool, Bool, Point a)]
-> [(a, a, a, Bool, Bool, Point a)]
relToAbsArc Point Double
p [(Double, Double, Double, Bool, Bool, Point Double)]
xs)