module Text.Blaze.Svg.Internal where

import           Control.Monad.State
import           Data.Monoid         (mappend, mempty)

import           Text.Blaze

-- | Type to represent an SVG document fragment.
type Svg = Markup

toSvg :: ToMarkup a => a -> Svg
toSvg :: a -> Svg
toSvg = a -> Svg
forall a. ToMarkup a => a -> Svg
toMarkup

-- | Type to accumulate an SVG path.
type Path = State AttributeValue ()

-- | Construct SVG path values using path instruction combinators.
-- See simple example below of how you can use @mkPath@ to
-- specify a path using the path instruction combinators
-- that are included as part of the same module.
--
-- More information available at: <http://www.w3.org/TR/SVG/paths.html>
--
-- > import Text.Blaze.Svg11 ((!), mkPath, l, m)
-- > import qualified Text.Blaze.Svg11 as S
-- > import qualified Text.Blaze.Svg11.Attributes as A
-- >
-- > svgDoc :: S.Svg
-- > svgDoc = S.docTypeSvg ! A.version "1.1" ! A.width "150" ! A.height "100" $ do
-- >  S.path ! A.d makeSimplePath
-- >
-- > makeSimplePath :: S.AttributeValue
-- > makeSimplePath =  mkPath do
-- >   l 2 3
-- >   m 4 5
mkPath :: Path -> AttributeValue
mkPath :: Path -> AttributeValue
mkPath path :: Path
path = ((), AttributeValue) -> AttributeValue
forall a b. (a, b) -> b
snd (((), AttributeValue) -> AttributeValue)
-> ((), AttributeValue) -> AttributeValue
forall a b. (a -> b) -> a -> b
$ Path -> AttributeValue -> ((), AttributeValue)
forall s a. State s a -> s -> (a, s)
runState Path
path AttributeValue
forall a. Monoid a => a
mempty

appendToPath :: [String] -> Path
appendToPath :: [String] -> Path
appendToPath  = (AttributeValue -> AttributeValue) -> Path
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((AttributeValue -> AttributeValue) -> Path)
-> ([String] -> AttributeValue -> AttributeValue)
-> [String]
-> Path
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AttributeValue -> AttributeValue -> AttributeValue)
-> AttributeValue -> AttributeValue -> AttributeValue
forall a b c. (a -> b -> c) -> b -> a -> c
flip AttributeValue -> AttributeValue -> AttributeValue
forall a. Monoid a => a -> a -> a
mappend (AttributeValue -> AttributeValue -> AttributeValue)
-> ([String] -> AttributeValue)
-> [String]
-> AttributeValue
-> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join

-- | Moveto
m :: Show a => a -> a -> Path
m :: a -> a -> Path
m x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "M "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y
  , " "
  ]

-- | Moveto (relative)
mr :: Show a => a -> a -> Path
mr :: a -> a -> Path
mr dx :: a
dx dy :: a
dy = [String] -> Path
appendToPath
  [ "m "
  , a -> String
forall a. Show a => a -> String
show a
dx, ",", a -> String
forall a. Show a => a -> String
show a
dy
  , " "
  ]

-- | ClosePath
z :: Path
z :: Path
z = (AttributeValue -> AttributeValue) -> Path
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (AttributeValue -> AttributeValue -> AttributeValue
forall a. Monoid a => a -> a -> a
`mappend` String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue "Z")

-- | Lineto
l :: Show a => a -> a -> Path
l :: a -> a -> Path
l x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "L "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y
  , " "
  ]

-- | Lineto (relative)
lr :: Show a => a -> a -> Path
lr :: a -> a -> Path
lr dx :: a
dx dy :: a
dy = [String] -> Path
appendToPath
  [ "l "
  , a -> String
forall a. Show a => a -> String
show a
dx, ",", a -> String
forall a. Show a => a -> String
show a
dy
  , " "
  ]

-- | Horizontal lineto
h :: Show a => a -> Path
h :: a -> Path
h x :: a
x = [String] -> Path
appendToPath
  [ "H "
  , a -> String
forall a. Show a => a -> String
show a
x
  , " "
  ]

-- | Horizontal lineto (relative)
hr :: Show a => a -> Path
hr :: a -> Path
hr dx :: a
dx = [String] -> Path
appendToPath
  [ "h "
  , a -> String
forall a. Show a => a -> String
show a
dx
  , " "
  ]


-- | Vertical lineto
v :: Show a => a -> Path
v :: a -> Path
v y :: a
y = [String] -> Path
appendToPath
  [ "V "
  , a -> String
forall a. Show a => a -> String
show a
y
  , " "
  ]

-- | Vertical lineto (relative)
vr :: Show a => a -> Path
vr :: a -> Path
vr dy :: a
dy = [String] -> Path
appendToPath
  [ "v "
  , a -> String
forall a. Show a => a -> String
show a
dy
  , " "
  ]

-- | Cubic Bezier curve
c :: Show a => a -> a -> a -> a -> a -> a -> Path
c :: a -> a -> a -> a -> a -> a -> Path
c c1x :: a
c1x c1y :: a
c1y c2x :: a
c2x c2y :: a
c2y x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "C "
  , a -> String
forall a. Show a => a -> String
show a
c1x, ",", a -> String
forall a. Show a => a -> String
show a
c1y
  , " "
  , a -> String
forall a. Show a => a -> String
show a
c2x, ",", a -> String
forall a. Show a => a -> String
show a
c2y
  , " "
  , a -> String
forall a. Show a => a -> String
show a
x, " ", a -> String
forall a. Show a => a -> String
show a
y
  ]

-- | Cubic Bezier curve (relative)
cr :: Show a => a -> a -> a -> a -> a -> a -> Path
cr :: a -> a -> a -> a -> a -> a -> Path
cr dc1x :: a
dc1x dc1y :: a
dc1y dc2x :: a
dc2x dc2y :: a
dc2y dx :: a
dx dy :: a
dy = [String] -> Path
appendToPath
  [ "c "
  , a -> String
forall a. Show a => a -> String
show a
dc1x, ",", a -> String
forall a. Show a => a -> String
show a
dc1y
  , " "
  , a -> String
forall a. Show a => a -> String
show a
dc2x, ",", a -> String
forall a. Show a => a -> String
show a
dc2y
  , " "
  , a -> String
forall a. Show a => a -> String
show a
dx, " ", a -> String
forall a. Show a => a -> String
show a
dy
  ]

-- | Smooth Cubic Bezier curve
s :: Show a => a -> a -> a -> a -> Path
s :: a -> a -> a -> a -> Path
s c2x :: a
c2x c2y :: a
c2y x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "S "
  , a -> String
forall a. Show a => a -> String
show a
c2x, ",", a -> String
forall a. Show a => a -> String
show a
c2y
  , " "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y
  , " "
  ]

-- | Smooth Cubic Bezier curve (relative)
sr :: Show a => a -> a -> a -> a -> Path
sr :: a -> a -> a -> a -> Path
sr dc2x :: a
dc2x dc2y :: a
dc2y dx :: a
dx dy :: a
dy = [String] -> Path
appendToPath
  [ "s "
  , a -> String
forall a. Show a => a -> String
show a
dc2x, ",", a -> String
forall a. Show a => a -> String
show a
dc2y
  , " "
  , a -> String
forall a. Show a => a -> String
show a
dx, ",", a -> String
forall a. Show a => a -> String
show a
dy
  , " "
  ]

-- | Quadratic Bezier curve
q :: Show a => a -> a -> a -> a -> Path
q :: a -> a -> a -> a -> Path
q cx :: a
cx cy :: a
cy x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "Q "
  , a -> String
forall a. Show a => a -> String
show a
cx, ",", a -> String
forall a. Show a => a -> String
show a
cy
  , " "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y
  , " "
  ]

-- | Quadratic Bezier curve (relative)
qr :: Show a => a -> a -> a -> a  -> Path
qr :: a -> a -> a -> a -> Path
qr dcx :: a
dcx dcy :: a
dcy dx :: a
dx dy :: a
dy = [String] -> Path
appendToPath
  [ "q "
  , a -> String
forall a. Show a => a -> String
show a
dcx, ",", a -> String
forall a. Show a => a -> String
show a
dcy
  , " "
  , a -> String
forall a. Show a => a -> String
show a
dx, ",", a -> String
forall a. Show a => a -> String
show a
dy
  , " "
  ]

-- | Smooth Quadratic Bezier curve
t  :: Show a => a -> a -> Path
t :: a -> a -> Path
t x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "T "
  , " "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y
  , " "
  ]

-- | Smooth Quadratic Bezier curve (relative)
tr :: Show a => a -> a -> Path
tr :: a -> a -> Path
tr x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "t "
  , " "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y
  , " "
  ]

-- | Elliptical Arc (absolute).
--
--   Note that this function is an alias for the function
--   'Text.Blaze.Svg.Internal.a', defined in
--   "Text.Blaze.Svg.Internal". 'aa' is exported from "Text.Blaze.Svg"
--   instead of 'a' due to naming conflicts with 'Text.Blaze.SVG11.a'
--   from "Text.Blaze.SVG11".
aa
  :: Show a
  => a -- ^ Radius in the x-direction
  -> a -- ^ Radius in the y-direction
  -> a -- ^ The rotation of the arc's x-axis compared to the normal x-axis
  -> Bool -- ^ Draw the smaller or bigger arc satisfying the start point
  -> Bool -- ^ To mirror or not
  -> a -- ^ The x-coordinate of the end point
  -> a -- ^ The y-coordinate of the end point
  -> Path
aa :: a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa = a -> a -> a -> Bool -> Bool -> a -> a -> Path
forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
a

-- | Elliptical Arc (absolute). This is the internal definition for absolute
--   arcs. It is not exported but instead exported as 'aa' due to naming
--   conflicts with 'Text.Blaze.SVG11.a'.
a
  :: Show a
  => a -- ^ Radius in the x-direction
  -> a -- ^ Radius in the y-direction
  -> a -- ^ The rotation of the arc's x-axis compared to the normal x-axis
  -> Bool -- ^ True to draw the larger of the two arcs satisfying constraints.
  -> Bool -- ^ To mirror or not
  -> a -- ^ The x-coordinate of the end point
  -> a -- ^ The y-coordinate of the end point
  -> Path
a :: a -> a -> a -> Bool -> Bool -> a -> a -> Path
a rx :: a
rx ry :: a
ry xAxisRotation :: a
xAxisRotation largeArcFlag :: Bool
largeArcFlag sweepFlag :: Bool
sweepFlag x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "A "
  , a -> String
forall a. Show a => a -> String
show a
rx, ",", a -> String
forall a. Show a => a -> String
show a
ry, " "
  , a -> String
forall a. Show a => a -> String
show a
xAxisRotation, " "
  , if Bool
largeArcFlag then "1" else "0", ",", if Bool
sweepFlag then "1" else "0", " "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y, " "
  ]

-- | Elliptical Arc (relative)
ar
  :: Show a
  => a -- ^ Radius in the x-direction
  -> a -- ^ Radius in the y-direction
  -> a -- ^ The rotation of the arc's x-axis compared to the normal x-axis
  -> Bool -- ^ True to draw the larger of the two arcs satisfying constraints.
  -> Bool -- ^ To mirror or not
  -> a -- ^ The x-coordinate of the end point
  -> a -- ^ The y-coordinate of the end point
  -> Path
ar :: a -> a -> a -> Bool -> Bool -> a -> a -> Path
ar rx :: a
rx ry :: a
ry xAxisRotation :: a
xAxisRotation largeArcFlag :: Bool
largeArcFlag sweepFlag :: Bool
sweepFlag x :: a
x y :: a
y = [String] -> Path
appendToPath
  [ "a "
  , a -> String
forall a. Show a => a -> String
show a
rx, ",", a -> String
forall a. Show a => a -> String
show a
ry, " "
  , a -> String
forall a. Show a => a -> String
show a
xAxisRotation, " "
  , if Bool
largeArcFlag then "1" else "0", ",", if Bool
sweepFlag then "1" else "0", " "
  , a -> String
forall a. Show a => a -> String
show a
x, ",", a -> String
forall a. Show a => a -> String
show a
y, " "
  ]

-- | Specifies a translation by @x@ and @y@
translate :: Show a => a -> a -> AttributeValue
translate :: a -> a -> AttributeValue
translate x :: a
x y :: a
y = String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([String] -> AttributeValue) -> [String] -> AttributeValue
forall a b. (a -> b) -> a -> b
$
  [ "translate("
  , a -> String
forall a. Show a => a -> String
show a
x, " ", a -> String
forall a. Show a => a -> String
show a
y
  , ")"
  ]

-- | Specifies a scale operation by @x@ and @y@
scale :: Show a => a -> a -> AttributeValue
scale :: a -> a -> AttributeValue
scale x :: a
x y :: a
y = String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([String] -> AttributeValue) -> [String] -> AttributeValue
forall a b. (a -> b) -> a -> b
$
  [ "scale("
  , a -> String
forall a. Show a => a -> String
show a
x, " ", a -> String
forall a. Show a => a -> String
show a
y
  , ")"
  ]

-- | Specifies a rotation by @rotate-angle@ degrees
rotate :: Show a => a -> AttributeValue
rotate :: a -> AttributeValue
rotate rotateAngle :: a
rotateAngle = String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([String] -> AttributeValue) -> [String] -> AttributeValue
forall a b. (a -> b) -> a -> b
$
  [ "rotate("
  , a -> String
forall a. Show a => a -> String
show a
rotateAngle
  , ")"
  ]

-- | Specifies a rotation by @rotate-angle@ degrees about the given time @rx,ry@
rotateAround :: Show a => a -> a -> a -> AttributeValue
rotateAround :: a -> a -> a -> AttributeValue
rotateAround rotateAngle :: a
rotateAngle rx :: a
rx ry :: a
ry = String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([String] -> AttributeValue) -> [String] -> AttributeValue
forall a b. (a -> b) -> a -> b
$
  [ "rotate("
  , a -> String
forall a. Show a => a -> String
show a
rotateAngle, ","
  , a -> String
forall a. Show a => a -> String
show a
rx, ",", a -> String
forall a. Show a => a -> String
show a
ry
  , ")"
  ]

-- | Skew tansformation along x-axis
skewX :: Show a => a -> AttributeValue
skewX :: a -> AttributeValue
skewX skewAngle :: a
skewAngle = String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([String] -> AttributeValue) -> [String] -> AttributeValue
forall a b. (a -> b) -> a -> b
$
  [ "skewX("
  , a -> String
forall a. Show a => a -> String
show a
skewAngle
  , ")"
  ]

-- | Skew tansformation along y-axis
skewY :: Show a => a -> AttributeValue
skewY :: a -> AttributeValue
skewY skewAngle :: a
skewAngle = String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([String] -> AttributeValue) -> [String] -> AttributeValue
forall a b. (a -> b) -> a -> b
$
  [ "skewY("
  , a -> String
forall a. Show a => a -> String
show a
skewAngle
  , ")"
  ]

-- | Specifies a transform in the form of a transformation matrix
matrix :: Show a => a -> a -> a -> a -> a -> a -> AttributeValue
matrix :: a -> a -> a -> a -> a -> a -> AttributeValue
matrix a_ :: a
a_ b :: a
b c_ :: a
c_ d :: a
d e :: a
e f :: a
f =  String -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (String -> AttributeValue)
-> ([String] -> String) -> [String] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([String] -> AttributeValue) -> [String] -> AttributeValue
forall a b. (a -> b) -> a -> b
$
  [  "matrix("
  ,  a -> String
forall a. Show a => a -> String
show a
a_, ","
  ,  a -> String
forall a. Show a => a -> String
show a
b, ","
  ,  a -> String
forall a. Show a => a -> String
show a
c_, ","
  ,  a -> String
forall a. Show a => a -> String
show a
d, ","
  ,  a -> String
forall a. Show a => a -> String
show a
e, ","
  ,  a -> String
forall a. Show a => a -> String
show a
f
  , ")"
  ]