module Reanimate.Svg.Constructors
(
mkCircle
, mkEllipse
, mkRect
, mkLine
, mkPath
, mkPathString
, mkPathText
, mkLinePath
, mkLinePathClosed
, mkClipPath
, mkText
, mkGroup
, mkDefinitions
, mkUse
, withId
, withStrokeColor
, withStrokeColorPixel
, withStrokeDashArray
, withStrokeLineJoin
, withFillColor
, withFillColorPixel
, withFillOpacity
, withGroupOpacity
, withStrokeWidth
, withClipPathRef
, center
, centerX
, centerY
, centerUsing
, translate
, rotate
, rotateAroundCenter
, rotateAround
, scale
, scaleToSize
, scaleToWidth
, scaleToHeight
, scaleXY
, flipXAxis
, flipYAxis
, aroundCenter
, aroundCenterX
, aroundCenterY
, withTransformations
, withViewBox
, mkColor
, mkBackground
, mkBackgroundPixel
, gridLayout
) where
import Codec.Picture (PixelRGBA8 (..))
import Control.Lens ((&), (.~), (?~))
import Data.Attoparsec.Text (parseOnly)
import qualified Data.Map as Map
import qualified Data.Text as T
import Graphics.SvgTree
import Graphics.SvgTree.NamedColors
import Graphics.SvgTree.PathParser
import Linear.V2 hiding (angle)
import Reanimate.Constants
import Reanimate.Svg.BoundingBox
withTransformations :: [Transformation] -> Tree -> Tree
withTransformations transformations t =
mkGroup [t] & transform ?~ transformations
translate :: Double -> Double -> Tree -> Tree
translate x y = withTransformations [Translate x y]
rotate :: Double -> Tree -> Tree
rotate a = withTransformations [Rotate a Nothing]
rotateAround :: Double -> RPoint -> Tree -> Tree
rotateAround a (V2 x y) = withTransformations [Rotate a (Just (x,y))]
rotateAroundCenter :: Double -> Tree -> Tree
rotateAroundCenter a t =
rotateAround a (V2 (x+w/2) (y+h/2)) t
where
(x,y,w,h) = boundingBox t
aroundCenter :: (Tree -> Tree) -> Tree -> Tree
aroundCenter fn t =
translate (-offsetX) (-offsetY) $ fn $ translate offsetX offsetY t
where
offsetX = -x-w/2
offsetY = -y-h/2
(x,y,w,h) = boundingBox t
aroundCenterY :: (Tree -> Tree) -> Tree -> Tree
aroundCenterY fn t =
translate 0 (-offsetY) $ fn $ translate 0 offsetY t
where
offsetY = -y-h/2
(_x,y,_w,h) = boundingBox t
aroundCenterX :: (Tree -> Tree) -> Tree -> Tree
aroundCenterX fn t =
translate (-offsetX) 0 $ fn $ translate offsetX 0 t
where
offsetX = -x-w/2
(x,_y,w,_h) = boundingBox t
scale :: Double -> Tree -> Tree
scale a = withTransformations [Scale a Nothing]
scaleToSize :: Double -> Double -> Tree -> Tree
scaleToSize w h t =
scaleXY (w/w') (h/h') t
where
(_x, _y, w', h') = boundingBox t
scaleToWidth :: Double -> Tree -> Tree
scaleToWidth w t =
scale (w/w') t
where
(_x, _y, w', _h') = boundingBox t
scaleToHeight :: Double -> Tree -> Tree
scaleToHeight h t =
scale (h/h') t
where
(_x, _y, _w', h') = boundingBox t
scaleXY :: Double -> Double -> Tree -> Tree
scaleXY x y = withTransformations [Scale x (Just y)]
flipXAxis :: Tree -> Tree
flipXAxis = scaleXY (-1) 1
flipYAxis :: Tree -> Tree
flipYAxis = scaleXY 1 (-1)
center :: Tree -> Tree
center t = centerUsing t t
centerX :: Tree -> Tree
centerX t = translate (-x-w/2) 0 t
where
(x, _y, w, _h) = boundingBox t
centerY :: Tree -> Tree
centerY t = translate 0 (-y-h/2) t
where
(_x, y, _w, h) = boundingBox t
centerUsing :: Tree -> Tree -> Tree
centerUsing a = translate (-x-w/2) (-y-h/2)
where
(x, y, w, h) = boundingBox a
mkColor :: String -> Texture
mkColor name =
case Map.lookup (T.pack name) svgNamedColors of
Nothing -> ColorRef (PixelRGBA8 240 248 255 255)
Just c -> ColorRef c
withStrokeColor :: String -> Tree -> Tree
withStrokeColor color = strokeColor .~ pure (mkColor color)
withStrokeColorPixel :: PixelRGBA8 -> Tree -> Tree
withStrokeColorPixel color = strokeColor .~ pure (ColorRef color)
withStrokeDashArray :: [Double] -> Tree -> Tree
withStrokeDashArray arr = strokeDashArray .~ pure (map Num arr)
withStrokeLineJoin :: LineJoin -> Tree -> Tree
withStrokeLineJoin ljoin = strokeLineJoin .~ pure ljoin
withFillColor :: String -> Tree -> Tree
withFillColor color = fillColor .~ pure (mkColor color)
withFillColorPixel :: PixelRGBA8 -> Tree -> Tree
withFillColorPixel color = fillColor .~ pure (ColorRef color)
withFillOpacity :: Double -> Tree -> Tree
withFillOpacity opacity = fillOpacity ?~ realToFrac opacity
withGroupOpacity :: Double -> Tree -> Tree
withGroupOpacity opacity = groupOpacity ?~ realToFrac opacity
withStrokeWidth :: Double -> Tree -> Tree
withStrokeWidth width = strokeWidth .~ pure (Num width)
withClipPathRef :: ElementRef
-> Tree
-> Tree
withClipPathRef ref sub = mkGroup [sub] & clipPathRef .~ pure ref
withId :: String -> Tree -> Tree
withId idTag = attrId ?~ idTag
mkRect :: Double -> Double -> Tree
mkRect width height = translate (-width/2) (-height/2) $ rectangleTree $ defaultSvg
& rectUpperLeftCorner .~ (Num 0, Num 0)
& rectWidth ?~ Num width
& rectHeight ?~ Num height
mkCircle :: Double -> Tree
mkCircle radius = circleTree $ defaultSvg
& circleCenter .~ (Num 0, Num 0)
& circleRadius .~ Num radius
mkEllipse :: Double -> Double -> Tree
mkEllipse rx ry = ellipseTree $ defaultSvg
& ellipseCenter .~ (Num 0, Num 0)
& ellipseXRadius .~ Num rx
& ellipseYRadius .~ Num ry
mkLine :: (Double,Double) -> (Double, Double) -> Tree
mkLine (x1,y1) (x2,y2) = lineTree $ defaultSvg
& linePoint1 .~ (Num x1, Num y1)
& linePoint2 .~ (Num x2, Num y2)
mkGroup :: [Tree] -> Tree
mkGroup forest = groupTree $ defaultSvg
& groupChildren .~ forest
mkDefinitions :: [Tree] -> Tree
mkDefinitions forest = definitionTree $ defaultSvg
& groupChildren .~ forest
mkUse :: String -> Tree
mkUse name = useTree (defaultSvg & useName .~ name)
mkClipPath :: String
-> [Tree]
-> Tree
mkClipPath idTag forest = withId idTag $ clipPathTree $ defaultSvg
& clipPathContent .~ forest
mkPath :: [PathCommand] -> Tree
mkPath cmds = pathTree $ defaultSvg & pathDefinition .~ cmds
mkPathString :: String -> Tree
mkPathString = mkPathText . T.pack
mkPathText :: T.Text -> Tree
mkPathText str =
case parseOnly pathParser str of
Left err -> error err
Right cmds -> mkPath cmds
mkLinePath :: [(Double, Double)] -> Tree
mkLinePath [] = mkGroup []
mkLinePath ((startX, startY):rest) =
pathTree $ defaultSvg & pathDefinition .~ cmds
where
cmds = [ MoveTo OriginAbsolute [V2 startX startY]
, LineTo OriginAbsolute [ V2 x y | (x, y) <- rest ] ]
mkLinePathClosed :: [(Double, Double)] -> Tree
mkLinePathClosed [] = mkGroup []
mkLinePathClosed ((startX, startY):rest) =
pathTree $ defaultSvg & pathDefinition .~ cmds
where
cmds = [ MoveTo OriginAbsolute [V2 startX startY]
, LineTo OriginAbsolute [ V2 x y | (x, y) <- rest ]
, EndPath ]
mkBackground :: String -> Tree
mkBackground color = withFillOpacity 1 $ withStrokeWidth 0 $
withFillColor color $ mkRect screenWidth screenHeight
mkBackgroundPixel :: PixelRGBA8 -> Tree
mkBackgroundPixel pixel =
withFillOpacity 1 $ withStrokeWidth 0 $
withFillColorPixel pixel $ mkRect screenWidth screenHeight
gridLayout :: [[Tree]] -> Tree
gridLayout rows = mkGroup
[ translate (-screenWidth/2+colSep*nCol + colSep*0.5)
(screenHeight/2-rowSep*nRow - rowSep*0.5)
elt
| (nRow, row) <- zip [0..] rows
, let nCols = length row
colSep = screenWidth / fromIntegral nCols
, (nCol, elt) <- zip [0..] row ]
where
rowSep = screenHeight / fromIntegral nRows
nRows = length rows
mkText :: T.Text -> Tree
mkText str =
flipYAxis
(TextTree Nothing $ defaultSvg
& textRoot .~ span_
& fontSize .~ pure (Num 2))
& textAnchor .~ pure TextAnchorMiddle
where
span_ = defaultSvg & spanContent .~ [SpanText str]
withViewBox :: (Double, Double, Double, Double) -> Tree -> Tree
withViewBox vbox child = translate (-screenWidth/2) (-screenHeight/2) $
svgTree Document
{ _documentViewBox = Just vbox
, _documentWidth = Just (Num screenWidth)
, _documentHeight = Just (Num screenHeight)
, _documentElements = [child]
, _documentDescription = ""
, _documentLocation = ""
, _documentAspectRatio = PreserveAspectRatio False AlignNone Nothing
}