{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Graphics.SvgTree.Types.Internal
(
Coord,
Origin (..),
Point,
RPoint,
PathCommand (..),
Transformation (..),
ElementRef (..),
CoordinateUnits (..),
serializeNumber,
serializeTransformation,
serializeTransformations,
Cap (..),
LineJoin (..),
Tree (..),
TreeBranch (..),
Number (..),
Spread (..),
Texture (..),
Element (..),
FillRule (..),
FontStyle (..),
Dpi,
WithDefaultSvg (..),
Document (..),
documentViewBox,
documentWidth,
documentHeight,
documentElements,
documentDescription,
documentLocation,
documentAspectRatio,
documentSize,
DrawAttributes (..),
HasDrawAttributes (..),
FilterElement (..),
FilterAttributes (..),
HasFilterAttributes (..),
FilterSource (..),
Blend (..),
BlendMode (..),
blendDrawAttributes,
blendFilterAttr,
blendIn,
blendIn2,
blendMode,
ConvolveMatrix (..),
convolveMatrixDrawAttributes,
convolveMatrixFilterAttr,
convolveMatrixIn,
convolveMatrixOrder,
convolveMatrixKernelMatrix,
convolveMatrixDivisor,
convolveMatrixBias,
convolveMatrixTargetX,
convolveMatrixTargetY,
convolveMatrixEdgeMode,
convolveMatrixKernelUnitLength,
convolveMatrixPreserveAlpha,
Morphology (..),
OperatorType (..),
NumberOptionalNumber (..),
morphologyDrawAttributes,
morphologyFilterAttr,
morphologyIn,
morphologyOperator,
morphologyRadius,
SpecularLighting (..),
specLightingDrawAttributes,
specLightingFilterAttr,
specLightingIn,
specLightingSurfaceScale,
specLightingSpecularConst,
specLightingSpecularExp,
specLightingKernelUnitLength,
DropShadow (..),
dropShadowDrawAttributes,
dropShadowFilterAttr,
dropShadowDx,
dropShadowDy,
dropShadowStdDeviation,
DiffuseLighting,
diffuseLightingDrawAttributes,
diffuseLightingFilterAttr,
diffuseLightingIn,
diffuseLightingSurfaceScale,
diffuseLightingDiffuseConst,
diffuseLightingKernelUnitLength,
Tile (..),
tileDrawAttributes,
tileFilterAttr,
tileIn,
Flood (..),
floodDrawAttributes,
floodFilterAttr,
floodColor,
floodOpacity,
Offset (..),
offsetDrawAttributes,
offsetFilterAttr,
offsetIn,
offsetDX,
offsetDY,
Merge (..),
mergeDrawAttributes,
mergeFilterAttributes,
mergeChildren,
MergeNode (..),
mergeNodeDrawAttributes,
mergeNodeIn,
ImageF (..),
imageFDrawAttributes,
imageFFilterAttr,
imageFHref,
imageFAspectRatio,
ComponentTransfer (..),
compTransferDrawAttributes,
compTransferFilterAttr,
compTransferChildren,
compTransferIn,
FuncA (..),
FuncType (..),
funcADrawAttributes,
funcAType,
funcATableValues,
funcASlope,
funcAIntercept,
funcAAmplitude,
funcAExponent,
FuncR (..),
funcRDrawAttributes,
funcRType,
funcRTableValues,
funcRSlope,
funcRIntercept,
funcRAmplitude,
funcRExponent,
FuncG (..),
funcGDrawAttributes,
funcGType,
funcGTableValues,
funcGSlope,
funcGIntercept,
funcGAmplitude,
funcGExponent,
FuncB (..),
funcBDrawAttributes,
funcBType,
funcBTableValues,
funcBSlope,
funcBIntercept,
funcBAmplitude,
funcBExponent,
ColorMatrixType (..),
colorMatrixDrawAttributes,
colorMatrixFilterAttr,
colorMatrixIn,
colorMatrixType,
colorMatrixValues,
ColorMatrix (..),
compositeDrawAttributes,
compositeFilterAttr,
compositeIn,
compositeIn2,
compositeOperator,
compositeK1,
compositeK2,
compositeK3,
compositeK4,
Composite (..),
CompositeOperator (..),
EdgeMode (..),
gaussianBlurDrawAttributes,
gaussianBlurFilterAttr,
gaussianBlurIn,
gaussianBlurStdDeviationX,
gaussianBlurStdDeviationY,
gaussianBlurEdgeMode,
GaussianBlur (..),
turbulenceDrawAttributes,
turbulenceFilterAttr,
turbulenceBaseFrequency,
turbulenceNumOctaves,
turbulenceSeed,
turbulenceStitchTiles,
turbulenceType,
Turbulence (..),
TurbulenceType (..),
StitchTiles (..),
DisplacementMap (..),
displacementMapDrawAttributes,
displacementMapFilterAttr,
displacementMapIn,
displacementMapIn2,
displacementMapScale,
displacementMapXChannelSelector,
displacementMapYChannelSelector,
ChannelSelector (..),
Rectangle (..),
rectangleDrawAttributes,
rectUpperLeftCorner,
rectWidth,
rectHeight,
rectCornerRadius,
Line (..),
lineDrawAttributes,
linePoint1,
linePoint2,
Polygon (..),
polygonDrawAttributes,
polygonPoints,
PolyLine (..),
polyLineDrawAttributes,
polyLinePoints,
Path (..),
pathDrawAttributes,
pathDefinition,
Circle (..),
circleDrawAttributes,
circleCenter,
circleRadius,
Ellipse (..),
ellipseDrawAttributes,
ellipseCenter,
ellipseXRadius,
ellipseYRadius,
GradientPathCommand (..),
MeshGradientType (..),
MeshGradient (..),
meshGradientDrawAttributes,
meshGradientX,
meshGradientY,
meshGradientType,
meshGradientUnits,
meshGradientTransform,
meshGradientRows,
MeshGradientRow (..),
meshGradientRowPatches,
MeshGradientPatch (..),
meshGradientPatchStops,
Image (..),
imageDrawAttributes,
imageCornerUpperLeft,
imageWidth,
imageHeight,
imageHref,
imageAspectRatio,
Use (..),
useDrawAttributes,
useBase,
useName,
useWidth,
useHeight,
Group (..),
groupDrawAttributes,
groupChildren,
groupViewBox,
groupAspectRatio,
Filter (..),
filterDrawAttributes,
filterSelfAttributes,
filterChildren,
Text (..),
textAdjust,
textRoot,
TextAnchor (..),
textAt,
TextPath (..),
textPathStartOffset,
textPathName,
textPathMethod,
textPathSpacing,
TextPathSpacing (..),
TextPathMethod (..),
TextSpanContent (..),
TextSpan (..),
spanInfo,
spanDrawAttributes,
spanContent,
TextInfo (..),
textInfoX,
textInfoY,
textInfoDX,
textInfoDY,
textInfoRotate,
textInfoLength,
TextAdjust (..),
Marker (..),
Overflow (..),
MarkerOrientation (..),
MarkerUnit (..),
markerDrawAttributes,
markerRefPoint,
markerWidth,
markerHeight,
markerOrient,
markerUnits,
markerViewBox,
markerOverflow,
markerAspectRatio,
markerElements,
GradientStop (..),
gradientOffset,
gradientColor,
gradientPath,
gradientOpacity,
LinearGradient (..),
linearGradientDrawAttributes,
linearGradientUnits,
linearGradientStart,
linearGradientStop,
linearGradientSpread,
linearGradientTransform,
linearGradientStops,
RadialGradient (..),
radialGradientDrawAttributes,
radialGradientUnits,
radialGradientCenter,
radialGradientRadius,
radialGradientFocusX,
radialGradientFocusY,
radialGradientSpread,
radialGradientTransform,
radialGradientStops,
Pattern (..),
patternDrawAttributes,
patternViewBox,
patternWidth,
patternHeight,
patternPos,
patternHref,
patternElements,
patternUnit,
patternAspectRatio,
patternTransform,
Mask (..),
maskDrawAttributes,
maskContentUnits,
maskUnits,
maskPosition,
maskWidth,
maskHeight,
maskContent,
ClipPath (..),
clipPathDrawAttributes,
clipPathUnits,
clipPathContent,
PreserveAspectRatio (..),
Alignment (..),
MeetSlice (..),
aspectRatioDefer,
aspectRatioAlign,
aspectRatioMeetSlice,
nameOfTree,
toUserUnit,
mapNumber,
)
where
import Codec.Picture (PixelRGBA8 (..))
import Control.Lens.TH (makeClassy, makeLenses)
import Data.Function (on)
import Data.Monoid (Last (..))
import qualified Data.Text as T
import GHC.Generics (Generic)
import Graphics.SvgTree.CssTypes
( Dpi,
Number (..),
mapNumber,
serializeNumber,
toUserUnit,
)
import Graphics.SvgTree.Misc (ppD)
import Graphics.SvgTree.Types.Basic
import Text.Printf (printf)
data PathCommand
=
MoveTo !Origin ![RPoint]
|
LineTo !Origin ![RPoint]
|
HorizontalTo !Origin ![Coord]
|
VerticalTo !Origin ![Coord]
|
CurveTo !Origin ![(RPoint, RPoint, RPoint)]
|
SmoothCurveTo !Origin ![(RPoint, RPoint)]
|
QuadraticBezier !Origin ![(RPoint, RPoint)]
|
SmoothQuadraticBezierCurveTo !Origin ![RPoint]
|
EllipticalArc !Origin ![(Coord, Coord, Coord, Bool, Bool, RPoint)]
|
EndPath
deriving (Eq, Show, Generic)
data GradientPathCommand
=
GLine !Origin !(Maybe RPoint)
|
GCurve !Origin !RPoint !RPoint !(Maybe RPoint)
|
GClose
deriving (Eq, Show, Generic)
data PreserveAspectRatio = PreserveAspectRatio
{ _aspectRatioDefer :: !Bool,
_aspectRatioAlign :: !Alignment,
_aspectRatioMeetSlice :: !(Maybe MeetSlice)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg PreserveAspectRatio where
defaultSvg =
PreserveAspectRatio
{ _aspectRatioDefer = False,
_aspectRatioAlign = AlignxMidYMid,
_aspectRatioMeetSlice = Nothing
}
data Transformation
=
TransformMatrix
!Coord
!Coord
!Coord
!Coord
!Coord
!Coord
|
Translate !Double !Double
|
Scale !Double !(Maybe Double)
|
Rotate !Double !(Maybe (Double, Double))
|
SkewX !Double
|
SkewY !Double
|
TransformUnknown
deriving (Eq, Show, Generic)
serializeTransformation :: Transformation -> String
serializeTransformation t = case t of
TransformUnknown -> ""
TransformMatrix a b c d e f ->
printf
"matrix(%s, %s, %s, %s, %s, %s)"
(ppD a)
(ppD b)
(ppD c)
(ppD d)
(ppD e)
(ppD f)
Translate x y -> printf "translate(%s, %s)" (ppD x) (ppD y)
Scale x Nothing -> printf "scale(%s)" (ppD x)
Scale x (Just y) -> printf "scale(%s, %s)" (ppD x) (ppD y)
Rotate angle Nothing -> printf "rotate(%s)" (ppD angle)
Rotate angle (Just (x, y)) ->
printf
"rotate(%s, %s, %s)"
(ppD angle)
(ppD x)
(ppD y)
SkewX x -> printf "skewX(%s)" (ppD x)
SkewY y -> printf "skewY(%s)" (ppD y)
serializeTransformations :: [Transformation] -> String
serializeTransformations =
unwords . fmap serializeTransformation
class WithDefaultSvg a where
defaultSvg :: a
data FontStyle
= FontStyleNormal
| FontStyleItalic
| FontStyleOblique
deriving (Eq, Show, Generic)
data TextAnchor
=
TextAnchorStart
|
TextAnchorMiddle
|
TextAnchorEnd
deriving (Eq, Show, Generic)
data ElementRef
=
RefNone
|
Ref String
deriving (Eq, Show, Generic)
data FilterSource
= SourceGraphic
| SourceAlpha
| BackgroundImage
| BackgroundAlpha
| FillPaint
| StrokePaint
| SourceRef String
deriving (Eq, Show, Generic)
data FilterAttributes = FilterAttributes
{ _filterHeight :: !(Last Number),
_filterResult :: !(Maybe String),
_filterWidth :: !(Last Number),
_filterX :: !(Last Number),
_filterY :: !(Last Number)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg FilterAttributes where
defaultSvg =
FilterAttributes
{ _filterHeight = Last Nothing,
_filterResult = Nothing,
_filterWidth = Last Nothing,
_filterX = Last Nothing,
_filterY = Last Nothing
}
data DrawAttributes = DrawAttributes
{
_strokeWidth :: !(Last Number),
_strokeColor :: !(Last Texture),
_strokeOpacity :: !(Maybe Float),
_strokeLineCap :: !(Last Cap),
_strokeLineJoin :: !(Last LineJoin),
_strokeMiterLimit :: !(Last Double),
_fillColor :: !(Last Texture),
_fillOpacity :: !(Maybe Float),
_groupOpacity :: !(Maybe Float),
_transform :: !(Maybe [Transformation]),
_fillRule :: !(Last FillRule),
_maskRef :: !(Last ElementRef),
_clipPathRef :: !(Last ElementRef),
_clipRule :: !(Last FillRule),
_attrClass :: ![T.Text],
_attrId :: !(Maybe String),
_strokeOffset :: !(Last Number),
_strokeDashArray :: !(Last [Number]),
_fontSize :: !(Last Number),
_fontFamily :: !(Last [String]),
_fontStyle :: !(Last FontStyle),
_textAnchor :: !(Last TextAnchor),
_markerStart :: !(Last ElementRef),
_markerMid :: !(Last ElementRef),
_markerEnd :: !(Last ElementRef),
_filterRef :: !(Last ElementRef)
}
deriving (Eq, Show, Generic)
makeClassy ''DrawAttributes
data PolyLine = PolyLine
{ _polyLineDrawAttributes :: DrawAttributes,
_polyLinePoints :: [RPoint]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg PolyLine where
defaultSvg = PolyLine mempty mempty
data Polygon = Polygon
{ _polygonDrawAttributes :: DrawAttributes,
_polygonPoints :: [RPoint]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Polygon where
defaultSvg = Polygon mempty mempty
data Line = Line
{ _lineDrawAttributes :: DrawAttributes,
_linePoint1 :: !Point,
_linePoint2 :: !Point
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Line where
defaultSvg =
Line
{ _lineDrawAttributes = mempty,
_linePoint1 = zeroPoint,
_linePoint2 = zeroPoint
}
where
zeroPoint = (Num 0, Num 0)
data Rectangle = Rectangle
{ _rectangleDrawAttributes :: DrawAttributes,
_rectUpperLeftCorner :: !Point,
_rectWidth :: !(Maybe Number),
_rectHeight :: !(Maybe Number),
_rectCornerRadius :: !(Maybe Number, Maybe Number)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Rectangle where
defaultSvg =
Rectangle
{ _rectangleDrawAttributes = mempty,
_rectUpperLeftCorner = (Num 0, Num 0),
_rectWidth = Nothing,
_rectHeight = Nothing,
_rectCornerRadius = (Nothing, Nothing)
}
data Path = Path
{ _pathDrawAttributes :: DrawAttributes,
_pathDefinition :: [PathCommand]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Path where
defaultSvg = Path mempty mempty
data Group = Group
{ _groupDrawAttributes :: DrawAttributes,
_groupChildren :: ![Tree],
_groupViewBox :: !(Maybe (Double, Double, Double, Double)),
_groupAspectRatio :: !PreserveAspectRatio
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Group where
defaultSvg =
Group
{ _groupDrawAttributes = mempty,
_groupChildren = [],
_groupViewBox = Nothing,
_groupAspectRatio = defaultSvg
}
data Filter = Filter
{ _filterDrawAttributes :: DrawAttributes,
_filterSelfAttributes :: !FilterAttributes,
_filterChildren :: ![FilterElement]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Filter where
defaultSvg =
Filter
{ _filterDrawAttributes = mempty,
_filterSelfAttributes = defaultSvg,
_filterChildren = []
}
data Circle = Circle
{ _circleDrawAttributes :: DrawAttributes,
_circleCenter :: !Point,
_circleRadius :: !Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Circle where
defaultSvg =
Circle
{ _circleDrawAttributes = mempty,
_circleCenter = (Num 0, Num 0),
_circleRadius = Num 0
}
data Ellipse = Ellipse
{ _ellipseDrawAttributes :: DrawAttributes,
_ellipseCenter :: !Point,
_ellipseXRadius :: !Number,
_ellipseYRadius :: !Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Ellipse where
defaultSvg =
Ellipse
{ _ellipseDrawAttributes = mempty,
_ellipseCenter = (Num 0, Num 0),
_ellipseXRadius = Num 0,
_ellipseYRadius = Num 0
}
data GradientStop = GradientStop
{
_gradientOffset :: !Float,
_gradientColor :: !PixelRGBA8,
_gradientPath :: !(Maybe GradientPathCommand),
_gradientOpacity :: !(Maybe Float)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg GradientStop where
defaultSvg =
GradientStop
{ _gradientOffset = 0.0,
_gradientColor = PixelRGBA8 0 0 0 255,
_gradientPath = Nothing,
_gradientOpacity = Nothing
}
data MeshGradientPatch = MeshGradientPatch
{
_meshGradientPatchStops :: ![GradientStop]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg MeshGradientPatch where
defaultSvg = MeshGradientPatch []
data MeshGradientRow = MeshGradientRow
{
_meshGradientRowPatches :: ![MeshGradientPatch]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg MeshGradientRow where
defaultSvg = MeshGradientRow []
data MeshGradient = MeshGradient
{ _meshGradientDrawAttributes :: DrawAttributes,
_meshGradientX :: !Number,
_meshGradientY :: !Number,
_meshGradientType :: !MeshGradientType,
_meshGradientUnits :: !CoordinateUnits,
_meshGradientTransform :: ![Transformation],
_meshGradientRows :: ![MeshGradientRow]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg MeshGradient where
defaultSvg =
MeshGradient
{ _meshGradientDrawAttributes = mempty,
_meshGradientX = Percent 0,
_meshGradientY = Percent 0,
_meshGradientType = GradientBilinear,
_meshGradientUnits = CoordBoundingBox,
_meshGradientTransform = mempty,
_meshGradientRows = mempty
}
data Image = Image
{ _imageDrawAttributes :: DrawAttributes,
_imageCornerUpperLeft :: !Point,
_imageWidth :: !Number,
_imageHeight :: !Number,
_imageHref :: !String,
_imageAspectRatio :: !PreserveAspectRatio
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Image where
defaultSvg =
Image
{ _imageDrawAttributes = mempty,
_imageCornerUpperLeft = (Num 0, Num 0),
_imageWidth = Num 0,
_imageHeight = Num 0,
_imageHref = "",
_imageAspectRatio = defaultSvg
}
data Use = Use
{ _useDrawAttributes :: DrawAttributes,
_useBase :: Point,
_useName :: String,
_useWidth :: Maybe Number,
_useHeight :: Maybe Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Use where
defaultSvg =
Use
{ _useDrawAttributes = mempty,
_useBase = (Num 0, Num 0),
_useName = "",
_useWidth = Nothing,
_useHeight = Nothing
}
data TextInfo = TextInfo
{
_textInfoX :: ![Number],
_textInfoY :: ![Number],
_textInfoDX :: ![Number],
_textInfoDY :: ![Number],
_textInfoRotate :: ![Double],
_textInfoLength :: !(Maybe Number)
}
deriving (Eq, Show, Generic)
instance Semigroup TextInfo where
(<>)
(TextInfo x1 y1 dx1 dy1 r1 l1)
(TextInfo x2 y2 dx2 dy2 r2 l2) =
TextInfo
(x1 <> x2)
(y1 <> y2)
(dx1 <> dx2)
(dy1 <> dy2)
(r1 <> r2)
(getLast $ Last l1 <> Last l2)
instance Monoid TextInfo where
mempty = TextInfo [] [] [] [] [] Nothing
mappend = (<>)
instance WithDefaultSvg TextInfo where
defaultSvg = mempty
data TextSpanContent
=
SpanText !T.Text
|
SpanTextRef !String
|
SpanSub !TextSpan
deriving (Eq, Show, Generic)
data TextSpan = TextSpan
{
_spanInfo :: !TextInfo,
_spanDrawAttributes :: !DrawAttributes,
_spanContent :: ![TextSpanContent]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg TextSpan where
defaultSvg =
TextSpan
{ _spanInfo = defaultSvg,
_spanDrawAttributes = mempty,
_spanContent = mempty
}
data TextPathMethod
=
TextPathAlign
|
TextPathStretch
deriving (Eq, Show, Generic)
data TextPathSpacing
=
TextPathSpacingExact
|
TextPathSpacingAuto
deriving (Eq, Show, Generic)
data TextPath = TextPath
{
_textPathStartOffset :: !Number,
_textPathName :: !String,
_textPathMethod :: !TextPathMethod,
_textPathSpacing :: !TextPathSpacing
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg TextPath where
defaultSvg =
TextPath
{ _textPathStartOffset = Num 0,
_textPathName = mempty,
_textPathMethod = TextPathAlign,
_textPathSpacing = TextPathSpacingExact
}
data TextAdjust
=
TextAdjustSpacing
|
TextAdjustSpacingAndGlyphs
deriving (Eq, Show, Generic)
data Text = Text
{
_textAdjust :: !TextAdjust,
_textRoot :: !TextSpan
}
deriving (Eq, Show, Generic)
textAt :: Point -> T.Text -> Text
textAt (x, y) txt = Text TextAdjustSpacing tspan
where
tspan =
defaultSvg
{ _spanContent = [SpanText txt],
_spanInfo =
defaultSvg
{ _textInfoX = [x],
_textInfoY = [y]
}
}
instance WithDefaultSvg Text where
defaultSvg =
Text
{ _textRoot = defaultSvg,
_textAdjust = TextAdjustSpacing
}
data Tree = CachedTree
{ _treeBranch :: TreeBranch,
_treeHash :: Int
}
deriving (Eq, Show, Generic)
data TreeBranch
= NoNode
| UseNode
{ useInformation :: !Use,
useSubTree :: !(Maybe Tree)
}
| GroupNode !Group
| SymbolNode !Group
| DefinitionNode !Group
| FilterNode !Filter
| PathNode !Path
| CircleNode !Circle
| PolyLineNode !PolyLine
| PolygonNode !Polygon
| EllipseNode !Ellipse
| LineNode !Line
| RectangleNode !Rectangle
| TextNode !(Maybe TextPath) !Text
| ImageNode !Image
| LinearGradientNode !LinearGradient
| RadialGradientNode !RadialGradient
| MeshGradientNode !MeshGradient
| PatternNode !Pattern
| MarkerNode !Marker
| MaskNode !Mask
| ClipPathNode !ClipPath
| SvgNode !Document
deriving (Eq, Show, Generic)
instance WithDefaultSvg TreeBranch where
defaultSvg = NoNode
data FilterElement
= FEBlend Blend
| FEColorMatrix ColorMatrix
| FEComponentTransfer ComponentTransfer
| FEComposite Composite
| FEConvolveMatrix ConvolveMatrix
| FEDiffuseLighting DiffuseLighting
| FEDisplacementMap DisplacementMap
| FEDropShadow DropShadow
| FEFlood Flood
| FEFuncA FuncA
| FEFuncB FuncB
| FEFuncG FuncG
| FEFuncR FuncR
| FEGaussianBlur GaussianBlur
| FEImage ImageF
| FEMerge Merge
| FEMergeNode MergeNode
| FEMorphology Morphology
| FEOffset Offset
| FESpecularLighting SpecularLighting
| FETile Tile
| FETurbulence Turbulence
| FENone
deriving (Eq, Show, Generic)
instance WithDefaultSvg FilterElement where
defaultSvg = FENone
data SpecularLighting = SpecularLighting
{ _specLightingDrawAttributes :: DrawAttributes,
_specLightingFilterAttr :: !FilterAttributes,
_specLightingIn :: !(Last FilterSource),
_specLightingSurfaceScale :: Double,
_specLightingSpecularConst :: Double,
_specLightingSpecularExp :: Double,
_specLightingKernelUnitLength :: NumberOptionalNumber
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg SpecularLighting where
defaultSvg =
SpecularLighting
{ _specLightingDrawAttributes = defaultSvg,
_specLightingFilterAttr = defaultSvg,
_specLightingIn = Last Nothing,
_specLightingSurfaceScale = 1,
_specLightingSpecularConst = 1,
_specLightingSpecularExp = 1,
_specLightingKernelUnitLength = Num1 0
}
data ConvolveMatrix = ConvolveMatrix
{ _convolveMatrixDrawAttributes :: DrawAttributes,
_convolveMatrixFilterAttr :: !FilterAttributes,
_convolveMatrixIn :: !(Last FilterSource),
_convolveMatrixOrder :: NumberOptionalNumber,
_convolveMatrixKernelMatrix :: [Double],
_convolveMatrixDivisor :: Double,
_convolveMatrixBias :: Double,
_convolveMatrixTargetX :: Int,
_convolveMatrixTargetY :: Int,
_convolveMatrixEdgeMode :: EdgeMode,
_convolveMatrixKernelUnitLength :: NumberOptionalNumber,
_convolveMatrixPreserveAlpha :: Bool
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg ConvolveMatrix where
defaultSvg =
ConvolveMatrix
{ _convolveMatrixDrawAttributes = defaultSvg,
_convolveMatrixFilterAttr = defaultSvg,
_convolveMatrixIn = Last Nothing,
_convolveMatrixOrder = Num1 3,
_convolveMatrixKernelMatrix = [],
_convolveMatrixDivisor = 1,
_convolveMatrixBias = 0,
_convolveMatrixTargetX = 1,
_convolveMatrixTargetY = 1,
_convolveMatrixEdgeMode = EdgeDuplicate,
_convolveMatrixKernelUnitLength = Num1 0,
_convolveMatrixPreserveAlpha = False
}
data DiffuseLighting = DiffuseLighting
{ _diffuseLightingDrawAttributes :: DrawAttributes,
_diffuseLightingFilterAttr :: !FilterAttributes,
_diffuseLightingIn :: !(Last FilterSource),
_diffuseLightingSurfaceScale :: Double,
_diffuseLightingDiffuseConst :: Double,
_diffuseLightingKernelUnitLength :: NumberOptionalNumber
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg DiffuseLighting where
defaultSvg =
DiffuseLighting
{ _diffuseLightingDrawAttributes = defaultSvg,
_diffuseLightingFilterAttr = defaultSvg,
_diffuseLightingIn = Last Nothing,
_diffuseLightingSurfaceScale = 1,
_diffuseLightingDiffuseConst = 1,
_diffuseLightingKernelUnitLength = Num1 0
}
data Morphology = Morphology
{ _morphologyDrawAttributes :: DrawAttributes,
_morphologyFilterAttr :: !FilterAttributes,
_morphologyIn :: !(Last FilterSource),
_morphologyOperator :: OperatorType,
_morphologyRadius :: NumberOptionalNumber
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Morphology where
defaultSvg =
Morphology
{ _morphologyDrawAttributes = defaultSvg,
_morphologyFilterAttr = defaultSvg,
_morphologyIn = Last Nothing,
_morphologyOperator = OperatorOver,
_morphologyRadius = Num1 0
}
data DropShadow = DropShadow
{ _dropShadowDrawAttributes :: DrawAttributes,
_dropShadowFilterAttr :: !FilterAttributes,
_dropShadowDx :: Double,
_dropShadowDy :: Double,
_dropShadowStdDeviation :: NumberOptionalNumber
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg DropShadow where
defaultSvg =
DropShadow
{ _dropShadowDrawAttributes = defaultSvg,
_dropShadowFilterAttr = defaultSvg,
_dropShadowDx = 2,
_dropShadowDy = 2,
_dropShadowStdDeviation = Num1 0
}
data OperatorType
= OperatorOver
| OperatorIn
| OperatorOut
| OperatorAtop
| OperatorXor
| OperatorLighter
| OperatorArithmetic
deriving (Eq, Show, Generic)
data NumberOptionalNumber
= Num1 Double
| Num2 Double Double
deriving (Eq, Show, Generic)
data ImageF = ImageF
{ _imageFDrawAttributes :: DrawAttributes,
_imageFFilterAttr :: !FilterAttributes,
_imageFHref :: !String,
_imageFAspectRatio :: !PreserveAspectRatio
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg ImageF where
defaultSvg =
ImageF
{ _imageFDrawAttributes = defaultSvg,
_imageFFilterAttr = defaultSvg,
_imageFHref = "",
_imageFAspectRatio = defaultSvg
}
data TransferFunctionType
= TFIdentity
| TFTable
| TFDiscrete
| TFLinear
| TFGamma
deriving (Eq, Show, Generic)
data TransferFunction = TransferFunction
{ _transferFunctionDrawAttributes :: !DrawAttributes,
_transferFunctionFilterAttr :: !FilterAttributes,
_transferFunctionType :: TransferFunctionType,
_transferFunctionTableValues :: [Double],
_transferFunctionSlope :: Double,
_transferFunctionIntercept :: Double,
_transferFunctionAmplitude :: Double,
_transferFunctionExponent :: Double,
_transferFunctionOffset :: Double
}
deriving (Eq, Show, Generic)
data ChannelSelector
= ChannelR
| ChannelG
| ChannelB
| ChannelA
deriving (Eq, Show, Generic)
data DisplacementMap = DisplacementMap
{ _displacementMapDrawAttributes :: !DrawAttributes,
_displacementMapFilterAttr :: !FilterAttributes,
_displacementMapIn :: !(Last FilterSource),
_displacementMapIn2 :: !(Last FilterSource),
_displacementMapScale :: !(Last Double),
_displacementMapXChannelSelector :: ChannelSelector,
_displacementMapYChannelSelector :: ChannelSelector
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg DisplacementMap where
defaultSvg =
DisplacementMap
{ _displacementMapDrawAttributes = defaultSvg,
_displacementMapFilterAttr = defaultSvg,
_displacementMapIn = Last Nothing,
_displacementMapIn2 = Last Nothing,
_displacementMapScale = Last Nothing,
_displacementMapXChannelSelector = ChannelA,
_displacementMapYChannelSelector = ChannelA
}
data BlendMode
= Normal
| Multiply
| Screen
| Overlay
| Darken
| Lighten
| ColorDodge
| ColorBurn
| HardLight
| SoftLight
| Difference
| Exclusion
| Hue
| Saturation
| Color
| Luminosity
deriving (Eq, Show, Generic)
data Blend = Blend
{ _blendDrawAttributes :: !DrawAttributes,
_blendFilterAttr :: !FilterAttributes,
_blendIn :: !(Last FilterSource),
_blendIn2 :: !(Last FilterSource),
_blendMode :: !BlendMode
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Blend where
defaultSvg =
Blend
{ _blendDrawAttributes = defaultSvg,
_blendFilterAttr = defaultSvg,
_blendIn = Last Nothing,
_blendIn2 = Last Nothing,
_blendMode = Normal
}
data Flood = Flood
{ _floodDrawAttributes :: !DrawAttributes,
_floodFilterAttr :: !FilterAttributes,
_floodColor :: !PixelRGBA8,
_floodOpacity :: !(Maybe Double)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Flood where
defaultSvg =
Flood
{ _floodDrawAttributes = defaultSvg,
_floodFilterAttr = defaultSvg,
_floodColor = PixelRGBA8 0 0 0 255,
_floodOpacity = Just 1.0
}
data Offset = Offset
{ _offsetDrawAttributes :: !DrawAttributes,
_offsetFilterAttr :: !FilterAttributes,
_offsetIn :: !(Last FilterSource),
_offsetDX :: !Number,
_offsetDY :: !Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Offset where
defaultSvg =
Offset
{ _offsetDrawAttributes = defaultSvg,
_offsetFilterAttr = defaultSvg,
_offsetIn = Last Nothing,
_offsetDX = Num 0,
_offsetDY = Num 0
}
data Tile = Tile
{ _tileDrawAttributes :: !DrawAttributes,
_tileFilterAttr :: !FilterAttributes,
_tileIn :: !(Last FilterSource)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Tile where
defaultSvg =
Tile
{ _tileDrawAttributes = defaultSvg,
_tileFilterAttr = defaultSvg,
_tileIn = Last Nothing
}
data Merge = Merge
{ _mergeDrawAttributes :: !DrawAttributes,
_mergeFilterAttributes :: !FilterAttributes,
_mergeChildren :: ![FilterElement]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Merge where
defaultSvg =
Merge
{ _mergeDrawAttributes = defaultSvg,
_mergeFilterAttributes = defaultSvg,
_mergeChildren = []
}
data MergeNode = MergeNode
{ _mergeNodeDrawAttributes :: !DrawAttributes,
_mergeNodeIn :: !(Last FilterSource)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg MergeNode where
defaultSvg =
MergeNode
{ _mergeNodeDrawAttributes = defaultSvg,
_mergeNodeIn = Last Nothing
}
data ComponentTransfer = ComponentTransfer
{ _compTransferDrawAttributes :: !DrawAttributes,
_compTransferFilterAttr :: !FilterAttributes,
_compTransferChildren :: ![FilterElement],
_compTransferIn :: !(Last FilterSource)
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg ComponentTransfer where
defaultSvg =
ComponentTransfer
{ _compTransferDrawAttributes = defaultSvg,
_compTransferFilterAttr = defaultSvg,
_compTransferChildren = [],
_compTransferIn = Last Nothing
}
data FuncType
= FIdentity
| FTable
| FDiscrete
| FLinear
| FGamma
deriving (Eq, Show, Generic)
data FuncA = FuncA
{ _funcADrawAttributes :: !DrawAttributes,
_funcAType :: !FuncType,
_funcATableValues :: ![Number],
_funcASlope :: !Number,
_funcAIntercept :: !Number,
_funcAAmplitude :: !Number,
_funcAExponent :: !Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg FuncA where
defaultSvg =
FuncA
{ _funcADrawAttributes = defaultSvg,
_funcAType = FIdentity,
_funcATableValues = [],
_funcASlope = Num 0,
_funcAIntercept = Num 0,
_funcAAmplitude = Num 1,
_funcAExponent = Num 1
}
data FuncR = FuncR
{ _funcRDrawAttributes :: !DrawAttributes,
_funcRType :: !FuncType,
_funcRTableValues :: ![Number],
_funcRSlope :: !Number,
_funcRIntercept :: !Number,
_funcRAmplitude :: !Number,
_funcRExponent :: !Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg FuncR where
defaultSvg =
FuncR
{ _funcRDrawAttributes = defaultSvg,
_funcRType = FIdentity,
_funcRTableValues = [],
_funcRSlope = Num 0,
_funcRIntercept = Num 0,
_funcRAmplitude = Num 1,
_funcRExponent = Num 1
}
data FuncG = FuncG
{ _funcGDrawAttributes :: !DrawAttributes,
_funcGType :: !FuncType,
_funcGTableValues :: ![Number],
_funcGSlope :: !Number,
_funcGIntercept :: !Number,
_funcGAmplitude :: !Number,
_funcGExponent :: !Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg FuncG where
defaultSvg =
FuncG
{ _funcGDrawAttributes = defaultSvg,
_funcGType = FIdentity,
_funcGTableValues = [],
_funcGSlope = Num 0,
_funcGIntercept = Num 0,
_funcGAmplitude = Num 1,
_funcGExponent = Num 1
}
data FuncB = FuncB
{ _funcBDrawAttributes :: !DrawAttributes,
_funcBType :: !FuncType,
_funcBTableValues :: ![Number],
_funcBSlope :: !Number,
_funcBIntercept :: !Number,
_funcBAmplitude :: !Number,
_funcBExponent :: !Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg FuncB where
defaultSvg =
FuncB
{ _funcBDrawAttributes = defaultSvg,
_funcBType = FIdentity,
_funcBTableValues = [],
_funcBSlope = Num 0,
_funcBIntercept = Num 0,
_funcBAmplitude = Num 1,
_funcBExponent = Num 1
}
data ColorMatrixType
= Matrix
| Saturate
| HueRotate
| LuminanceToAlpha
deriving (Eq, Show, Generic)
data ColorMatrix = ColorMatrix
{ _colorMatrixDrawAttributes :: !DrawAttributes,
_colorMatrixFilterAttr :: !FilterAttributes,
_colorMatrixIn :: !(Last FilterSource),
_colorMatrixType :: !ColorMatrixType,
_colorMatrixValues :: !String
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg ColorMatrix where
defaultSvg =
ColorMatrix
{ _colorMatrixDrawAttributes = defaultSvg,
_colorMatrixFilterAttr = defaultSvg,
_colorMatrixIn = Last Nothing,
_colorMatrixType = Matrix,
_colorMatrixValues = ""
}
data CompositeOperator
= CompositeOver
| CompositeIn
| CompositeOut
| CompositeAtop
| CompositeXor
| CompositeArithmetic
deriving (Eq, Show, Generic)
data Composite = Composite
{ _compositeDrawAttributes :: DrawAttributes,
_compositeFilterAttr :: !FilterAttributes,
_compositeIn :: Last FilterSource,
_compositeIn2 :: Last FilterSource,
_compositeOperator :: CompositeOperator,
_compositeK1 :: Number,
_compositeK2 :: Number,
_compositeK3 :: Number,
_compositeK4 :: Number
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Composite where
defaultSvg =
Composite
{ _compositeDrawAttributes = defaultSvg,
_compositeFilterAttr = defaultSvg,
_compositeIn = Last Nothing,
_compositeIn2 = Last Nothing,
_compositeOperator = CompositeOver,
_compositeK1 = Num 0,
_compositeK2 = Num 0,
_compositeK3 = Num 0,
_compositeK4 = Num 0
}
data Turbulence = Turbulence
{ _turbulenceDrawAttributes :: !DrawAttributes,
_turbulenceFilterAttr :: !FilterAttributes,
_turbulenceBaseFrequency :: !(Double, Last Double),
_turbulenceNumOctaves :: Int,
_turbulenceSeed :: Double,
_turbulenceStitchTiles :: StitchTiles,
_turbulenceType :: TurbulenceType
}
deriving (Eq, Show, Generic)
data StitchTiles
= NoStitch
| Stitch
deriving (Eq, Show, Generic)
data TurbulenceType
= FractalNoiseType
| TurbulenceType
deriving (Eq, Show, Generic)
instance WithDefaultSvg Turbulence where
defaultSvg =
Turbulence
{ _turbulenceDrawAttributes = defaultSvg,
_turbulenceFilterAttr = defaultSvg,
_turbulenceBaseFrequency = (0, Last Nothing),
_turbulenceNumOctaves = 1,
_turbulenceSeed = 0,
_turbulenceStitchTiles = NoStitch,
_turbulenceType = TurbulenceType
}
data EdgeMode
= EdgeDuplicate
| EdgeWrap
| EdgeNone
deriving (Eq, Show, Generic)
data GaussianBlur = GaussianBlur
{ _gaussianBlurDrawAttributes :: DrawAttributes,
_gaussianBlurFilterAttr :: !FilterAttributes,
_gaussianBlurIn :: Last FilterSource,
_gaussianBlurStdDeviationX :: Number,
_gaussianBlurStdDeviationY :: Last Number,
_gaussianBlurEdgeMode :: EdgeMode
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg GaussianBlur where
defaultSvg =
GaussianBlur
{ _gaussianBlurDrawAttributes = defaultSvg,
_gaussianBlurFilterAttr = defaultSvg,
_gaussianBlurIn = Last Nothing,
_gaussianBlurStdDeviationX = Num 0,
_gaussianBlurStdDeviationY = Last Nothing,
_gaussianBlurEdgeMode = EdgeDuplicate
}
data MarkerOrientation
=
OrientationAuto
|
OrientationAngle Coord
deriving (Eq, Show, Generic)
data MarkerUnit
=
MarkerUnitStrokeWidth
|
MarkerUnitUserSpaceOnUse
deriving (Eq, Show, Generic)
data Overflow
=
OverflowVisible
|
OverflowHidden
deriving (Eq, Show, Generic)
data Marker = Marker
{ _markerDrawAttributes :: DrawAttributes,
_markerRefPoint :: !(Number, Number),
_markerWidth :: !(Maybe Number),
_markerHeight :: !(Maybe Number),
_markerOrient :: !(Maybe MarkerOrientation),
_markerUnits :: !(Maybe MarkerUnit),
_markerViewBox :: !(Maybe (Double, Double, Double, Double)),
_markerOverflow :: !(Maybe Overflow),
_markerAspectRatio :: !PreserveAspectRatio,
_markerElements :: [Tree]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Marker where
defaultSvg =
Marker
{ _markerDrawAttributes = mempty,
_markerRefPoint = (Num 0, Num 0),
_markerWidth = Just (Num 3),
_markerHeight = Just (Num 3),
_markerOrient = Nothing,
_markerUnits = Nothing,
_markerViewBox = Nothing,
_markerOverflow = Nothing,
_markerElements = mempty,
_markerAspectRatio = defaultSvg
}
nameOfTree :: Tree -> T.Text
nameOfTree v =
case _treeBranch v of
NoNode -> ""
UseNode _ _ -> "use"
GroupNode _ -> "g"
SymbolNode _ -> "symbol"
DefinitionNode _ -> "defs"
FilterNode _ -> "filter"
PathNode _ -> "path"
CircleNode _ -> "circle"
PolyLineNode _ -> "polyline"
PolygonNode _ -> "polygon"
EllipseNode _ -> "ellipse"
LineNode _ -> "line"
RectangleNode _ -> "rectangle"
TextNode _ _ -> "text"
ImageNode _ -> "image"
LinearGradientNode _ -> "lineargradient"
RadialGradientNode _ -> "radialgradient"
MeshGradientNode _ -> "meshgradient"
PatternNode _ -> "pattern"
MarkerNode _ -> "marker"
MaskNode _ -> "mask"
ClipPathNode _ -> "clipPath"
SvgNode {} -> "svg"
data Spread
=
SpreadRepeat
|
SpreadPad
|
SpreadReflect
deriving (Eq, Show, Generic)
data LinearGradient = LinearGradient
{ _linearGradientDrawAttributes :: DrawAttributes,
_linearGradientUnits :: CoordinateUnits,
_linearGradientStart :: Point,
_linearGradientStop :: Point,
_linearGradientSpread :: Spread,
_linearGradientTransform :: [Transformation],
_linearGradientStops :: [GradientStop]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg LinearGradient where
defaultSvg =
LinearGradient
{ _linearGradientDrawAttributes = mempty,
_linearGradientUnits = CoordBoundingBox,
_linearGradientStart = (Percent 0, Percent 0),
_linearGradientStop = (Percent 1, Percent 0),
_linearGradientSpread = SpreadPad,
_linearGradientTransform = [],
_linearGradientStops = []
}
data RadialGradient = RadialGradient
{ _radialGradientDrawAttributes :: DrawAttributes,
_radialGradientUnits :: CoordinateUnits,
_radialGradientCenter :: Point,
_radialGradientRadius :: Number,
_radialGradientFocusX :: Maybe Number,
_radialGradientFocusY :: Maybe Number,
_radialGradientSpread :: Spread,
_radialGradientTransform :: [Transformation],
_radialGradientStops :: [GradientStop]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg RadialGradient where
defaultSvg =
RadialGradient
{ _radialGradientDrawAttributes = mempty,
_radialGradientUnits = CoordBoundingBox,
_radialGradientCenter = (Percent 0.5, Percent 0.5),
_radialGradientRadius = Percent 0.5,
_radialGradientFocusX = Nothing,
_radialGradientFocusY = Nothing,
_radialGradientSpread = SpreadPad,
_radialGradientTransform = [],
_radialGradientStops = []
}
data Mask = Mask
{ _maskDrawAttributes :: DrawAttributes,
_maskContentUnits :: CoordinateUnits,
_maskUnits :: CoordinateUnits,
_maskPosition :: Point,
_maskWidth :: Number,
_maskHeight :: Number,
_maskContent :: [Tree]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Mask where
defaultSvg =
Mask
{ _maskDrawAttributes = mempty,
_maskContentUnits = CoordUserSpace,
_maskUnits = CoordBoundingBox,
_maskPosition = (Percent (-0.1), Percent (-0.1)),
_maskWidth = Percent 1.2,
_maskHeight = Percent 1.2,
_maskContent = []
}
data ClipPath = ClipPath
{ _clipPathDrawAttributes :: DrawAttributes,
_clipPathUnits :: CoordinateUnits,
_clipPathContent :: [Tree]
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg ClipPath where
defaultSvg =
ClipPath
{ _clipPathDrawAttributes = mempty,
_clipPathUnits = CoordUserSpace,
_clipPathContent = mempty
}
data Pattern = Pattern
{ _patternDrawAttributes :: DrawAttributes,
_patternViewBox :: !(Maybe (Double, Double, Double, Double)),
_patternWidth :: !Number,
_patternHeight :: !Number,
_patternPos :: !Point,
_patternHref :: !String,
_patternElements :: ![Tree],
_patternUnit :: !CoordinateUnits,
_patternAspectRatio :: !PreserveAspectRatio,
_patternTransform :: !(Maybe [Transformation])
}
deriving (Eq, Show, Generic)
instance WithDefaultSvg Pattern where
defaultSvg =
Pattern
{ _patternDrawAttributes = mempty,
_patternViewBox = Nothing,
_patternWidth = Num 0,
_patternHeight = Num 0,
_patternPos = (Num 0, Num 0),
_patternElements = [],
_patternUnit = CoordBoundingBox,
_patternAspectRatio = defaultSvg,
_patternHref = "",
_patternTransform = mempty
}
data Element
= ElementLinearGradient LinearGradient
| ElementRadialGradient RadialGradient
| ElementMeshGradient MeshGradient
| ElementGeometry Tree
| ElementPattern Pattern
| ElementMarker Marker
| ElementMask Mask
| ElementClipPath ClipPath
deriving (Eq, Show, Generic)
data Document = Document
{ _documentViewBox :: Maybe (Double, Double, Double, Double),
_documentWidth :: Maybe Number,
_documentHeight :: Maybe Number,
_documentElements :: [Tree],
_documentDescription :: String,
_documentLocation :: FilePath,
_documentAspectRatio :: PreserveAspectRatio
}
deriving (Show, Eq, Generic)
documentSize :: Dpi -> Document -> (Int, Int)
documentSize
_
Document
{ _documentViewBox = Just (x1, y1, x2, y2),
_documentWidth = Just (Percent pw),
_documentHeight = Just (Percent ph)
} =
(floor $ dx * pw, floor $ dy * ph)
where
dx = abs $ x2 - x1
dy = abs $ y2 - y1
documentSize
_
Document
{ _documentWidth = Just (Num w),
_documentHeight = Just (Num h)
} = (floor w, floor h)
documentSize
dpi
doc@( Document
{ _documentWidth = Just w,
_documentHeight = Just h
}
) =
documentSize dpi $
doc
{ _documentWidth = Just $ toUserUnit dpi w,
_documentHeight = Just $ toUserUnit dpi h
}
documentSize _ Document {_documentViewBox = Just (x1, y1, x2, y2)} =
(floor . abs $ x2 - x1, floor . abs $ y2 - y1)
documentSize _ _ = (1, 1)
mayMerge :: Monoid a => Maybe a -> Maybe a -> Maybe a
mayMerge (Just a) (Just b) = Just $ mappend a b
mayMerge _ b@(Just _) = b
mayMerge a Nothing = a
instance Semigroup DrawAttributes where
(<>) a b =
DrawAttributes
{ _strokeWidth = (mappend `on` _strokeWidth) a b,
_strokeColor = (mappend `on` _strokeColor) a b,
_strokeLineCap = (mappend `on` _strokeLineCap) a b,
_strokeOpacity = (opacityMappend `on` _strokeOpacity) a b,
_strokeLineJoin = (mappend `on` _strokeLineJoin) a b,
_strokeMiterLimit = (mappend `on` _strokeMiterLimit) a b,
_fillColor = (mappend `on` _fillColor) a b,
_fillOpacity = (opacityMappend `on` _fillOpacity) a b,
_fontSize = (mappend `on` _fontSize) a b,
_transform = (mayMerge `on` _transform) a b,
_fillRule = (mappend `on` _fillRule) a b,
_attrClass = _attrClass b,
_attrId = _attrId b,
_groupOpacity = _groupOpacity b,
_strokeOffset = (mappend `on` _strokeOffset) a b,
_strokeDashArray = (mappend `on` _strokeDashArray) a b,
_fontFamily = (mappend `on` _fontFamily) a b,
_fontStyle = (mappend `on` _fontStyle) a b,
_textAnchor = (mappend `on` _textAnchor) a b,
_maskRef = (mappend `on` _maskRef) a b,
_clipPathRef = (mappend `on` _clipPathRef) a b,
_clipRule = (mappend `on` _clipRule) a b,
_markerStart = (mappend `on` _markerStart) a b,
_markerMid = (mappend `on` _markerMid) a b,
_markerEnd = (mappend `on` _markerEnd) a b,
_filterRef = (mappend `on` _filterRef) a b
}
where
opacityMappend Nothing Nothing = Nothing
opacityMappend (Just v) Nothing = Just v
opacityMappend Nothing (Just v) = Just v
opacityMappend (Just v) (Just v2) = Just $ v * v2
instance Monoid DrawAttributes where
mappend = (<>)
mempty =
DrawAttributes
{ _strokeWidth = Last Nothing,
_strokeColor = Last Nothing,
_strokeOpacity = Nothing,
_strokeLineCap = Last Nothing,
_strokeLineJoin = Last Nothing,
_strokeMiterLimit = Last Nothing,
_fillColor = Last Nothing,
_groupOpacity = Nothing,
_fillOpacity = Nothing,
_fontSize = Last Nothing,
_fontFamily = Last Nothing,
_fontStyle = Last Nothing,
_transform = Nothing,
_fillRule = Last Nothing,
_attrClass = mempty,
_attrId = Nothing,
_strokeOffset = Last Nothing,
_strokeDashArray = Last Nothing,
_textAnchor = Last Nothing,
_maskRef = Last Nothing,
_clipPathRef = Last Nothing,
_clipRule = Last Nothing,
_markerStart = Last Nothing,
_markerMid = Last Nothing,
_markerEnd = Last Nothing,
_filterRef = Last Nothing
}
instance WithDefaultSvg DrawAttributes where
defaultSvg = mempty
makeLenses ''Rectangle
makeLenses ''Pattern
makeLenses ''Document
makeLenses ''Filter
makeLenses ''Line
makeLenses ''Polygon
makeLenses ''PolyLine
makeLenses ''PreserveAspectRatio
makeLenses ''Path
makeLenses ''Circle
makeLenses ''Text
makeLenses ''TextPath
makeLenses ''Ellipse
makeLenses ''MeshGradientPatch
makeLenses ''MeshGradientRow
makeLenses ''MeshGradient
makeLenses ''Image
makeLenses ''Use
makeLenses ''TextSpan
makeLenses ''TextInfo
makeLenses ''Marker
makeLenses ''GradientStop
makeLenses ''LinearGradient
makeLenses ''RadialGradient
makeLenses ''Mask
makeLenses ''ClipPath
makeLenses ''Blend
makeLenses ''Flood
makeLenses ''Tile
makeLenses ''Offset
makeLenses ''ColorMatrix
makeLenses ''Composite
makeLenses ''GaussianBlur
makeLenses ''Turbulence
makeLenses ''DisplacementMap
makeLenses ''Merge
makeLenses ''MergeNode
makeLenses ''Group
makeLenses ''ImageF
makeLenses ''ComponentTransfer
makeLenses ''FuncA
makeLenses ''FuncR
makeLenses ''FuncG
makeLenses ''FuncB
makeLenses ''Morphology
makeLenses ''SpecularLighting
makeLenses ''DropShadow
makeLenses ''DiffuseLighting
makeLenses ''ConvolveMatrix
makeClassy ''FilterAttributes