module Text.Blaze.Svg.Internal where
import Control.Monad.State
import Data.Monoid (mappend, mempty)
import Text.Blaze
type Svg = Markup
toSvg :: ToMarkup a => a -> Svg
toSvg = toMarkup
type Path = State AttributeValue ()
mkPath :: Path -> AttributeValue
mkPath path = snd $ runState path mempty
appendToPath :: [String] -> Path
appendToPath = modify . flip mappend . toValue . join
m :: Show a => a -> a -> Path
m x y = appendToPath
[ "M "
, show x, ",", show y
, " "
]
mr :: Show a => a -> a -> Path
mr dx dy = appendToPath
[ "m "
, show dx, ",", show dy
, " "
]
z :: Path
z = modify (`mappend` toValue "Z")
l :: Show a => a -> a -> Path
l x y = appendToPath
[ "L "
, show x, ",", show y
, " "
]
lr :: Show a => a -> a -> Path
lr dx dy = appendToPath
[ "l "
, show dx, ",", show dy
, " "
]
h :: Show a => a -> Path
h x = appendToPath
[ "H "
, show x
, " "
]
hr :: Show a => a -> Path
hr dx = appendToPath
[ "h "
, show dx
, " "
]
v :: Show a => a -> Path
v y = appendToPath
[ "V "
, show y
, " "
]
vr :: Show a => a -> Path
vr dy = appendToPath
[ "v "
, show dy
, " "
]
c :: Show a => a -> a -> a -> a -> a -> a -> Path
c c1x c1y c2x c2y x y = appendToPath
[ "C "
, show c1x, ",", show c1y
, " "
, show c2x, ",", show c2y
, " "
, show x, " ", show y
]
cr :: Show a => a -> a -> a -> a -> a -> a -> Path
cr dc1x dc1y dc2x dc2y dx dy = appendToPath
[ "c "
, show dc1x, ",", show dc1y
, " "
, show dc2x, ",", show dc2y
, " "
, show dx, " ", show dy
]
s :: Show a => a -> a -> a -> a -> Path
s c2x c2y x y = appendToPath
[ "S "
, show c2x, ",", show c2y
, " "
, show x, ",", show y
, " "
]
sr :: Show a => a -> a -> a -> a -> Path
sr dc2x dc2y dx dy = appendToPath
[ "s "
, show dc2x, ",", show dc2y
, " "
, show dx, ",", show dy
, " "
]
q :: Show a => a -> a -> a -> a -> Path
q cx cy x y = appendToPath
[ "Q "
, show cx, ",", show cy
, " "
, show x, ",", show y
, " "
]
qr :: Show a => a -> a -> a -> a -> Path
qr dcx dcy dx dy = appendToPath
[ "q "
, show dcx, ",", show dcy
, " "
, show dx, ",", show dy
, " "
]
t :: Show a => a -> a -> Path
t x y = appendToPath
[ "T "
, " "
, show x, ",", show y
, " "
]
tr :: Show a => a -> a -> Path
tr x y = appendToPath
[ "t "
, " "
, show x, ",", show y
, " "
]
aa
:: Show a
=> a
-> a
-> a
-> Bool
-> Bool
-> a
-> a
-> Path
aa = a
a
:: Show a
=> a
-> a
-> a
-> Bool
-> Bool
-> a
-> a
-> Path
a rx ry xAxisRotation largeArcFlag sweepFlag x y = appendToPath
[ "A "
, show rx, ",", show ry, " "
, show xAxisRotation, " "
, if largeArcFlag then "1" else "0", ",", if sweepFlag then "1" else "0", " "
, show x, ",", show y, " "
]
ar
:: Show a
=> a
-> a
-> a
-> Bool
-> Bool
-> a
-> a
-> Path
ar rx ry xAxisRotation largeArcFlag sweepFlag x y = appendToPath
[ "a "
, show rx, ",", show ry, " "
, show xAxisRotation, " "
, if largeArcFlag then "1" else "0", ",", if sweepFlag then "1" else "0", " "
, show x, ",", show y, " "
]
translate :: Show a => a -> a -> AttributeValue
translate x y = toValue . join $
[ "translate("
, show x, " ", show y
, ")"
]
scale :: Show a => a -> a -> AttributeValue
scale x y = toValue . join $
[ "scale("
, show x, " ", show y
, ")"
]
rotate :: Show a => a -> AttributeValue
rotate rotateAngle = toValue . join $
[ "rotate("
, show rotateAngle
, ")"
]
rotateAround :: Show a => a -> a -> a -> AttributeValue
rotateAround rotateAngle rx ry = toValue . join $
[ "rotate("
, show rotateAngle, ","
, show rx, ",", show ry
, ")"
]
skewX :: Show a => a -> AttributeValue
skewX skewAngle = toValue . join $
[ "skewX("
, show skewAngle
, ")"
]
skewY :: Show a => a -> AttributeValue
skewY skewAngle = toValue . join $
[ "skewY("
, show skewAngle
, ")"
]
matrix :: Show a => a -> a -> a -> a -> a -> a -> AttributeValue
matrix a_ b c_ d e f = toValue . join $
[ "matrix("
, show a_, ","
, show b, ","
, show c_, ","
, show d, ","
, show e, ","
, show f
, ")"
]