{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# 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.Applicative ((<|>))
import Control.Lens.TH (makeClassy, makeLenses)
import Data.Function (on)
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 (PathCommand -> PathCommand -> Bool
(PathCommand -> PathCommand -> Bool)
-> (PathCommand -> PathCommand -> Bool) -> Eq PathCommand
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
(Int -> PathCommand -> ShowS)
-> (PathCommand -> String)
-> ([PathCommand] -> ShowS)
-> Show PathCommand
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. PathCommand -> Rep PathCommand x)
-> (forall x. Rep PathCommand x -> PathCommand)
-> Generic PathCommand
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 GradientPathCommand
=
GLine !Origin !(Maybe RPoint)
|
GCurve !Origin !RPoint !RPoint !(Maybe RPoint)
|
GClose
deriving (GradientPathCommand -> GradientPathCommand -> Bool
(GradientPathCommand -> GradientPathCommand -> Bool)
-> (GradientPathCommand -> GradientPathCommand -> Bool)
-> Eq GradientPathCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GradientPathCommand -> GradientPathCommand -> Bool
$c/= :: GradientPathCommand -> GradientPathCommand -> Bool
== :: GradientPathCommand -> GradientPathCommand -> Bool
$c== :: GradientPathCommand -> GradientPathCommand -> Bool
Eq, Int -> GradientPathCommand -> ShowS
[GradientPathCommand] -> ShowS
GradientPathCommand -> String
(Int -> GradientPathCommand -> ShowS)
-> (GradientPathCommand -> String)
-> ([GradientPathCommand] -> ShowS)
-> Show GradientPathCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GradientPathCommand] -> ShowS
$cshowList :: [GradientPathCommand] -> ShowS
show :: GradientPathCommand -> String
$cshow :: GradientPathCommand -> String
showsPrec :: Int -> GradientPathCommand -> ShowS
$cshowsPrec :: Int -> GradientPathCommand -> ShowS
Show, (forall x. GradientPathCommand -> Rep GradientPathCommand x)
-> (forall x. Rep GradientPathCommand x -> GradientPathCommand)
-> Generic GradientPathCommand
forall x. Rep GradientPathCommand x -> GradientPathCommand
forall x. GradientPathCommand -> Rep GradientPathCommand x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GradientPathCommand x -> GradientPathCommand
$cfrom :: forall x. GradientPathCommand -> Rep GradientPathCommand x
Generic)
data PreserveAspectRatio = PreserveAspectRatio
{ PreserveAspectRatio -> Bool
_aspectRatioDefer :: !Bool,
PreserveAspectRatio -> Alignment
_aspectRatioAlign :: !Alignment,
PreserveAspectRatio -> Maybe MeetSlice
_aspectRatioMeetSlice :: !(Maybe MeetSlice)
}
deriving (PreserveAspectRatio -> PreserveAspectRatio -> Bool
(PreserveAspectRatio -> PreserveAspectRatio -> Bool)
-> (PreserveAspectRatio -> PreserveAspectRatio -> Bool)
-> Eq PreserveAspectRatio
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreserveAspectRatio -> PreserveAspectRatio -> Bool
$c/= :: PreserveAspectRatio -> PreserveAspectRatio -> Bool
== :: PreserveAspectRatio -> PreserveAspectRatio -> Bool
$c== :: PreserveAspectRatio -> PreserveAspectRatio -> Bool
Eq, Int -> PreserveAspectRatio -> ShowS
[PreserveAspectRatio] -> ShowS
PreserveAspectRatio -> String
(Int -> PreserveAspectRatio -> ShowS)
-> (PreserveAspectRatio -> String)
-> ([PreserveAspectRatio] -> ShowS)
-> Show PreserveAspectRatio
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PreserveAspectRatio] -> ShowS
$cshowList :: [PreserveAspectRatio] -> ShowS
show :: PreserveAspectRatio -> String
$cshow :: PreserveAspectRatio -> String
showsPrec :: Int -> PreserveAspectRatio -> ShowS
$cshowsPrec :: Int -> PreserveAspectRatio -> ShowS
Show, (forall x. PreserveAspectRatio -> Rep PreserveAspectRatio x)
-> (forall x. Rep PreserveAspectRatio x -> PreserveAspectRatio)
-> Generic PreserveAspectRatio
forall x. Rep PreserveAspectRatio x -> PreserveAspectRatio
forall x. PreserveAspectRatio -> Rep PreserveAspectRatio x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PreserveAspectRatio x -> PreserveAspectRatio
$cfrom :: forall x. PreserveAspectRatio -> Rep PreserveAspectRatio x
Generic)
instance WithDefaultSvg PreserveAspectRatio where
defaultSvg :: PreserveAspectRatio
defaultSvg =
PreserveAspectRatio :: Bool -> Alignment -> Maybe MeetSlice -> PreserveAspectRatio
PreserveAspectRatio
{ _aspectRatioDefer :: Bool
_aspectRatioDefer = Bool
False,
_aspectRatioAlign :: Alignment
_aspectRatioAlign = Alignment
AlignxMidYMid,
_aspectRatioMeetSlice :: Maybe MeetSlice
_aspectRatioMeetSlice = Maybe MeetSlice
forall a. Maybe a
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 (Transformation -> Transformation -> Bool
(Transformation -> Transformation -> Bool)
-> (Transformation -> Transformation -> Bool) -> Eq Transformation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transformation -> Transformation -> Bool
$c/= :: Transformation -> Transformation -> Bool
== :: Transformation -> Transformation -> Bool
$c== :: Transformation -> Transformation -> Bool
Eq, Int -> Transformation -> ShowS
[Transformation] -> ShowS
Transformation -> String
(Int -> Transformation -> ShowS)
-> (Transformation -> String)
-> ([Transformation] -> ShowS)
-> Show Transformation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transformation] -> ShowS
$cshowList :: [Transformation] -> ShowS
show :: Transformation -> String
$cshow :: Transformation -> String
showsPrec :: Int -> Transformation -> ShowS
$cshowsPrec :: Int -> Transformation -> ShowS
Show, (forall x. Transformation -> Rep Transformation x)
-> (forall x. Rep Transformation x -> Transformation)
-> Generic Transformation
forall x. Rep Transformation x -> Transformation
forall x. Transformation -> Rep Transformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Transformation x -> Transformation
$cfrom :: forall x. Transformation -> Rep Transformation x
Generic)
serializeTransformation :: Transformation -> String
serializeTransformation :: Transformation -> String
serializeTransformation Transformation
t = case Transformation
t of
Transformation
TransformUnknown -> String
""
TransformMatrix Coord
a Coord
b Coord
c Coord
d Coord
e Coord
f ->
String -> String -> String -> String -> String -> String -> ShowS
forall r. PrintfType r => String -> r
printf
String
"matrix(%s, %s, %s, %s, %s, %s)"
(Coord -> String
ppD Coord
a)
(Coord -> String
ppD Coord
b)
(Coord -> String
ppD Coord
c)
(Coord -> String
ppD Coord
d)
(Coord -> String
ppD Coord
e)
(Coord -> String
ppD Coord
f)
Translate Coord
x Coord
y -> String -> String -> ShowS
forall r. PrintfType r => String -> r
printf String
"translate(%s, %s)" (Coord -> String
ppD Coord
x) (Coord -> String
ppD Coord
y)
Scale Coord
x Maybe Coord
Nothing -> String -> ShowS
forall r. PrintfType r => String -> r
printf String
"scale(%s)" (Coord -> String
ppD Coord
x)
Scale Coord
x (Just Coord
y) -> String -> String -> ShowS
forall r. PrintfType r => String -> r
printf String
"scale(%s, %s)" (Coord -> String
ppD Coord
x) (Coord -> String
ppD Coord
y)
Rotate Coord
angle Maybe (Coord, Coord)
Nothing -> String -> ShowS
forall r. PrintfType r => String -> r
printf String
"rotate(%s)" (Coord -> String
ppD Coord
angle)
Rotate Coord
angle (Just (Coord
x, Coord
y)) ->
String -> String -> String -> ShowS
forall r. PrintfType r => String -> r
printf
String
"rotate(%s, %s, %s)"
(Coord -> String
ppD Coord
angle)
(Coord -> String
ppD Coord
x)
(Coord -> String
ppD Coord
y)
SkewX Coord
x -> String -> ShowS
forall r. PrintfType r => String -> r
printf String
"skewX(%s)" (Coord -> String
ppD Coord
x)
SkewY Coord
y -> String -> ShowS
forall r. PrintfType r => String -> r
printf String
"skewY(%s)" (Coord -> String
ppD Coord
y)
serializeTransformations :: [Transformation] -> String
serializeTransformations :: [Transformation] -> String
serializeTransformations =
[String] -> String
unwords ([String] -> String)
-> ([Transformation] -> [String]) -> [Transformation] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transformation -> String) -> [Transformation] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Transformation -> String
serializeTransformation
class WithDefaultSvg a where
defaultSvg :: a
data FontStyle
= FontStyleNormal
| FontStyleItalic
| FontStyleOblique
deriving (FontStyle -> FontStyle -> Bool
(FontStyle -> FontStyle -> Bool)
-> (FontStyle -> FontStyle -> Bool) -> Eq FontStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontStyle -> FontStyle -> Bool
$c/= :: FontStyle -> FontStyle -> Bool
== :: FontStyle -> FontStyle -> Bool
$c== :: FontStyle -> FontStyle -> Bool
Eq, Int -> FontStyle -> ShowS
[FontStyle] -> ShowS
FontStyle -> String
(Int -> FontStyle -> ShowS)
-> (FontStyle -> String)
-> ([FontStyle] -> ShowS)
-> Show FontStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontStyle] -> ShowS
$cshowList :: [FontStyle] -> ShowS
show :: FontStyle -> String
$cshow :: FontStyle -> String
showsPrec :: Int -> FontStyle -> ShowS
$cshowsPrec :: Int -> FontStyle -> ShowS
Show, (forall x. FontStyle -> Rep FontStyle x)
-> (forall x. Rep FontStyle x -> FontStyle) -> Generic FontStyle
forall x. Rep FontStyle x -> FontStyle
forall x. FontStyle -> Rep FontStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FontStyle x -> FontStyle
$cfrom :: forall x. FontStyle -> Rep FontStyle x
Generic)
data TextAnchor
=
TextAnchorStart
|
TextAnchorMiddle
|
TextAnchorEnd
deriving (TextAnchor -> TextAnchor -> Bool
(TextAnchor -> TextAnchor -> Bool)
-> (TextAnchor -> TextAnchor -> Bool) -> Eq TextAnchor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextAnchor -> TextAnchor -> Bool
$c/= :: TextAnchor -> TextAnchor -> Bool
== :: TextAnchor -> TextAnchor -> Bool
$c== :: TextAnchor -> TextAnchor -> Bool
Eq, Int -> TextAnchor -> ShowS
[TextAnchor] -> ShowS
TextAnchor -> String
(Int -> TextAnchor -> ShowS)
-> (TextAnchor -> String)
-> ([TextAnchor] -> ShowS)
-> Show TextAnchor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextAnchor] -> ShowS
$cshowList :: [TextAnchor] -> ShowS
show :: TextAnchor -> String
$cshow :: TextAnchor -> String
showsPrec :: Int -> TextAnchor -> ShowS
$cshowsPrec :: Int -> TextAnchor -> ShowS
Show, (forall x. TextAnchor -> Rep TextAnchor x)
-> (forall x. Rep TextAnchor x -> TextAnchor) -> Generic TextAnchor
forall x. Rep TextAnchor x -> TextAnchor
forall x. TextAnchor -> Rep TextAnchor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextAnchor x -> TextAnchor
$cfrom :: forall x. TextAnchor -> Rep TextAnchor x
Generic)
data ElementRef
=
RefNone
|
Ref String
deriving (ElementRef -> ElementRef -> Bool
(ElementRef -> ElementRef -> Bool)
-> (ElementRef -> ElementRef -> Bool) -> Eq ElementRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementRef -> ElementRef -> Bool
$c/= :: ElementRef -> ElementRef -> Bool
== :: ElementRef -> ElementRef -> Bool
$c== :: ElementRef -> ElementRef -> Bool
Eq, Int -> ElementRef -> ShowS
[ElementRef] -> ShowS
ElementRef -> String
(Int -> ElementRef -> ShowS)
-> (ElementRef -> String)
-> ([ElementRef] -> ShowS)
-> Show ElementRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ElementRef] -> ShowS
$cshowList :: [ElementRef] -> ShowS
show :: ElementRef -> String
$cshow :: ElementRef -> String
showsPrec :: Int -> ElementRef -> ShowS
$cshowsPrec :: Int -> ElementRef -> ShowS
Show, (forall x. ElementRef -> Rep ElementRef x)
-> (forall x. Rep ElementRef x -> ElementRef) -> Generic ElementRef
forall x. Rep ElementRef x -> ElementRef
forall x. ElementRef -> Rep ElementRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ElementRef x -> ElementRef
$cfrom :: forall x. ElementRef -> Rep ElementRef x
Generic)
data FilterSource
= SourceGraphic
| SourceAlpha
| BackgroundImage
| BackgroundAlpha
| FillPaint
| StrokePaint
| SourceRef String
deriving (FilterSource -> FilterSource -> Bool
(FilterSource -> FilterSource -> Bool)
-> (FilterSource -> FilterSource -> Bool) -> Eq FilterSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterSource -> FilterSource -> Bool
$c/= :: FilterSource -> FilterSource -> Bool
== :: FilterSource -> FilterSource -> Bool
$c== :: FilterSource -> FilterSource -> Bool
Eq, Int -> FilterSource -> ShowS
[FilterSource] -> ShowS
FilterSource -> String
(Int -> FilterSource -> ShowS)
-> (FilterSource -> String)
-> ([FilterSource] -> ShowS)
-> Show FilterSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilterSource] -> ShowS
$cshowList :: [FilterSource] -> ShowS
show :: FilterSource -> String
$cshow :: FilterSource -> String
showsPrec :: Int -> FilterSource -> ShowS
$cshowsPrec :: Int -> FilterSource -> ShowS
Show, (forall x. FilterSource -> Rep FilterSource x)
-> (forall x. Rep FilterSource x -> FilterSource)
-> Generic FilterSource
forall x. Rep FilterSource x -> FilterSource
forall x. FilterSource -> Rep FilterSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FilterSource x -> FilterSource
$cfrom :: forall x. FilterSource -> Rep FilterSource x
Generic)
data FilterAttributes = FilterAttributes
{ FilterAttributes -> Maybe Number
_filterHeight :: !(Maybe Number),
FilterAttributes -> Maybe String
_filterResult :: !(Maybe String),
FilterAttributes -> Maybe Number
_filterWidth :: !(Maybe Number),
FilterAttributes -> Maybe Number
_filterX :: !(Maybe Number),
FilterAttributes -> Maybe Number
_filterY :: !(Maybe Number)
}
deriving (FilterAttributes -> FilterAttributes -> Bool
(FilterAttributes -> FilterAttributes -> Bool)
-> (FilterAttributes -> FilterAttributes -> Bool)
-> Eq FilterAttributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterAttributes -> FilterAttributes -> Bool
$c/= :: FilterAttributes -> FilterAttributes -> Bool
== :: FilterAttributes -> FilterAttributes -> Bool
$c== :: FilterAttributes -> FilterAttributes -> Bool
Eq, Int -> FilterAttributes -> ShowS
[FilterAttributes] -> ShowS
FilterAttributes -> String
(Int -> FilterAttributes -> ShowS)
-> (FilterAttributes -> String)
-> ([FilterAttributes] -> ShowS)
-> Show FilterAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilterAttributes] -> ShowS
$cshowList :: [FilterAttributes] -> ShowS
show :: FilterAttributes -> String
$cshow :: FilterAttributes -> String
showsPrec :: Int -> FilterAttributes -> ShowS
$cshowsPrec :: Int -> FilterAttributes -> ShowS
Show, (forall x. FilterAttributes -> Rep FilterAttributes x)
-> (forall x. Rep FilterAttributes x -> FilterAttributes)
-> Generic FilterAttributes
forall x. Rep FilterAttributes x -> FilterAttributes
forall x. FilterAttributes -> Rep FilterAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FilterAttributes x -> FilterAttributes
$cfrom :: forall x. FilterAttributes -> Rep FilterAttributes x
Generic)
instance WithDefaultSvg FilterAttributes where
defaultSvg :: FilterAttributes
defaultSvg =
FilterAttributes :: Maybe Number
-> Maybe String
-> Maybe Number
-> Maybe Number
-> Maybe Number
-> FilterAttributes
FilterAttributes
{ _filterHeight :: Maybe Number
_filterHeight = Maybe Number
forall a. Maybe a
Nothing,
_filterResult :: Maybe String
_filterResult = Maybe String
forall a. Maybe a
Nothing,
_filterWidth :: Maybe Number
_filterWidth = Maybe Number
forall a. Maybe a
Nothing,
_filterX :: Maybe Number
_filterX = Maybe Number
forall a. Maybe a
Nothing,
_filterY :: Maybe Number
_filterY = Maybe Number
forall a. Maybe a
Nothing
}
data DrawAttributes = DrawAttributes
{
DrawAttributes -> Maybe Number
_strokeWidth :: !(Maybe Number),
DrawAttributes -> Maybe Texture
_strokeColor :: !(Maybe Texture),
DrawAttributes -> Maybe Float
_strokeOpacity :: !(Maybe Float),
DrawAttributes -> Maybe Cap
_strokeLineCap :: !(Maybe Cap),
DrawAttributes -> Maybe LineJoin
_strokeLineJoin :: !(Maybe LineJoin),
DrawAttributes -> Maybe Coord
_strokeMiterLimit :: !(Maybe Double),
DrawAttributes -> Maybe Texture
_fillColor :: !(Maybe Texture),
DrawAttributes -> Maybe Float
_fillOpacity :: !(Maybe Float),
DrawAttributes -> Maybe Float
_groupOpacity :: !(Maybe Float),
DrawAttributes -> Maybe [Transformation]
_transform :: !(Maybe [Transformation]),
DrawAttributes -> Maybe FillRule
_fillRule :: !(Maybe FillRule),
DrawAttributes -> Maybe ElementRef
_maskRef :: !(Maybe ElementRef),
DrawAttributes -> Maybe ElementRef
_clipPathRef :: !(Maybe ElementRef),
DrawAttributes -> Maybe FillRule
_clipRule :: !(Maybe FillRule),
DrawAttributes -> [Text]
_attrClass :: ![T.Text],
DrawAttributes -> Maybe String
_attrId :: !(Maybe String),
DrawAttributes -> Maybe Number
_strokeOffset :: !(Maybe Number),
DrawAttributes -> Maybe [Number]
_strokeDashArray :: !(Maybe [Number]),
DrawAttributes -> Maybe Number
_fontSize :: !(Maybe Number),
DrawAttributes -> Maybe [String]
_fontFamily :: !(Maybe [String]),
DrawAttributes -> Maybe FontStyle
_fontStyle :: !(Maybe FontStyle),
DrawAttributes -> Maybe TextAnchor
_textAnchor :: !(Maybe TextAnchor),
DrawAttributes -> Maybe ElementRef
_markerStart :: !(Maybe ElementRef),
DrawAttributes -> Maybe ElementRef
_markerMid :: !(Maybe ElementRef),
DrawAttributes -> Maybe ElementRef
_markerEnd :: !(Maybe ElementRef),
DrawAttributes -> Maybe ElementRef
_filterRef :: !(Maybe ElementRef)
}
deriving (DrawAttributes -> DrawAttributes -> Bool
(DrawAttributes -> DrawAttributes -> Bool)
-> (DrawAttributes -> DrawAttributes -> Bool) -> Eq DrawAttributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawAttributes -> DrawAttributes -> Bool
$c/= :: DrawAttributes -> DrawAttributes -> Bool
== :: DrawAttributes -> DrawAttributes -> Bool
$c== :: DrawAttributes -> DrawAttributes -> Bool
Eq, Int -> DrawAttributes -> ShowS
[DrawAttributes] -> ShowS
DrawAttributes -> String
(Int -> DrawAttributes -> ShowS)
-> (DrawAttributes -> String)
-> ([DrawAttributes] -> ShowS)
-> Show DrawAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DrawAttributes] -> ShowS
$cshowList :: [DrawAttributes] -> ShowS
show :: DrawAttributes -> String
$cshow :: DrawAttributes -> String
showsPrec :: Int -> DrawAttributes -> ShowS
$cshowsPrec :: Int -> DrawAttributes -> ShowS
Show, (forall x. DrawAttributes -> Rep DrawAttributes x)
-> (forall x. Rep DrawAttributes x -> DrawAttributes)
-> Generic DrawAttributes
forall x. Rep DrawAttributes x -> DrawAttributes
forall x. DrawAttributes -> Rep DrawAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DrawAttributes x -> DrawAttributes
$cfrom :: forall x. DrawAttributes -> Rep DrawAttributes x
Generic)
makeClassy ''DrawAttributes
data PolyLine = PolyLine
{ PolyLine -> DrawAttributes
_polyLineDrawAttributes :: DrawAttributes,
PolyLine -> [RPoint]
_polyLinePoints :: [RPoint]
}
deriving (PolyLine -> PolyLine -> Bool
(PolyLine -> PolyLine -> Bool)
-> (PolyLine -> PolyLine -> Bool) -> Eq PolyLine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PolyLine -> PolyLine -> Bool
$c/= :: PolyLine -> PolyLine -> Bool
== :: PolyLine -> PolyLine -> Bool
$c== :: PolyLine -> PolyLine -> Bool
Eq, Int -> PolyLine -> ShowS
[PolyLine] -> ShowS
PolyLine -> String
(Int -> PolyLine -> ShowS)
-> (PolyLine -> String) -> ([PolyLine] -> ShowS) -> Show PolyLine
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PolyLine] -> ShowS
$cshowList :: [PolyLine] -> ShowS
show :: PolyLine -> String
$cshow :: PolyLine -> String
showsPrec :: Int -> PolyLine -> ShowS
$cshowsPrec :: Int -> PolyLine -> ShowS
Show, (forall x. PolyLine -> Rep PolyLine x)
-> (forall x. Rep PolyLine x -> PolyLine) -> Generic PolyLine
forall x. Rep PolyLine x -> PolyLine
forall x. PolyLine -> Rep PolyLine x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PolyLine x -> PolyLine
$cfrom :: forall x. PolyLine -> Rep PolyLine x
Generic)
instance WithDefaultSvg PolyLine where
defaultSvg :: PolyLine
defaultSvg = DrawAttributes -> [RPoint] -> PolyLine
PolyLine DrawAttributes
forall a. Monoid a => a
mempty [RPoint]
forall a. Monoid a => a
mempty
data Polygon = Polygon
{ Polygon -> DrawAttributes
_polygonDrawAttributes :: DrawAttributes,
Polygon -> [RPoint]
_polygonPoints :: [RPoint]
}
deriving (Polygon -> Polygon -> Bool
(Polygon -> Polygon -> Bool)
-> (Polygon -> Polygon -> Bool) -> Eq Polygon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Polygon -> Polygon -> Bool
$c/= :: Polygon -> Polygon -> Bool
== :: Polygon -> Polygon -> Bool
$c== :: Polygon -> Polygon -> Bool
Eq, Int -> Polygon -> ShowS
[Polygon] -> ShowS
Polygon -> String
(Int -> Polygon -> ShowS)
-> (Polygon -> String) -> ([Polygon] -> ShowS) -> Show Polygon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Polygon] -> ShowS
$cshowList :: [Polygon] -> ShowS
show :: Polygon -> String
$cshow :: Polygon -> String
showsPrec :: Int -> Polygon -> ShowS
$cshowsPrec :: Int -> Polygon -> ShowS
Show, (forall x. Polygon -> Rep Polygon x)
-> (forall x. Rep Polygon x -> Polygon) -> Generic Polygon
forall x. Rep Polygon x -> Polygon
forall x. Polygon -> Rep Polygon x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Polygon x -> Polygon
$cfrom :: forall x. Polygon -> Rep Polygon x
Generic)
instance WithDefaultSvg Polygon where
defaultSvg :: Polygon
defaultSvg = DrawAttributes -> [RPoint] -> Polygon
Polygon DrawAttributes
forall a. Monoid a => a
mempty [RPoint]
forall a. Monoid a => a
mempty
data Line = Line
{ Line -> DrawAttributes
_lineDrawAttributes :: DrawAttributes,
Line -> Point
_linePoint1 :: !Point,
Line -> Point
_linePoint2 :: !Point
}
deriving (Line -> Line -> Bool
(Line -> Line -> Bool) -> (Line -> Line -> Bool) -> Eq Line
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Line -> Line -> Bool
$c/= :: Line -> Line -> Bool
== :: Line -> Line -> Bool
$c== :: Line -> Line -> Bool
Eq, Int -> Line -> ShowS
[Line] -> ShowS
Line -> String
(Int -> Line -> ShowS)
-> (Line -> String) -> ([Line] -> ShowS) -> Show Line
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Line] -> ShowS
$cshowList :: [Line] -> ShowS
show :: Line -> String
$cshow :: Line -> String
showsPrec :: Int -> Line -> ShowS
$cshowsPrec :: Int -> Line -> ShowS
Show, (forall x. Line -> Rep Line x)
-> (forall x. Rep Line x -> Line) -> Generic Line
forall x. Rep Line x -> Line
forall x. Line -> Rep Line x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Line x -> Line
$cfrom :: forall x. Line -> Rep Line x
Generic)
instance WithDefaultSvg Line where
defaultSvg :: Line
defaultSvg =
Line :: DrawAttributes -> Point -> Point -> Line
Line
{ _lineDrawAttributes :: DrawAttributes
_lineDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_linePoint1 :: Point
_linePoint1 = Point
zeroPoint,
_linePoint2 :: Point
_linePoint2 = Point
zeroPoint
}
where
zeroPoint :: Point
zeroPoint = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0)
data Rectangle = Rectangle
{ Rectangle -> DrawAttributes
_rectangleDrawAttributes :: DrawAttributes,
Rectangle -> Point
_rectUpperLeftCorner :: !Point,
Rectangle -> Maybe Number
_rectWidth :: !(Maybe Number),
Rectangle -> Maybe Number
_rectHeight :: !(Maybe Number),
Rectangle -> (Maybe Number, Maybe Number)
_rectCornerRadius :: !(Maybe Number, Maybe Number)
}
deriving (Rectangle -> Rectangle -> Bool
(Rectangle -> Rectangle -> Bool)
-> (Rectangle -> Rectangle -> Bool) -> Eq Rectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rectangle -> Rectangle -> Bool
$c/= :: Rectangle -> Rectangle -> Bool
== :: Rectangle -> Rectangle -> Bool
$c== :: Rectangle -> Rectangle -> Bool
Eq, Int -> Rectangle -> ShowS
[Rectangle] -> ShowS
Rectangle -> String
(Int -> Rectangle -> ShowS)
-> (Rectangle -> String)
-> ([Rectangle] -> ShowS)
-> Show Rectangle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Rectangle] -> ShowS
$cshowList :: [Rectangle] -> ShowS
show :: Rectangle -> String
$cshow :: Rectangle -> String
showsPrec :: Int -> Rectangle -> ShowS
$cshowsPrec :: Int -> Rectangle -> ShowS
Show, (forall x. Rectangle -> Rep Rectangle x)
-> (forall x. Rep Rectangle x -> Rectangle) -> Generic Rectangle
forall x. Rep Rectangle x -> Rectangle
forall x. Rectangle -> Rep Rectangle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Rectangle x -> Rectangle
$cfrom :: forall x. Rectangle -> Rep Rectangle x
Generic)
instance WithDefaultSvg Rectangle where
defaultSvg :: Rectangle
defaultSvg =
Rectangle :: DrawAttributes
-> Point
-> Maybe Number
-> Maybe Number
-> (Maybe Number, Maybe Number)
-> Rectangle
Rectangle
{ _rectangleDrawAttributes :: DrawAttributes
_rectangleDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_rectUpperLeftCorner :: Point
_rectUpperLeftCorner = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0),
_rectWidth :: Maybe Number
_rectWidth = Maybe Number
forall a. Maybe a
Nothing,
_rectHeight :: Maybe Number
_rectHeight = Maybe Number
forall a. Maybe a
Nothing,
_rectCornerRadius :: (Maybe Number, Maybe Number)
_rectCornerRadius = (Maybe Number
forall a. Maybe a
Nothing, Maybe Number
forall a. Maybe a
Nothing)
}
data Path = Path
{ Path -> DrawAttributes
_pathDrawAttributes :: DrawAttributes,
Path -> [PathCommand]
_pathDefinition :: [PathCommand]
}
deriving (Path -> Path -> Bool
(Path -> Path -> Bool) -> (Path -> Path -> Bool) -> Eq Path
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Path -> Path -> Bool
$c/= :: Path -> Path -> Bool
== :: Path -> Path -> Bool
$c== :: Path -> Path -> Bool
Eq, Int -> Path -> ShowS
[Path] -> ShowS
Path -> String
(Int -> Path -> ShowS)
-> (Path -> String) -> ([Path] -> ShowS) -> Show Path
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Path] -> ShowS
$cshowList :: [Path] -> ShowS
show :: Path -> String
$cshow :: Path -> String
showsPrec :: Int -> Path -> ShowS
$cshowsPrec :: Int -> Path -> ShowS
Show, (forall x. Path -> Rep Path x)
-> (forall x. Rep Path x -> Path) -> Generic Path
forall x. Rep Path x -> Path
forall x. Path -> Rep Path x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Path x -> Path
$cfrom :: forall x. Path -> Rep Path x
Generic)
instance WithDefaultSvg Path where
defaultSvg :: Path
defaultSvg = DrawAttributes -> [PathCommand] -> Path
Path DrawAttributes
forall a. Monoid a => a
mempty [PathCommand]
forall a. Monoid a => a
mempty
data Group = Group
{ Group -> DrawAttributes
_groupDrawAttributes :: DrawAttributes,
Group -> [Tree]
_groupChildren :: ![Tree],
Group -> Maybe (Coord, Coord, Coord, Coord)
_groupViewBox :: !(Maybe (Double, Double, Double, Double)),
Group -> PreserveAspectRatio
_groupAspectRatio :: !PreserveAspectRatio
}
deriving (Group -> Group -> Bool
(Group -> Group -> Bool) -> (Group -> Group -> Bool) -> Eq Group
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Group -> Group -> Bool
$c/= :: Group -> Group -> Bool
== :: Group -> Group -> Bool
$c== :: Group -> Group -> Bool
Eq, Int -> Group -> ShowS
[Group] -> ShowS
Group -> String
(Int -> Group -> ShowS)
-> (Group -> String) -> ([Group] -> ShowS) -> Show Group
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Group] -> ShowS
$cshowList :: [Group] -> ShowS
show :: Group -> String
$cshow :: Group -> String
showsPrec :: Int -> Group -> ShowS
$cshowsPrec :: Int -> Group -> ShowS
Show, (forall x. Group -> Rep Group x)
-> (forall x. Rep Group x -> Group) -> Generic Group
forall x. Rep Group x -> Group
forall x. Group -> Rep Group x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Group x -> Group
$cfrom :: forall x. Group -> Rep Group x
Generic)
instance WithDefaultSvg Group where
defaultSvg :: Group
defaultSvg =
Group :: DrawAttributes
-> [Tree]
-> Maybe (Coord, Coord, Coord, Coord)
-> PreserveAspectRatio
-> Group
Group
{ _groupDrawAttributes :: DrawAttributes
_groupDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_groupChildren :: [Tree]
_groupChildren = [],
_groupViewBox :: Maybe (Coord, Coord, Coord, Coord)
_groupViewBox = Maybe (Coord, Coord, Coord, Coord)
forall a. Maybe a
Nothing,
_groupAspectRatio :: PreserveAspectRatio
_groupAspectRatio = PreserveAspectRatio
forall a. WithDefaultSvg a => a
defaultSvg
}
data Filter = Filter
{ Filter -> DrawAttributes
_filterDrawAttributes :: DrawAttributes,
Filter -> FilterAttributes
_filterSelfAttributes :: !FilterAttributes,
Filter -> [FilterElement]
_filterChildren :: ![FilterElement]
}
deriving (Filter -> Filter -> Bool
(Filter -> Filter -> Bool)
-> (Filter -> Filter -> Bool) -> Eq Filter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Filter -> Filter -> Bool
$c/= :: Filter -> Filter -> Bool
== :: Filter -> Filter -> Bool
$c== :: Filter -> Filter -> Bool
Eq, Int -> Filter -> ShowS
[Filter] -> ShowS
Filter -> String
(Int -> Filter -> ShowS)
-> (Filter -> String) -> ([Filter] -> ShowS) -> Show Filter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Filter] -> ShowS
$cshowList :: [Filter] -> ShowS
show :: Filter -> String
$cshow :: Filter -> String
showsPrec :: Int -> Filter -> ShowS
$cshowsPrec :: Int -> Filter -> ShowS
Show, (forall x. Filter -> Rep Filter x)
-> (forall x. Rep Filter x -> Filter) -> Generic Filter
forall x. Rep Filter x -> Filter
forall x. Filter -> Rep Filter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Filter x -> Filter
$cfrom :: forall x. Filter -> Rep Filter x
Generic)
instance WithDefaultSvg Filter where
defaultSvg :: Filter
defaultSvg =
Filter :: DrawAttributes -> FilterAttributes -> [FilterElement] -> Filter
Filter
{ _filterDrawAttributes :: DrawAttributes
_filterDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_filterSelfAttributes :: FilterAttributes
_filterSelfAttributes = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_filterChildren :: [FilterElement]
_filterChildren = []
}
data Circle = Circle
{ Circle -> DrawAttributes
_circleDrawAttributes :: DrawAttributes,
Circle -> Point
_circleCenter :: !Point,
Circle -> Number
_circleRadius :: !Number
}
deriving (Circle -> Circle -> Bool
(Circle -> Circle -> Bool)
-> (Circle -> Circle -> Bool) -> Eq Circle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Circle -> Circle -> Bool
$c/= :: Circle -> Circle -> Bool
== :: Circle -> Circle -> Bool
$c== :: Circle -> Circle -> Bool
Eq, Int -> Circle -> ShowS
[Circle] -> ShowS
Circle -> String
(Int -> Circle -> ShowS)
-> (Circle -> String) -> ([Circle] -> ShowS) -> Show Circle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Circle] -> ShowS
$cshowList :: [Circle] -> ShowS
show :: Circle -> String
$cshow :: Circle -> String
showsPrec :: Int -> Circle -> ShowS
$cshowsPrec :: Int -> Circle -> ShowS
Show, (forall x. Circle -> Rep Circle x)
-> (forall x. Rep Circle x -> Circle) -> Generic Circle
forall x. Rep Circle x -> Circle
forall x. Circle -> Rep Circle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Circle x -> Circle
$cfrom :: forall x. Circle -> Rep Circle x
Generic)
instance WithDefaultSvg Circle where
defaultSvg :: Circle
defaultSvg =
Circle :: DrawAttributes -> Point -> Number -> Circle
Circle
{ _circleDrawAttributes :: DrawAttributes
_circleDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_circleCenter :: Point
_circleCenter = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0),
_circleRadius :: Number
_circleRadius = Coord -> Number
Num Coord
0
}
data Ellipse = Ellipse
{ Ellipse -> DrawAttributes
_ellipseDrawAttributes :: DrawAttributes,
Ellipse -> Point
_ellipseCenter :: !Point,
Ellipse -> Number
_ellipseXRadius :: !Number,
Ellipse -> Number
_ellipseYRadius :: !Number
}
deriving (Ellipse -> Ellipse -> Bool
(Ellipse -> Ellipse -> Bool)
-> (Ellipse -> Ellipse -> Bool) -> Eq Ellipse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ellipse -> Ellipse -> Bool
$c/= :: Ellipse -> Ellipse -> Bool
== :: Ellipse -> Ellipse -> Bool
$c== :: Ellipse -> Ellipse -> Bool
Eq, Int -> Ellipse -> ShowS
[Ellipse] -> ShowS
Ellipse -> String
(Int -> Ellipse -> ShowS)
-> (Ellipse -> String) -> ([Ellipse] -> ShowS) -> Show Ellipse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ellipse] -> ShowS
$cshowList :: [Ellipse] -> ShowS
show :: Ellipse -> String
$cshow :: Ellipse -> String
showsPrec :: Int -> Ellipse -> ShowS
$cshowsPrec :: Int -> Ellipse -> ShowS
Show, (forall x. Ellipse -> Rep Ellipse x)
-> (forall x. Rep Ellipse x -> Ellipse) -> Generic Ellipse
forall x. Rep Ellipse x -> Ellipse
forall x. Ellipse -> Rep Ellipse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Ellipse x -> Ellipse
$cfrom :: forall x. Ellipse -> Rep Ellipse x
Generic)
instance WithDefaultSvg Ellipse where
defaultSvg :: Ellipse
defaultSvg =
Ellipse :: DrawAttributes -> Point -> Number -> Number -> Ellipse
Ellipse
{ _ellipseDrawAttributes :: DrawAttributes
_ellipseDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_ellipseCenter :: Point
_ellipseCenter = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0),
_ellipseXRadius :: Number
_ellipseXRadius = Coord -> Number
Num Coord
0,
_ellipseYRadius :: Number
_ellipseYRadius = Coord -> Number
Num Coord
0
}
data GradientStop = GradientStop
{
GradientStop -> Float
_gradientOffset :: !Float,
GradientStop -> PixelRGBA8
_gradientColor :: !PixelRGBA8,
GradientStop -> Maybe GradientPathCommand
_gradientPath :: !(Maybe GradientPathCommand),
GradientStop -> Maybe Float
_gradientOpacity :: !(Maybe Float)
}
deriving (GradientStop -> GradientStop -> Bool
(GradientStop -> GradientStop -> Bool)
-> (GradientStop -> GradientStop -> Bool) -> Eq GradientStop
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GradientStop -> GradientStop -> Bool
$c/= :: GradientStop -> GradientStop -> Bool
== :: GradientStop -> GradientStop -> Bool
$c== :: GradientStop -> GradientStop -> Bool
Eq, Int -> GradientStop -> ShowS
[GradientStop] -> ShowS
GradientStop -> String
(Int -> GradientStop -> ShowS)
-> (GradientStop -> String)
-> ([GradientStop] -> ShowS)
-> Show GradientStop
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GradientStop] -> ShowS
$cshowList :: [GradientStop] -> ShowS
show :: GradientStop -> String
$cshow :: GradientStop -> String
showsPrec :: Int -> GradientStop -> ShowS
$cshowsPrec :: Int -> GradientStop -> ShowS
Show, (forall x. GradientStop -> Rep GradientStop x)
-> (forall x. Rep GradientStop x -> GradientStop)
-> Generic GradientStop
forall x. Rep GradientStop x -> GradientStop
forall x. GradientStop -> Rep GradientStop x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GradientStop x -> GradientStop
$cfrom :: forall x. GradientStop -> Rep GradientStop x
Generic)
instance WithDefaultSvg GradientStop where
defaultSvg :: GradientStop
defaultSvg =
GradientStop :: Float
-> PixelRGBA8
-> Maybe GradientPathCommand
-> Maybe Float
-> GradientStop
GradientStop
{ _gradientOffset :: Float
_gradientOffset = Float
0.0,
_gradientColor :: PixelRGBA8
_gradientColor = Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> PixelRGBA8
PixelRGBA8 Pixel8
0 Pixel8
0 Pixel8
0 Pixel8
255,
_gradientPath :: Maybe GradientPathCommand
_gradientPath = Maybe GradientPathCommand
forall a. Maybe a
Nothing,
_gradientOpacity :: Maybe Float
_gradientOpacity = Maybe Float
forall a. Maybe a
Nothing
}
newtype MeshGradientPatch = MeshGradientPatch
{
MeshGradientPatch -> [GradientStop]
_meshGradientPatchStops :: [GradientStop]
}
deriving (MeshGradientPatch -> MeshGradientPatch -> Bool
(MeshGradientPatch -> MeshGradientPatch -> Bool)
-> (MeshGradientPatch -> MeshGradientPatch -> Bool)
-> Eq MeshGradientPatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MeshGradientPatch -> MeshGradientPatch -> Bool
$c/= :: MeshGradientPatch -> MeshGradientPatch -> Bool
== :: MeshGradientPatch -> MeshGradientPatch -> Bool
$c== :: MeshGradientPatch -> MeshGradientPatch -> Bool
Eq, Int -> MeshGradientPatch -> ShowS
[MeshGradientPatch] -> ShowS
MeshGradientPatch -> String
(Int -> MeshGradientPatch -> ShowS)
-> (MeshGradientPatch -> String)
-> ([MeshGradientPatch] -> ShowS)
-> Show MeshGradientPatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MeshGradientPatch] -> ShowS
$cshowList :: [MeshGradientPatch] -> ShowS
show :: MeshGradientPatch -> String
$cshow :: MeshGradientPatch -> String
showsPrec :: Int -> MeshGradientPatch -> ShowS
$cshowsPrec :: Int -> MeshGradientPatch -> ShowS
Show, (forall x. MeshGradientPatch -> Rep MeshGradientPatch x)
-> (forall x. Rep MeshGradientPatch x -> MeshGradientPatch)
-> Generic MeshGradientPatch
forall x. Rep MeshGradientPatch x -> MeshGradientPatch
forall x. MeshGradientPatch -> Rep MeshGradientPatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MeshGradientPatch x -> MeshGradientPatch
$cfrom :: forall x. MeshGradientPatch -> Rep MeshGradientPatch x
Generic)
instance WithDefaultSvg MeshGradientPatch where
defaultSvg :: MeshGradientPatch
defaultSvg = [GradientStop] -> MeshGradientPatch
MeshGradientPatch []
newtype MeshGradientRow = MeshGradientRow
{
MeshGradientRow -> [MeshGradientPatch]
_meshGradientRowPatches :: [MeshGradientPatch]
}
deriving (MeshGradientRow -> MeshGradientRow -> Bool
(MeshGradientRow -> MeshGradientRow -> Bool)
-> (MeshGradientRow -> MeshGradientRow -> Bool)
-> Eq MeshGradientRow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MeshGradientRow -> MeshGradientRow -> Bool
$c/= :: MeshGradientRow -> MeshGradientRow -> Bool
== :: MeshGradientRow -> MeshGradientRow -> Bool
$c== :: MeshGradientRow -> MeshGradientRow -> Bool
Eq, Int -> MeshGradientRow -> ShowS
[MeshGradientRow] -> ShowS
MeshGradientRow -> String
(Int -> MeshGradientRow -> ShowS)
-> (MeshGradientRow -> String)
-> ([MeshGradientRow] -> ShowS)
-> Show MeshGradientRow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MeshGradientRow] -> ShowS
$cshowList :: [MeshGradientRow] -> ShowS
show :: MeshGradientRow -> String
$cshow :: MeshGradientRow -> String
showsPrec :: Int -> MeshGradientRow -> ShowS
$cshowsPrec :: Int -> MeshGradientRow -> ShowS
Show, (forall x. MeshGradientRow -> Rep MeshGradientRow x)
-> (forall x. Rep MeshGradientRow x -> MeshGradientRow)
-> Generic MeshGradientRow
forall x. Rep MeshGradientRow x -> MeshGradientRow
forall x. MeshGradientRow -> Rep MeshGradientRow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MeshGradientRow x -> MeshGradientRow
$cfrom :: forall x. MeshGradientRow -> Rep MeshGradientRow x
Generic)
instance WithDefaultSvg MeshGradientRow where
defaultSvg :: MeshGradientRow
defaultSvg = [MeshGradientPatch] -> MeshGradientRow
MeshGradientRow []
data MeshGradient = MeshGradient
{ MeshGradient -> DrawAttributes
_meshGradientDrawAttributes :: DrawAttributes,
MeshGradient -> Number
_meshGradientX :: !Number,
MeshGradient -> Number
_meshGradientY :: !Number,
MeshGradient -> MeshGradientType
_meshGradientType :: !MeshGradientType,
MeshGradient -> CoordinateUnits
_meshGradientUnits :: !CoordinateUnits,
MeshGradient -> [Transformation]
_meshGradientTransform :: ![Transformation],
MeshGradient -> [MeshGradientRow]
_meshGradientRows :: ![MeshGradientRow]
}
deriving (MeshGradient -> MeshGradient -> Bool
(MeshGradient -> MeshGradient -> Bool)
-> (MeshGradient -> MeshGradient -> Bool) -> Eq MeshGradient
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MeshGradient -> MeshGradient -> Bool
$c/= :: MeshGradient -> MeshGradient -> Bool
== :: MeshGradient -> MeshGradient -> Bool
$c== :: MeshGradient -> MeshGradient -> Bool
Eq, Int -> MeshGradient -> ShowS
[MeshGradient] -> ShowS
MeshGradient -> String
(Int -> MeshGradient -> ShowS)
-> (MeshGradient -> String)
-> ([MeshGradient] -> ShowS)
-> Show MeshGradient
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MeshGradient] -> ShowS
$cshowList :: [MeshGradient] -> ShowS
show :: MeshGradient -> String
$cshow :: MeshGradient -> String
showsPrec :: Int -> MeshGradient -> ShowS
$cshowsPrec :: Int -> MeshGradient -> ShowS
Show, (forall x. MeshGradient -> Rep MeshGradient x)
-> (forall x. Rep MeshGradient x -> MeshGradient)
-> Generic MeshGradient
forall x. Rep MeshGradient x -> MeshGradient
forall x. MeshGradient -> Rep MeshGradient x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MeshGradient x -> MeshGradient
$cfrom :: forall x. MeshGradient -> Rep MeshGradient x
Generic)
instance WithDefaultSvg MeshGradient where
defaultSvg :: MeshGradient
defaultSvg =
MeshGradient :: DrawAttributes
-> Number
-> Number
-> MeshGradientType
-> CoordinateUnits
-> [Transformation]
-> [MeshGradientRow]
-> MeshGradient
MeshGradient
{ _meshGradientDrawAttributes :: DrawAttributes
_meshGradientDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_meshGradientX :: Number
_meshGradientX = Coord -> Number
Percent Coord
0,
_meshGradientY :: Number
_meshGradientY = Coord -> Number
Percent Coord
0,
_meshGradientType :: MeshGradientType
_meshGradientType = MeshGradientType
GradientBilinear,
_meshGradientUnits :: CoordinateUnits
_meshGradientUnits = CoordinateUnits
CoordBoundingBox,
_meshGradientTransform :: [Transformation]
_meshGradientTransform = [Transformation]
forall a. Monoid a => a
mempty,
_meshGradientRows :: [MeshGradientRow]
_meshGradientRows = [MeshGradientRow]
forall a. Monoid a => a
mempty
}
data Image = Image
{ Image -> DrawAttributes
_imageDrawAttributes :: DrawAttributes,
Image -> Point
_imageCornerUpperLeft :: !Point,
Image -> Number
_imageWidth :: !Number,
Image -> Number
_imageHeight :: !Number,
Image -> String
_imageHref :: !String,
Image -> PreserveAspectRatio
_imageAspectRatio :: !PreserveAspectRatio
}
deriving (Image -> Image -> Bool
(Image -> Image -> Bool) -> (Image -> Image -> Bool) -> Eq Image
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Image -> Image -> Bool
$c/= :: Image -> Image -> Bool
== :: Image -> Image -> Bool
$c== :: Image -> Image -> Bool
Eq, Int -> Image -> ShowS
[Image] -> ShowS
Image -> String
(Int -> Image -> ShowS)
-> (Image -> String) -> ([Image] -> ShowS) -> Show Image
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Image] -> ShowS
$cshowList :: [Image] -> ShowS
show :: Image -> String
$cshow :: Image -> String
showsPrec :: Int -> Image -> ShowS
$cshowsPrec :: Int -> Image -> ShowS
Show, (forall x. Image -> Rep Image x)
-> (forall x. Rep Image x -> Image) -> Generic Image
forall x. Rep Image x -> Image
forall x. Image -> Rep Image x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Image x -> Image
$cfrom :: forall x. Image -> Rep Image x
Generic)
instance WithDefaultSvg Image where
defaultSvg :: Image
defaultSvg =
Image :: DrawAttributes
-> Point
-> Number
-> Number
-> String
-> PreserveAspectRatio
-> Image
Image
{ _imageDrawAttributes :: DrawAttributes
_imageDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_imageCornerUpperLeft :: Point
_imageCornerUpperLeft = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0),
_imageWidth :: Number
_imageWidth = Coord -> Number
Num Coord
0,
_imageHeight :: Number
_imageHeight = Coord -> Number
Num Coord
0,
_imageHref :: String
_imageHref = String
"",
_imageAspectRatio :: PreserveAspectRatio
_imageAspectRatio = PreserveAspectRatio
forall a. WithDefaultSvg a => a
defaultSvg
}
data Use = Use
{ Use -> DrawAttributes
_useDrawAttributes :: DrawAttributes,
Use -> Point
_useBase :: Point,
Use -> String
_useName :: String,
Use -> Maybe Number
_useWidth :: Maybe Number,
Use -> Maybe Number
_useHeight :: Maybe Number
}
deriving (Use -> Use -> Bool
(Use -> Use -> Bool) -> (Use -> Use -> Bool) -> Eq Use
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Use -> Use -> Bool
$c/= :: Use -> Use -> Bool
== :: Use -> Use -> Bool
$c== :: Use -> Use -> Bool
Eq, Int -> Use -> ShowS
[Use] -> ShowS
Use -> String
(Int -> Use -> ShowS)
-> (Use -> String) -> ([Use] -> ShowS) -> Show Use
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Use] -> ShowS
$cshowList :: [Use] -> ShowS
show :: Use -> String
$cshow :: Use -> String
showsPrec :: Int -> Use -> ShowS
$cshowsPrec :: Int -> Use -> ShowS
Show, (forall x. Use -> Rep Use x)
-> (forall x. Rep Use x -> Use) -> Generic Use
forall x. Rep Use x -> Use
forall x. Use -> Rep Use x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Use x -> Use
$cfrom :: forall x. Use -> Rep Use x
Generic)
instance WithDefaultSvg Use where
defaultSvg :: Use
defaultSvg =
Use :: DrawAttributes
-> Point -> String -> Maybe Number -> Maybe Number -> Use
Use
{ _useDrawAttributes :: DrawAttributes
_useDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_useBase :: Point
_useBase = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0),
_useName :: String
_useName = String
"",
_useWidth :: Maybe Number
_useWidth = Maybe Number
forall a. Maybe a
Nothing,
_useHeight :: Maybe Number
_useHeight = Maybe Number
forall a. Maybe a
Nothing
}
data TextInfo = TextInfo
{
TextInfo -> [Number]
_textInfoX :: ![Number],
TextInfo -> [Number]
_textInfoY :: ![Number],
TextInfo -> [Number]
_textInfoDX :: ![Number],
TextInfo -> [Number]
_textInfoDY :: ![Number],
TextInfo -> [Coord]
_textInfoRotate :: ![Double],
TextInfo -> Maybe Number
_textInfoLength :: !(Maybe Number)
}
deriving (TextInfo -> TextInfo -> Bool
(TextInfo -> TextInfo -> Bool)
-> (TextInfo -> TextInfo -> Bool) -> Eq TextInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextInfo -> TextInfo -> Bool
$c/= :: TextInfo -> TextInfo -> Bool
== :: TextInfo -> TextInfo -> Bool
$c== :: TextInfo -> TextInfo -> Bool
Eq, Int -> TextInfo -> ShowS
[TextInfo] -> ShowS
TextInfo -> String
(Int -> TextInfo -> ShowS)
-> (TextInfo -> String) -> ([TextInfo] -> ShowS) -> Show TextInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextInfo] -> ShowS
$cshowList :: [TextInfo] -> ShowS
show :: TextInfo -> String
$cshow :: TextInfo -> String
showsPrec :: Int -> TextInfo -> ShowS
$cshowsPrec :: Int -> TextInfo -> ShowS
Show, (forall x. TextInfo -> Rep TextInfo x)
-> (forall x. Rep TextInfo x -> TextInfo) -> Generic TextInfo
forall x. Rep TextInfo x -> TextInfo
forall x. TextInfo -> Rep TextInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextInfo x -> TextInfo
$cfrom :: forall x. TextInfo -> Rep TextInfo x
Generic)
instance Semigroup TextInfo where
<> :: TextInfo -> TextInfo -> TextInfo
(<>)
(TextInfo [Number]
x1 [Number]
y1 [Number]
dx1 [Number]
dy1 [Coord]
r1 Maybe Number
l1)
(TextInfo [Number]
x2 [Number]
y2 [Number]
dx2 [Number]
dy2 [Coord]
r2 Maybe Number
l2) =
[Number]
-> [Number]
-> [Number]
-> [Number]
-> [Coord]
-> Maybe Number
-> TextInfo
TextInfo
([Number]
x1 [Number] -> [Number] -> [Number]
forall a. Semigroup a => a -> a -> a
<> [Number]
x2)
([Number]
y1 [Number] -> [Number] -> [Number]
forall a. Semigroup a => a -> a -> a
<> [Number]
y2)
([Number]
dx1 [Number] -> [Number] -> [Number]
forall a. Semigroup a => a -> a -> a
<> [Number]
dx2)
([Number]
dy1 [Number] -> [Number] -> [Number]
forall a. Semigroup a => a -> a -> a
<> [Number]
dy2)
([Coord]
r1 [Coord] -> [Coord] -> [Coord]
forall a. Semigroup a => a -> a -> a
<> [Coord]
r2)
(Maybe Number
l2 Maybe Number -> Maybe Number -> Maybe Number
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Number
l1)
instance Monoid TextInfo where
mempty :: TextInfo
mempty = [Number]
-> [Number]
-> [Number]
-> [Number]
-> [Coord]
-> Maybe Number
-> TextInfo
TextInfo [] [] [] [] [] Maybe Number
forall a. Maybe a
Nothing
mappend :: TextInfo -> TextInfo -> TextInfo
mappend = TextInfo -> TextInfo -> TextInfo
forall a. Semigroup a => a -> a -> a
(<>)
instance WithDefaultSvg TextInfo where
defaultSvg :: TextInfo
defaultSvg = TextInfo
forall a. Monoid a => a
mempty
data TextSpanContent
=
SpanText !T.Text
|
SpanTextRef !String
|
SpanSub !TextSpan
deriving (TextSpanContent -> TextSpanContent -> Bool
(TextSpanContent -> TextSpanContent -> Bool)
-> (TextSpanContent -> TextSpanContent -> Bool)
-> Eq TextSpanContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextSpanContent -> TextSpanContent -> Bool
$c/= :: TextSpanContent -> TextSpanContent -> Bool
== :: TextSpanContent -> TextSpanContent -> Bool
$c== :: TextSpanContent -> TextSpanContent -> Bool
Eq, Int -> TextSpanContent -> ShowS
[TextSpanContent] -> ShowS
TextSpanContent -> String
(Int -> TextSpanContent -> ShowS)
-> (TextSpanContent -> String)
-> ([TextSpanContent] -> ShowS)
-> Show TextSpanContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextSpanContent] -> ShowS
$cshowList :: [TextSpanContent] -> ShowS
show :: TextSpanContent -> String
$cshow :: TextSpanContent -> String
showsPrec :: Int -> TextSpanContent -> ShowS
$cshowsPrec :: Int -> TextSpanContent -> ShowS
Show, (forall x. TextSpanContent -> Rep TextSpanContent x)
-> (forall x. Rep TextSpanContent x -> TextSpanContent)
-> Generic TextSpanContent
forall x. Rep TextSpanContent x -> TextSpanContent
forall x. TextSpanContent -> Rep TextSpanContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextSpanContent x -> TextSpanContent
$cfrom :: forall x. TextSpanContent -> Rep TextSpanContent x
Generic)
data TextSpan = TextSpan
{
TextSpan -> TextInfo
_spanInfo :: !TextInfo,
TextSpan -> DrawAttributes
_spanDrawAttributes :: !DrawAttributes,
TextSpan -> [TextSpanContent]
_spanContent :: ![TextSpanContent]
}
deriving (TextSpan -> TextSpan -> Bool
(TextSpan -> TextSpan -> Bool)
-> (TextSpan -> TextSpan -> Bool) -> Eq TextSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextSpan -> TextSpan -> Bool
$c/= :: TextSpan -> TextSpan -> Bool
== :: TextSpan -> TextSpan -> Bool
$c== :: TextSpan -> TextSpan -> Bool
Eq, Int -> TextSpan -> ShowS
[TextSpan] -> ShowS
TextSpan -> String
(Int -> TextSpan -> ShowS)
-> (TextSpan -> String) -> ([TextSpan] -> ShowS) -> Show TextSpan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextSpan] -> ShowS
$cshowList :: [TextSpan] -> ShowS
show :: TextSpan -> String
$cshow :: TextSpan -> String
showsPrec :: Int -> TextSpan -> ShowS
$cshowsPrec :: Int -> TextSpan -> ShowS
Show, (forall x. TextSpan -> Rep TextSpan x)
-> (forall x. Rep TextSpan x -> TextSpan) -> Generic TextSpan
forall x. Rep TextSpan x -> TextSpan
forall x. TextSpan -> Rep TextSpan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextSpan x -> TextSpan
$cfrom :: forall x. TextSpan -> Rep TextSpan x
Generic)
instance WithDefaultSvg TextSpan where
defaultSvg :: TextSpan
defaultSvg =
TextSpan :: TextInfo -> DrawAttributes -> [TextSpanContent] -> TextSpan
TextSpan
{ _spanInfo :: TextInfo
_spanInfo = TextInfo
forall a. WithDefaultSvg a => a
defaultSvg,
_spanDrawAttributes :: DrawAttributes
_spanDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_spanContent :: [TextSpanContent]
_spanContent = [TextSpanContent]
forall a. Monoid a => a
mempty
}
data TextPathMethod
=
TextPathAlign
|
TextPathStretch
deriving (TextPathMethod -> TextPathMethod -> Bool
(TextPathMethod -> TextPathMethod -> Bool)
-> (TextPathMethod -> TextPathMethod -> Bool) -> Eq TextPathMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextPathMethod -> TextPathMethod -> Bool
$c/= :: TextPathMethod -> TextPathMethod -> Bool
== :: TextPathMethod -> TextPathMethod -> Bool
$c== :: TextPathMethod -> TextPathMethod -> Bool
Eq, Int -> TextPathMethod -> ShowS
[TextPathMethod] -> ShowS
TextPathMethod -> String
(Int -> TextPathMethod -> ShowS)
-> (TextPathMethod -> String)
-> ([TextPathMethod] -> ShowS)
-> Show TextPathMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextPathMethod] -> ShowS
$cshowList :: [TextPathMethod] -> ShowS
show :: TextPathMethod -> String
$cshow :: TextPathMethod -> String
showsPrec :: Int -> TextPathMethod -> ShowS
$cshowsPrec :: Int -> TextPathMethod -> ShowS
Show, (forall x. TextPathMethod -> Rep TextPathMethod x)
-> (forall x. Rep TextPathMethod x -> TextPathMethod)
-> Generic TextPathMethod
forall x. Rep TextPathMethod x -> TextPathMethod
forall x. TextPathMethod -> Rep TextPathMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextPathMethod x -> TextPathMethod
$cfrom :: forall x. TextPathMethod -> Rep TextPathMethod x
Generic)
data TextPathSpacing
=
TextPathSpacingExact
|
TextPathSpacingAuto
deriving (TextPathSpacing -> TextPathSpacing -> Bool
(TextPathSpacing -> TextPathSpacing -> Bool)
-> (TextPathSpacing -> TextPathSpacing -> Bool)
-> Eq TextPathSpacing
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextPathSpacing -> TextPathSpacing -> Bool
$c/= :: TextPathSpacing -> TextPathSpacing -> Bool
== :: TextPathSpacing -> TextPathSpacing -> Bool
$c== :: TextPathSpacing -> TextPathSpacing -> Bool
Eq, Int -> TextPathSpacing -> ShowS
[TextPathSpacing] -> ShowS
TextPathSpacing -> String
(Int -> TextPathSpacing -> ShowS)
-> (TextPathSpacing -> String)
-> ([TextPathSpacing] -> ShowS)
-> Show TextPathSpacing
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextPathSpacing] -> ShowS
$cshowList :: [TextPathSpacing] -> ShowS
show :: TextPathSpacing -> String
$cshow :: TextPathSpacing -> String
showsPrec :: Int -> TextPathSpacing -> ShowS
$cshowsPrec :: Int -> TextPathSpacing -> ShowS
Show, (forall x. TextPathSpacing -> Rep TextPathSpacing x)
-> (forall x. Rep TextPathSpacing x -> TextPathSpacing)
-> Generic TextPathSpacing
forall x. Rep TextPathSpacing x -> TextPathSpacing
forall x. TextPathSpacing -> Rep TextPathSpacing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextPathSpacing x -> TextPathSpacing
$cfrom :: forall x. TextPathSpacing -> Rep TextPathSpacing x
Generic)
data TextPath = TextPath
{
TextPath -> Number
_textPathStartOffset :: !Number,
TextPath -> String
_textPathName :: !String,
TextPath -> TextPathMethod
_textPathMethod :: !TextPathMethod,
TextPath -> TextPathSpacing
_textPathSpacing :: !TextPathSpacing
}
deriving (TextPath -> TextPath -> Bool
(TextPath -> TextPath -> Bool)
-> (TextPath -> TextPath -> Bool) -> Eq TextPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextPath -> TextPath -> Bool
$c/= :: TextPath -> TextPath -> Bool
== :: TextPath -> TextPath -> Bool
$c== :: TextPath -> TextPath -> Bool
Eq, Int -> TextPath -> ShowS
[TextPath] -> ShowS
TextPath -> String
(Int -> TextPath -> ShowS)
-> (TextPath -> String) -> ([TextPath] -> ShowS) -> Show TextPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextPath] -> ShowS
$cshowList :: [TextPath] -> ShowS
show :: TextPath -> String
$cshow :: TextPath -> String
showsPrec :: Int -> TextPath -> ShowS
$cshowsPrec :: Int -> TextPath -> ShowS
Show, (forall x. TextPath -> Rep TextPath x)
-> (forall x. Rep TextPath x -> TextPath) -> Generic TextPath
forall x. Rep TextPath x -> TextPath
forall x. TextPath -> Rep TextPath x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextPath x -> TextPath
$cfrom :: forall x. TextPath -> Rep TextPath x
Generic)
instance WithDefaultSvg TextPath where
defaultSvg :: TextPath
defaultSvg =
TextPath :: Number -> String -> TextPathMethod -> TextPathSpacing -> TextPath
TextPath
{ _textPathStartOffset :: Number
_textPathStartOffset = Coord -> Number
Num Coord
0,
_textPathName :: String
_textPathName = String
forall a. Monoid a => a
mempty,
_textPathMethod :: TextPathMethod
_textPathMethod = TextPathMethod
TextPathAlign,
_textPathSpacing :: TextPathSpacing
_textPathSpacing = TextPathSpacing
TextPathSpacingExact
}
data TextAdjust
=
TextAdjustSpacing
|
TextAdjustSpacingAndGlyphs
deriving (TextAdjust -> TextAdjust -> Bool
(TextAdjust -> TextAdjust -> Bool)
-> (TextAdjust -> TextAdjust -> Bool) -> Eq TextAdjust
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextAdjust -> TextAdjust -> Bool
$c/= :: TextAdjust -> TextAdjust -> Bool
== :: TextAdjust -> TextAdjust -> Bool
$c== :: TextAdjust -> TextAdjust -> Bool
Eq, Int -> TextAdjust -> ShowS
[TextAdjust] -> ShowS
TextAdjust -> String
(Int -> TextAdjust -> ShowS)
-> (TextAdjust -> String)
-> ([TextAdjust] -> ShowS)
-> Show TextAdjust
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextAdjust] -> ShowS
$cshowList :: [TextAdjust] -> ShowS
show :: TextAdjust -> String
$cshow :: TextAdjust -> String
showsPrec :: Int -> TextAdjust -> ShowS
$cshowsPrec :: Int -> TextAdjust -> ShowS
Show, (forall x. TextAdjust -> Rep TextAdjust x)
-> (forall x. Rep TextAdjust x -> TextAdjust) -> Generic TextAdjust
forall x. Rep TextAdjust x -> TextAdjust
forall x. TextAdjust -> Rep TextAdjust x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextAdjust x -> TextAdjust
$cfrom :: forall x. TextAdjust -> Rep TextAdjust x
Generic)
data Text = Text
{
Text -> TextAdjust
_textAdjust :: !TextAdjust,
Text -> TextSpan
_textRoot :: !TextSpan
}
deriving (Text -> Text -> Bool
(Text -> Text -> Bool) -> (Text -> Text -> Bool) -> Eq Text
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Text -> Text -> Bool
$c/= :: Text -> Text -> Bool
== :: Text -> Text -> Bool
$c== :: Text -> Text -> Bool
Eq, Int -> Text -> ShowS
[Text] -> ShowS
Text -> String
(Int -> Text -> ShowS)
-> (Text -> String) -> ([Text] -> ShowS) -> Show Text
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Text] -> ShowS
$cshowList :: [Text] -> ShowS
show :: Text -> String
$cshow :: Text -> String
showsPrec :: Int -> Text -> ShowS
$cshowsPrec :: Int -> Text -> ShowS
Show, (forall x. Text -> Rep Text x)
-> (forall x. Rep Text x -> Text) -> Generic Text
forall x. Rep Text x -> Text
forall x. Text -> Rep Text x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Text x -> Text
$cfrom :: forall x. Text -> Rep Text x
Generic)
textAt :: Point -> T.Text -> Text
textAt :: Point -> Text -> Text
textAt (Number
x, Number
y) Text
txt = TextAdjust -> TextSpan -> Text
Text TextAdjust
TextAdjustSpacing TextSpan
tspan
where
tspan :: TextSpan
tspan =
TextSpan
forall a. WithDefaultSvg a => a
defaultSvg
{ _spanContent :: [TextSpanContent]
_spanContent = [Text -> TextSpanContent
SpanText Text
txt],
_spanInfo :: TextInfo
_spanInfo =
TextInfo
forall a. WithDefaultSvg a => a
defaultSvg
{ _textInfoX :: [Number]
_textInfoX = [Number
x],
_textInfoY :: [Number]
_textInfoY = [Number
y]
}
}
instance WithDefaultSvg Text where
defaultSvg :: Text
defaultSvg =
Text :: TextAdjust -> TextSpan -> Text
Text
{ _textRoot :: TextSpan
_textRoot = TextSpan
forall a. WithDefaultSvg a => a
defaultSvg,
_textAdjust :: TextAdjust
_textAdjust = TextAdjust
TextAdjustSpacing
}
data Tree = CachedTree
{ Tree -> TreeBranch
_treeBranch :: TreeBranch,
Tree -> Int
_treeHash :: Int
}
deriving (Tree -> Tree -> Bool
(Tree -> Tree -> Bool) -> (Tree -> Tree -> Bool) -> Eq Tree
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tree -> Tree -> Bool
$c/= :: Tree -> Tree -> Bool
== :: Tree -> Tree -> Bool
$c== :: Tree -> Tree -> Bool
Eq, Int -> Tree -> ShowS
[Tree] -> ShowS
Tree -> String
(Int -> Tree -> ShowS)
-> (Tree -> String) -> ([Tree] -> ShowS) -> Show Tree
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tree] -> ShowS
$cshowList :: [Tree] -> ShowS
show :: Tree -> String
$cshow :: Tree -> String
showsPrec :: Int -> Tree -> ShowS
$cshowsPrec :: Int -> Tree -> ShowS
Show, (forall x. Tree -> Rep Tree x)
-> (forall x. Rep Tree x -> Tree) -> Generic Tree
forall x. Rep Tree x -> Tree
forall x. Tree -> Rep Tree x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tree x -> Tree
$cfrom :: forall x. Tree -> Rep Tree x
Generic)
data TreeBranch
= NoNode
| UseNode
{ TreeBranch -> Use
useInformation :: !Use,
TreeBranch -> Maybe Tree
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 (TreeBranch -> TreeBranch -> Bool
(TreeBranch -> TreeBranch -> Bool)
-> (TreeBranch -> TreeBranch -> Bool) -> Eq TreeBranch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TreeBranch -> TreeBranch -> Bool
$c/= :: TreeBranch -> TreeBranch -> Bool
== :: TreeBranch -> TreeBranch -> Bool
$c== :: TreeBranch -> TreeBranch -> Bool
Eq, Int -> TreeBranch -> ShowS
[TreeBranch] -> ShowS
TreeBranch -> String
(Int -> TreeBranch -> ShowS)
-> (TreeBranch -> String)
-> ([TreeBranch] -> ShowS)
-> Show TreeBranch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TreeBranch] -> ShowS
$cshowList :: [TreeBranch] -> ShowS
show :: TreeBranch -> String
$cshow :: TreeBranch -> String
showsPrec :: Int -> TreeBranch -> ShowS
$cshowsPrec :: Int -> TreeBranch -> ShowS
Show, (forall x. TreeBranch -> Rep TreeBranch x)
-> (forall x. Rep TreeBranch x -> TreeBranch) -> Generic TreeBranch
forall x. Rep TreeBranch x -> TreeBranch
forall x. TreeBranch -> Rep TreeBranch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TreeBranch x -> TreeBranch
$cfrom :: forall x. TreeBranch -> Rep TreeBranch x
Generic)
instance WithDefaultSvg TreeBranch where
defaultSvg :: TreeBranch
defaultSvg = TreeBranch
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 (FilterElement -> FilterElement -> Bool
(FilterElement -> FilterElement -> Bool)
-> (FilterElement -> FilterElement -> Bool) -> Eq FilterElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterElement -> FilterElement -> Bool
$c/= :: FilterElement -> FilterElement -> Bool
== :: FilterElement -> FilterElement -> Bool
$c== :: FilterElement -> FilterElement -> Bool
Eq, Int -> FilterElement -> ShowS
[FilterElement] -> ShowS
FilterElement -> String
(Int -> FilterElement -> ShowS)
-> (FilterElement -> String)
-> ([FilterElement] -> ShowS)
-> Show FilterElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilterElement] -> ShowS
$cshowList :: [FilterElement] -> ShowS
show :: FilterElement -> String
$cshow :: FilterElement -> String
showsPrec :: Int -> FilterElement -> ShowS
$cshowsPrec :: Int -> FilterElement -> ShowS
Show, (forall x. FilterElement -> Rep FilterElement x)
-> (forall x. Rep FilterElement x -> FilterElement)
-> Generic FilterElement
forall x. Rep FilterElement x -> FilterElement
forall x. FilterElement -> Rep FilterElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FilterElement x -> FilterElement
$cfrom :: forall x. FilterElement -> Rep FilterElement x
Generic)
instance WithDefaultSvg FilterElement where
defaultSvg :: FilterElement
defaultSvg = FilterElement
FENone
data SpecularLighting = SpecularLighting
{ SpecularLighting -> DrawAttributes
_specLightingDrawAttributes :: DrawAttributes,
SpecularLighting -> FilterAttributes
_specLightingFilterAttr :: !FilterAttributes,
SpecularLighting -> Maybe FilterSource
_specLightingIn :: !(Maybe FilterSource),
SpecularLighting -> Coord
_specLightingSurfaceScale :: Double,
SpecularLighting -> Coord
_specLightingSpecularConst :: Double,
SpecularLighting -> Coord
_specLightingSpecularExp :: Double,
SpecularLighting -> NumberOptionalNumber
_specLightingKernelUnitLength :: NumberOptionalNumber
}
deriving (SpecularLighting -> SpecularLighting -> Bool
(SpecularLighting -> SpecularLighting -> Bool)
-> (SpecularLighting -> SpecularLighting -> Bool)
-> Eq SpecularLighting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpecularLighting -> SpecularLighting -> Bool
$c/= :: SpecularLighting -> SpecularLighting -> Bool
== :: SpecularLighting -> SpecularLighting -> Bool
$c== :: SpecularLighting -> SpecularLighting -> Bool
Eq, Int -> SpecularLighting -> ShowS
[SpecularLighting] -> ShowS
SpecularLighting -> String
(Int -> SpecularLighting -> ShowS)
-> (SpecularLighting -> String)
-> ([SpecularLighting] -> ShowS)
-> Show SpecularLighting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpecularLighting] -> ShowS
$cshowList :: [SpecularLighting] -> ShowS
show :: SpecularLighting -> String
$cshow :: SpecularLighting -> String
showsPrec :: Int -> SpecularLighting -> ShowS
$cshowsPrec :: Int -> SpecularLighting -> ShowS
Show, (forall x. SpecularLighting -> Rep SpecularLighting x)
-> (forall x. Rep SpecularLighting x -> SpecularLighting)
-> Generic SpecularLighting
forall x. Rep SpecularLighting x -> SpecularLighting
forall x. SpecularLighting -> Rep SpecularLighting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpecularLighting x -> SpecularLighting
$cfrom :: forall x. SpecularLighting -> Rep SpecularLighting x
Generic)
instance WithDefaultSvg SpecularLighting where
defaultSvg :: SpecularLighting
defaultSvg =
SpecularLighting :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> Coord
-> Coord
-> Coord
-> NumberOptionalNumber
-> SpecularLighting
SpecularLighting
{ _specLightingDrawAttributes :: DrawAttributes
_specLightingDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_specLightingFilterAttr :: FilterAttributes
_specLightingFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_specLightingIn :: Maybe FilterSource
_specLightingIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_specLightingSurfaceScale :: Coord
_specLightingSurfaceScale = Coord
1,
_specLightingSpecularConst :: Coord
_specLightingSpecularConst = Coord
1,
_specLightingSpecularExp :: Coord
_specLightingSpecularExp = Coord
1,
_specLightingKernelUnitLength :: NumberOptionalNumber
_specLightingKernelUnitLength = Coord -> NumberOptionalNumber
Num1 Coord
0
}
data ConvolveMatrix = ConvolveMatrix
{ ConvolveMatrix -> DrawAttributes
_convolveMatrixDrawAttributes :: DrawAttributes,
ConvolveMatrix -> FilterAttributes
_convolveMatrixFilterAttr :: !FilterAttributes,
ConvolveMatrix -> Maybe FilterSource
_convolveMatrixIn :: !(Maybe FilterSource),
ConvolveMatrix -> NumberOptionalNumber
_convolveMatrixOrder :: NumberOptionalNumber,
ConvolveMatrix -> [Coord]
_convolveMatrixKernelMatrix :: [Double],
ConvolveMatrix -> Coord
_convolveMatrixDivisor :: Double,
ConvolveMatrix -> Coord
_convolveMatrixBias :: Double,
ConvolveMatrix -> Int
_convolveMatrixTargetX :: Int,
ConvolveMatrix -> Int
_convolveMatrixTargetY :: Int,
ConvolveMatrix -> EdgeMode
_convolveMatrixEdgeMode :: EdgeMode,
ConvolveMatrix -> NumberOptionalNumber
_convolveMatrixKernelUnitLength :: NumberOptionalNumber,
ConvolveMatrix -> Bool
_convolveMatrixPreserveAlpha :: Bool
}
deriving (ConvolveMatrix -> ConvolveMatrix -> Bool
(ConvolveMatrix -> ConvolveMatrix -> Bool)
-> (ConvolveMatrix -> ConvolveMatrix -> Bool) -> Eq ConvolveMatrix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConvolveMatrix -> ConvolveMatrix -> Bool
$c/= :: ConvolveMatrix -> ConvolveMatrix -> Bool
== :: ConvolveMatrix -> ConvolveMatrix -> Bool
$c== :: ConvolveMatrix -> ConvolveMatrix -> Bool
Eq, Int -> ConvolveMatrix -> ShowS
[ConvolveMatrix] -> ShowS
ConvolveMatrix -> String
(Int -> ConvolveMatrix -> ShowS)
-> (ConvolveMatrix -> String)
-> ([ConvolveMatrix] -> ShowS)
-> Show ConvolveMatrix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConvolveMatrix] -> ShowS
$cshowList :: [ConvolveMatrix] -> ShowS
show :: ConvolveMatrix -> String
$cshow :: ConvolveMatrix -> String
showsPrec :: Int -> ConvolveMatrix -> ShowS
$cshowsPrec :: Int -> ConvolveMatrix -> ShowS
Show, (forall x. ConvolveMatrix -> Rep ConvolveMatrix x)
-> (forall x. Rep ConvolveMatrix x -> ConvolveMatrix)
-> Generic ConvolveMatrix
forall x. Rep ConvolveMatrix x -> ConvolveMatrix
forall x. ConvolveMatrix -> Rep ConvolveMatrix x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConvolveMatrix x -> ConvolveMatrix
$cfrom :: forall x. ConvolveMatrix -> Rep ConvolveMatrix x
Generic)
instance WithDefaultSvg ConvolveMatrix where
defaultSvg :: ConvolveMatrix
defaultSvg =
ConvolveMatrix :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> NumberOptionalNumber
-> [Coord]
-> Coord
-> Coord
-> Int
-> Int
-> EdgeMode
-> NumberOptionalNumber
-> Bool
-> ConvolveMatrix
ConvolveMatrix
{ _convolveMatrixDrawAttributes :: DrawAttributes
_convolveMatrixDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_convolveMatrixFilterAttr :: FilterAttributes
_convolveMatrixFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_convolveMatrixIn :: Maybe FilterSource
_convolveMatrixIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_convolveMatrixOrder :: NumberOptionalNumber
_convolveMatrixOrder = Coord -> NumberOptionalNumber
Num1 Coord
3,
_convolveMatrixKernelMatrix :: [Coord]
_convolveMatrixKernelMatrix = [],
_convolveMatrixDivisor :: Coord
_convolveMatrixDivisor = Coord
1,
_convolveMatrixBias :: Coord
_convolveMatrixBias = Coord
0,
_convolveMatrixTargetX :: Int
_convolveMatrixTargetX = Int
1,
_convolveMatrixTargetY :: Int
_convolveMatrixTargetY = Int
1,
_convolveMatrixEdgeMode :: EdgeMode
_convolveMatrixEdgeMode = EdgeMode
EdgeDuplicate,
_convolveMatrixKernelUnitLength :: NumberOptionalNumber
_convolveMatrixKernelUnitLength = Coord -> NumberOptionalNumber
Num1 Coord
0,
_convolveMatrixPreserveAlpha :: Bool
_convolveMatrixPreserveAlpha = Bool
False
}
data DiffuseLighting = DiffuseLighting
{ DiffuseLighting -> DrawAttributes
_diffuseLightingDrawAttributes :: DrawAttributes,
DiffuseLighting -> FilterAttributes
_diffuseLightingFilterAttr :: !FilterAttributes,
DiffuseLighting -> Maybe FilterSource
_diffuseLightingIn :: !(Maybe FilterSource),
DiffuseLighting -> Coord
_diffuseLightingSurfaceScale :: Double,
DiffuseLighting -> Coord
_diffuseLightingDiffuseConst :: Double,
DiffuseLighting -> NumberOptionalNumber
_diffuseLightingKernelUnitLength :: NumberOptionalNumber
}
deriving (DiffuseLighting -> DiffuseLighting -> Bool
(DiffuseLighting -> DiffuseLighting -> Bool)
-> (DiffuseLighting -> DiffuseLighting -> Bool)
-> Eq DiffuseLighting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiffuseLighting -> DiffuseLighting -> Bool
$c/= :: DiffuseLighting -> DiffuseLighting -> Bool
== :: DiffuseLighting -> DiffuseLighting -> Bool
$c== :: DiffuseLighting -> DiffuseLighting -> Bool
Eq, Int -> DiffuseLighting -> ShowS
[DiffuseLighting] -> ShowS
DiffuseLighting -> String
(Int -> DiffuseLighting -> ShowS)
-> (DiffuseLighting -> String)
-> ([DiffuseLighting] -> ShowS)
-> Show DiffuseLighting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiffuseLighting] -> ShowS
$cshowList :: [DiffuseLighting] -> ShowS
show :: DiffuseLighting -> String
$cshow :: DiffuseLighting -> String
showsPrec :: Int -> DiffuseLighting -> ShowS
$cshowsPrec :: Int -> DiffuseLighting -> ShowS
Show, (forall x. DiffuseLighting -> Rep DiffuseLighting x)
-> (forall x. Rep DiffuseLighting x -> DiffuseLighting)
-> Generic DiffuseLighting
forall x. Rep DiffuseLighting x -> DiffuseLighting
forall x. DiffuseLighting -> Rep DiffuseLighting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DiffuseLighting x -> DiffuseLighting
$cfrom :: forall x. DiffuseLighting -> Rep DiffuseLighting x
Generic)
instance WithDefaultSvg DiffuseLighting where
defaultSvg :: DiffuseLighting
defaultSvg =
DiffuseLighting :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> Coord
-> Coord
-> NumberOptionalNumber
-> DiffuseLighting
DiffuseLighting
{ _diffuseLightingDrawAttributes :: DrawAttributes
_diffuseLightingDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_diffuseLightingFilterAttr :: FilterAttributes
_diffuseLightingFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_diffuseLightingIn :: Maybe FilterSource
_diffuseLightingIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_diffuseLightingSurfaceScale :: Coord
_diffuseLightingSurfaceScale = Coord
1,
_diffuseLightingDiffuseConst :: Coord
_diffuseLightingDiffuseConst = Coord
1,
_diffuseLightingKernelUnitLength :: NumberOptionalNumber
_diffuseLightingKernelUnitLength = Coord -> NumberOptionalNumber
Num1 Coord
0
}
data Morphology = Morphology
{ Morphology -> DrawAttributes
_morphologyDrawAttributes :: DrawAttributes,
Morphology -> FilterAttributes
_morphologyFilterAttr :: !FilterAttributes,
Morphology -> Maybe FilterSource
_morphologyIn :: !(Maybe FilterSource),
Morphology -> OperatorType
_morphologyOperator :: OperatorType,
Morphology -> NumberOptionalNumber
_morphologyRadius :: NumberOptionalNumber
}
deriving (Morphology -> Morphology -> Bool
(Morphology -> Morphology -> Bool)
-> (Morphology -> Morphology -> Bool) -> Eq Morphology
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Morphology -> Morphology -> Bool
$c/= :: Morphology -> Morphology -> Bool
== :: Morphology -> Morphology -> Bool
$c== :: Morphology -> Morphology -> Bool
Eq, Int -> Morphology -> ShowS
[Morphology] -> ShowS
Morphology -> String
(Int -> Morphology -> ShowS)
-> (Morphology -> String)
-> ([Morphology] -> ShowS)
-> Show Morphology
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Morphology] -> ShowS
$cshowList :: [Morphology] -> ShowS
show :: Morphology -> String
$cshow :: Morphology -> String
showsPrec :: Int -> Morphology -> ShowS
$cshowsPrec :: Int -> Morphology -> ShowS
Show, (forall x. Morphology -> Rep Morphology x)
-> (forall x. Rep Morphology x -> Morphology) -> Generic Morphology
forall x. Rep Morphology x -> Morphology
forall x. Morphology -> Rep Morphology x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Morphology x -> Morphology
$cfrom :: forall x. Morphology -> Rep Morphology x
Generic)
instance WithDefaultSvg Morphology where
defaultSvg :: Morphology
defaultSvg =
Morphology :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> OperatorType
-> NumberOptionalNumber
-> Morphology
Morphology
{ _morphologyDrawAttributes :: DrawAttributes
_morphologyDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_morphologyFilterAttr :: FilterAttributes
_morphologyFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_morphologyIn :: Maybe FilterSource
_morphologyIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_morphologyOperator :: OperatorType
_morphologyOperator = OperatorType
OperatorOver,
_morphologyRadius :: NumberOptionalNumber
_morphologyRadius = Coord -> NumberOptionalNumber
Num1 Coord
0
}
data DropShadow = DropShadow
{ DropShadow -> DrawAttributes
_dropShadowDrawAttributes :: DrawAttributes,
DropShadow -> FilterAttributes
_dropShadowFilterAttr :: !FilterAttributes,
DropShadow -> Coord
_dropShadowDx :: Double,
DropShadow -> Coord
_dropShadowDy :: Double,
DropShadow -> NumberOptionalNumber
_dropShadowStdDeviation :: NumberOptionalNumber
}
deriving (DropShadow -> DropShadow -> Bool
(DropShadow -> DropShadow -> Bool)
-> (DropShadow -> DropShadow -> Bool) -> Eq DropShadow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DropShadow -> DropShadow -> Bool
$c/= :: DropShadow -> DropShadow -> Bool
== :: DropShadow -> DropShadow -> Bool
$c== :: DropShadow -> DropShadow -> Bool
Eq, Int -> DropShadow -> ShowS
[DropShadow] -> ShowS
DropShadow -> String
(Int -> DropShadow -> ShowS)
-> (DropShadow -> String)
-> ([DropShadow] -> ShowS)
-> Show DropShadow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DropShadow] -> ShowS
$cshowList :: [DropShadow] -> ShowS
show :: DropShadow -> String
$cshow :: DropShadow -> String
showsPrec :: Int -> DropShadow -> ShowS
$cshowsPrec :: Int -> DropShadow -> ShowS
Show, (forall x. DropShadow -> Rep DropShadow x)
-> (forall x. Rep DropShadow x -> DropShadow) -> Generic DropShadow
forall x. Rep DropShadow x -> DropShadow
forall x. DropShadow -> Rep DropShadow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DropShadow x -> DropShadow
$cfrom :: forall x. DropShadow -> Rep DropShadow x
Generic)
instance WithDefaultSvg DropShadow where
defaultSvg :: DropShadow
defaultSvg =
DropShadow :: DrawAttributes
-> FilterAttributes
-> Coord
-> Coord
-> NumberOptionalNumber
-> DropShadow
DropShadow
{ _dropShadowDrawAttributes :: DrawAttributes
_dropShadowDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_dropShadowFilterAttr :: FilterAttributes
_dropShadowFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_dropShadowDx :: Coord
_dropShadowDx = Coord
2,
_dropShadowDy :: Coord
_dropShadowDy = Coord
2,
_dropShadowStdDeviation :: NumberOptionalNumber
_dropShadowStdDeviation = Coord -> NumberOptionalNumber
Num1 Coord
0
}
data OperatorType
= OperatorOver
| OperatorIn
| OperatorOut
| OperatorAtop
| OperatorXor
| OperatorLighter
| OperatorArithmetic
deriving (OperatorType -> OperatorType -> Bool
(OperatorType -> OperatorType -> Bool)
-> (OperatorType -> OperatorType -> Bool) -> Eq OperatorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperatorType -> OperatorType -> Bool
$c/= :: OperatorType -> OperatorType -> Bool
== :: OperatorType -> OperatorType -> Bool
$c== :: OperatorType -> OperatorType -> Bool
Eq, Int -> OperatorType -> ShowS
[OperatorType] -> ShowS
OperatorType -> String
(Int -> OperatorType -> ShowS)
-> (OperatorType -> String)
-> ([OperatorType] -> ShowS)
-> Show OperatorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperatorType] -> ShowS
$cshowList :: [OperatorType] -> ShowS
show :: OperatorType -> String
$cshow :: OperatorType -> String
showsPrec :: Int -> OperatorType -> ShowS
$cshowsPrec :: Int -> OperatorType -> ShowS
Show, (forall x. OperatorType -> Rep OperatorType x)
-> (forall x. Rep OperatorType x -> OperatorType)
-> Generic OperatorType
forall x. Rep OperatorType x -> OperatorType
forall x. OperatorType -> Rep OperatorType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OperatorType x -> OperatorType
$cfrom :: forall x. OperatorType -> Rep OperatorType x
Generic)
data NumberOptionalNumber
= Num1 Double
| Num2 Double Double
deriving (NumberOptionalNumber -> NumberOptionalNumber -> Bool
(NumberOptionalNumber -> NumberOptionalNumber -> Bool)
-> (NumberOptionalNumber -> NumberOptionalNumber -> Bool)
-> Eq NumberOptionalNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumberOptionalNumber -> NumberOptionalNumber -> Bool
$c/= :: NumberOptionalNumber -> NumberOptionalNumber -> Bool
== :: NumberOptionalNumber -> NumberOptionalNumber -> Bool
$c== :: NumberOptionalNumber -> NumberOptionalNumber -> Bool
Eq, Int -> NumberOptionalNumber -> ShowS
[NumberOptionalNumber] -> ShowS
NumberOptionalNumber -> String
(Int -> NumberOptionalNumber -> ShowS)
-> (NumberOptionalNumber -> String)
-> ([NumberOptionalNumber] -> ShowS)
-> Show NumberOptionalNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NumberOptionalNumber] -> ShowS
$cshowList :: [NumberOptionalNumber] -> ShowS
show :: NumberOptionalNumber -> String
$cshow :: NumberOptionalNumber -> String
showsPrec :: Int -> NumberOptionalNumber -> ShowS
$cshowsPrec :: Int -> NumberOptionalNumber -> ShowS
Show, (forall x. NumberOptionalNumber -> Rep NumberOptionalNumber x)
-> (forall x. Rep NumberOptionalNumber x -> NumberOptionalNumber)
-> Generic NumberOptionalNumber
forall x. Rep NumberOptionalNumber x -> NumberOptionalNumber
forall x. NumberOptionalNumber -> Rep NumberOptionalNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NumberOptionalNumber x -> NumberOptionalNumber
$cfrom :: forall x. NumberOptionalNumber -> Rep NumberOptionalNumber x
Generic)
data ImageF = ImageF
{ ImageF -> DrawAttributes
_imageFDrawAttributes :: DrawAttributes,
ImageF -> FilterAttributes
_imageFFilterAttr :: !FilterAttributes,
ImageF -> String
_imageFHref :: !String,
ImageF -> PreserveAspectRatio
_imageFAspectRatio :: !PreserveAspectRatio
}
deriving (ImageF -> ImageF -> Bool
(ImageF -> ImageF -> Bool)
-> (ImageF -> ImageF -> Bool) -> Eq ImageF
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageF -> ImageF -> Bool
$c/= :: ImageF -> ImageF -> Bool
== :: ImageF -> ImageF -> Bool
$c== :: ImageF -> ImageF -> Bool
Eq, Int -> ImageF -> ShowS
[ImageF] -> ShowS
ImageF -> String
(Int -> ImageF -> ShowS)
-> (ImageF -> String) -> ([ImageF] -> ShowS) -> Show ImageF
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageF] -> ShowS
$cshowList :: [ImageF] -> ShowS
show :: ImageF -> String
$cshow :: ImageF -> String
showsPrec :: Int -> ImageF -> ShowS
$cshowsPrec :: Int -> ImageF -> ShowS
Show, (forall x. ImageF -> Rep ImageF x)
-> (forall x. Rep ImageF x -> ImageF) -> Generic ImageF
forall x. Rep ImageF x -> ImageF
forall x. ImageF -> Rep ImageF x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImageF x -> ImageF
$cfrom :: forall x. ImageF -> Rep ImageF x
Generic)
instance WithDefaultSvg ImageF where
defaultSvg :: ImageF
defaultSvg =
ImageF :: DrawAttributes
-> FilterAttributes -> String -> PreserveAspectRatio -> ImageF
ImageF
{ _imageFDrawAttributes :: DrawAttributes
_imageFDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_imageFFilterAttr :: FilterAttributes
_imageFFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_imageFHref :: String
_imageFHref = String
"",
_imageFAspectRatio :: PreserveAspectRatio
_imageFAspectRatio = PreserveAspectRatio
forall a. WithDefaultSvg a => a
defaultSvg
}
data TransferFunctionType
= TFIdentity
| TFTable
| TFDiscrete
| TFLinear
| TFGamma
deriving (TransferFunctionType -> TransferFunctionType -> Bool
(TransferFunctionType -> TransferFunctionType -> Bool)
-> (TransferFunctionType -> TransferFunctionType -> Bool)
-> Eq TransferFunctionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferFunctionType -> TransferFunctionType -> Bool
$c/= :: TransferFunctionType -> TransferFunctionType -> Bool
== :: TransferFunctionType -> TransferFunctionType -> Bool
$c== :: TransferFunctionType -> TransferFunctionType -> Bool
Eq, Int -> TransferFunctionType -> ShowS
[TransferFunctionType] -> ShowS
TransferFunctionType -> String
(Int -> TransferFunctionType -> ShowS)
-> (TransferFunctionType -> String)
-> ([TransferFunctionType] -> ShowS)
-> Show TransferFunctionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferFunctionType] -> ShowS
$cshowList :: [TransferFunctionType] -> ShowS
show :: TransferFunctionType -> String
$cshow :: TransferFunctionType -> String
showsPrec :: Int -> TransferFunctionType -> ShowS
$cshowsPrec :: Int -> TransferFunctionType -> ShowS
Show, (forall x. TransferFunctionType -> Rep TransferFunctionType x)
-> (forall x. Rep TransferFunctionType x -> TransferFunctionType)
-> Generic TransferFunctionType
forall x. Rep TransferFunctionType x -> TransferFunctionType
forall x. TransferFunctionType -> Rep TransferFunctionType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransferFunctionType x -> TransferFunctionType
$cfrom :: forall x. TransferFunctionType -> Rep TransferFunctionType x
Generic)
data TransferFunction = TransferFunction
{ TransferFunction -> DrawAttributes
_transferFunctionDrawAttributes :: !DrawAttributes,
TransferFunction -> FilterAttributes
_transferFunctionFilterAttr :: !FilterAttributes,
TransferFunction -> TransferFunctionType
_transferFunctionType :: TransferFunctionType,
TransferFunction -> [Coord]
_transferFunctionTableValues :: [Double],
TransferFunction -> Coord
_transferFunctionSlope :: Double,
TransferFunction -> Coord
_transferFunctionIntercept :: Double,
TransferFunction -> Coord
_transferFunctionAmplitude :: Double,
TransferFunction -> Coord
_transferFunctionExponent :: Double,
TransferFunction -> Coord
_transferFunctionOffset :: Double
}
deriving (TransferFunction -> TransferFunction -> Bool
(TransferFunction -> TransferFunction -> Bool)
-> (TransferFunction -> TransferFunction -> Bool)
-> Eq TransferFunction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferFunction -> TransferFunction -> Bool
$c/= :: TransferFunction -> TransferFunction -> Bool
== :: TransferFunction -> TransferFunction -> Bool
$c== :: TransferFunction -> TransferFunction -> Bool
Eq, Int -> TransferFunction -> ShowS
[TransferFunction] -> ShowS
TransferFunction -> String
(Int -> TransferFunction -> ShowS)
-> (TransferFunction -> String)
-> ([TransferFunction] -> ShowS)
-> Show TransferFunction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferFunction] -> ShowS
$cshowList :: [TransferFunction] -> ShowS
show :: TransferFunction -> String
$cshow :: TransferFunction -> String
showsPrec :: Int -> TransferFunction -> ShowS
$cshowsPrec :: Int -> TransferFunction -> ShowS
Show, (forall x. TransferFunction -> Rep TransferFunction x)
-> (forall x. Rep TransferFunction x -> TransferFunction)
-> Generic TransferFunction
forall x. Rep TransferFunction x -> TransferFunction
forall x. TransferFunction -> Rep TransferFunction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransferFunction x -> TransferFunction
$cfrom :: forall x. TransferFunction -> Rep TransferFunction x
Generic)
data ChannelSelector
= ChannelR
| ChannelG
| ChannelB
| ChannelA
deriving (ChannelSelector -> ChannelSelector -> Bool
(ChannelSelector -> ChannelSelector -> Bool)
-> (ChannelSelector -> ChannelSelector -> Bool)
-> Eq ChannelSelector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChannelSelector -> ChannelSelector -> Bool
$c/= :: ChannelSelector -> ChannelSelector -> Bool
== :: ChannelSelector -> ChannelSelector -> Bool
$c== :: ChannelSelector -> ChannelSelector -> Bool
Eq, Int -> ChannelSelector -> ShowS
[ChannelSelector] -> ShowS
ChannelSelector -> String
(Int -> ChannelSelector -> ShowS)
-> (ChannelSelector -> String)
-> ([ChannelSelector] -> ShowS)
-> Show ChannelSelector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelSelector] -> ShowS
$cshowList :: [ChannelSelector] -> ShowS
show :: ChannelSelector -> String
$cshow :: ChannelSelector -> String
showsPrec :: Int -> ChannelSelector -> ShowS
$cshowsPrec :: Int -> ChannelSelector -> ShowS
Show, (forall x. ChannelSelector -> Rep ChannelSelector x)
-> (forall x. Rep ChannelSelector x -> ChannelSelector)
-> Generic ChannelSelector
forall x. Rep ChannelSelector x -> ChannelSelector
forall x. ChannelSelector -> Rep ChannelSelector x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChannelSelector x -> ChannelSelector
$cfrom :: forall x. ChannelSelector -> Rep ChannelSelector x
Generic)
data DisplacementMap = DisplacementMap
{ DisplacementMap -> DrawAttributes
_displacementMapDrawAttributes :: !DrawAttributes,
DisplacementMap -> FilterAttributes
_displacementMapFilterAttr :: !FilterAttributes,
DisplacementMap -> Maybe FilterSource
_displacementMapIn :: !(Maybe FilterSource),
DisplacementMap -> Maybe FilterSource
_displacementMapIn2 :: !(Maybe FilterSource),
DisplacementMap -> Maybe Coord
_displacementMapScale :: !(Maybe Double),
DisplacementMap -> ChannelSelector
_displacementMapXChannelSelector :: ChannelSelector,
DisplacementMap -> ChannelSelector
_displacementMapYChannelSelector :: ChannelSelector
}
deriving (DisplacementMap -> DisplacementMap -> Bool
(DisplacementMap -> DisplacementMap -> Bool)
-> (DisplacementMap -> DisplacementMap -> Bool)
-> Eq DisplacementMap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplacementMap -> DisplacementMap -> Bool
$c/= :: DisplacementMap -> DisplacementMap -> Bool
== :: DisplacementMap -> DisplacementMap -> Bool
$c== :: DisplacementMap -> DisplacementMap -> Bool
Eq, Int -> DisplacementMap -> ShowS
[DisplacementMap] -> ShowS
DisplacementMap -> String
(Int -> DisplacementMap -> ShowS)
-> (DisplacementMap -> String)
-> ([DisplacementMap] -> ShowS)
-> Show DisplacementMap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisplacementMap] -> ShowS
$cshowList :: [DisplacementMap] -> ShowS
show :: DisplacementMap -> String
$cshow :: DisplacementMap -> String
showsPrec :: Int -> DisplacementMap -> ShowS
$cshowsPrec :: Int -> DisplacementMap -> ShowS
Show, (forall x. DisplacementMap -> Rep DisplacementMap x)
-> (forall x. Rep DisplacementMap x -> DisplacementMap)
-> Generic DisplacementMap
forall x. Rep DisplacementMap x -> DisplacementMap
forall x. DisplacementMap -> Rep DisplacementMap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisplacementMap x -> DisplacementMap
$cfrom :: forall x. DisplacementMap -> Rep DisplacementMap x
Generic)
instance WithDefaultSvg DisplacementMap where
defaultSvg :: DisplacementMap
defaultSvg =
DisplacementMap :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> Maybe FilterSource
-> Maybe Coord
-> ChannelSelector
-> ChannelSelector
-> DisplacementMap
DisplacementMap
{ _displacementMapDrawAttributes :: DrawAttributes
_displacementMapDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_displacementMapFilterAttr :: FilterAttributes
_displacementMapFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_displacementMapIn :: Maybe FilterSource
_displacementMapIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_displacementMapIn2 :: Maybe FilterSource
_displacementMapIn2 = Maybe FilterSource
forall a. Maybe a
Nothing,
_displacementMapScale :: Maybe Coord
_displacementMapScale = Maybe Coord
forall a. Maybe a
Nothing,
_displacementMapXChannelSelector :: ChannelSelector
_displacementMapXChannelSelector = ChannelSelector
ChannelA,
_displacementMapYChannelSelector :: ChannelSelector
_displacementMapYChannelSelector = ChannelSelector
ChannelA
}
data BlendMode
= Normal
| Multiply
| Screen
| Overlay
| Darken
| Lighten
| ColorDodge
| ColorBurn
| HardLight
| SoftLight
| Difference
| Exclusion
| Hue
| Saturation
| Color
| Luminosity
deriving (BlendMode -> BlendMode -> Bool
(BlendMode -> BlendMode -> Bool)
-> (BlendMode -> BlendMode -> Bool) -> Eq BlendMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlendMode -> BlendMode -> Bool
$c/= :: BlendMode -> BlendMode -> Bool
== :: BlendMode -> BlendMode -> Bool
$c== :: BlendMode -> BlendMode -> Bool
Eq, Int -> BlendMode -> ShowS
[BlendMode] -> ShowS
BlendMode -> String
(Int -> BlendMode -> ShowS)
-> (BlendMode -> String)
-> ([BlendMode] -> ShowS)
-> Show BlendMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlendMode] -> ShowS
$cshowList :: [BlendMode] -> ShowS
show :: BlendMode -> String
$cshow :: BlendMode -> String
showsPrec :: Int -> BlendMode -> ShowS
$cshowsPrec :: Int -> BlendMode -> ShowS
Show, (forall x. BlendMode -> Rep BlendMode x)
-> (forall x. Rep BlendMode x -> BlendMode) -> Generic BlendMode
forall x. Rep BlendMode x -> BlendMode
forall x. BlendMode -> Rep BlendMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlendMode x -> BlendMode
$cfrom :: forall x. BlendMode -> Rep BlendMode x
Generic)
data Blend = Blend
{ Blend -> DrawAttributes
_blendDrawAttributes :: !DrawAttributes,
Blend -> FilterAttributes
_blendFilterAttr :: !FilterAttributes,
Blend -> Maybe FilterSource
_blendIn :: !(Maybe FilterSource),
Blend -> Maybe FilterSource
_blendIn2 :: !(Maybe FilterSource),
Blend -> BlendMode
_blendMode :: !BlendMode
}
deriving (Blend -> Blend -> Bool
(Blend -> Blend -> Bool) -> (Blend -> Blend -> Bool) -> Eq Blend
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Blend -> Blend -> Bool
$c/= :: Blend -> Blend -> Bool
== :: Blend -> Blend -> Bool
$c== :: Blend -> Blend -> Bool
Eq, Int -> Blend -> ShowS
[Blend] -> ShowS
Blend -> String
(Int -> Blend -> ShowS)
-> (Blend -> String) -> ([Blend] -> ShowS) -> Show Blend
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Blend] -> ShowS
$cshowList :: [Blend] -> ShowS
show :: Blend -> String
$cshow :: Blend -> String
showsPrec :: Int -> Blend -> ShowS
$cshowsPrec :: Int -> Blend -> ShowS
Show, (forall x. Blend -> Rep Blend x)
-> (forall x. Rep Blend x -> Blend) -> Generic Blend
forall x. Rep Blend x -> Blend
forall x. Blend -> Rep Blend x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Blend x -> Blend
$cfrom :: forall x. Blend -> Rep Blend x
Generic)
instance WithDefaultSvg Blend where
defaultSvg :: Blend
defaultSvg =
Blend :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> Maybe FilterSource
-> BlendMode
-> Blend
Blend
{ _blendDrawAttributes :: DrawAttributes
_blendDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_blendFilterAttr :: FilterAttributes
_blendFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_blendIn :: Maybe FilterSource
_blendIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_blendIn2 :: Maybe FilterSource
_blendIn2 = Maybe FilterSource
forall a. Maybe a
Nothing,
_blendMode :: BlendMode
_blendMode = BlendMode
Normal
}
data Flood = Flood
{ Flood -> DrawAttributes
_floodDrawAttributes :: !DrawAttributes,
Flood -> FilterAttributes
_floodFilterAttr :: !FilterAttributes,
Flood -> PixelRGBA8
_floodColor :: !PixelRGBA8,
Flood -> Maybe Coord
_floodOpacity :: !(Maybe Double)
}
deriving (Flood -> Flood -> Bool
(Flood -> Flood -> Bool) -> (Flood -> Flood -> Bool) -> Eq Flood
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Flood -> Flood -> Bool
$c/= :: Flood -> Flood -> Bool
== :: Flood -> Flood -> Bool
$c== :: Flood -> Flood -> Bool
Eq, Int -> Flood -> ShowS
[Flood] -> ShowS
Flood -> String
(Int -> Flood -> ShowS)
-> (Flood -> String) -> ([Flood] -> ShowS) -> Show Flood
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Flood] -> ShowS
$cshowList :: [Flood] -> ShowS
show :: Flood -> String
$cshow :: Flood -> String
showsPrec :: Int -> Flood -> ShowS
$cshowsPrec :: Int -> Flood -> ShowS
Show, (forall x. Flood -> Rep Flood x)
-> (forall x. Rep Flood x -> Flood) -> Generic Flood
forall x. Rep Flood x -> Flood
forall x. Flood -> Rep Flood x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Flood x -> Flood
$cfrom :: forall x. Flood -> Rep Flood x
Generic)
instance WithDefaultSvg Flood where
defaultSvg :: Flood
defaultSvg =
Flood :: DrawAttributes
-> FilterAttributes -> PixelRGBA8 -> Maybe Coord -> Flood
Flood
{ _floodDrawAttributes :: DrawAttributes
_floodDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_floodFilterAttr :: FilterAttributes
_floodFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_floodColor :: PixelRGBA8
_floodColor = Pixel8 -> Pixel8 -> Pixel8 -> Pixel8 -> PixelRGBA8
PixelRGBA8 Pixel8
0 Pixel8
0 Pixel8
0 Pixel8
255,
_floodOpacity :: Maybe Coord
_floodOpacity = Coord -> Maybe Coord
forall a. a -> Maybe a
Just Coord
1.0
}
data Offset = Offset
{ Offset -> DrawAttributes
_offsetDrawAttributes :: !DrawAttributes,
Offset -> FilterAttributes
_offsetFilterAttr :: !FilterAttributes,
Offset -> Maybe FilterSource
_offsetIn :: !(Maybe FilterSource),
Offset -> Number
_offsetDX :: !Number,
Offset -> Number
_offsetDY :: !Number
}
deriving (Offset -> Offset -> Bool
(Offset -> Offset -> Bool)
-> (Offset -> Offset -> Bool) -> Eq Offset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Offset -> Offset -> Bool
$c/= :: Offset -> Offset -> Bool
== :: Offset -> Offset -> Bool
$c== :: Offset -> Offset -> Bool
Eq, Int -> Offset -> ShowS
[Offset] -> ShowS
Offset -> String
(Int -> Offset -> ShowS)
-> (Offset -> String) -> ([Offset] -> ShowS) -> Show Offset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Offset] -> ShowS
$cshowList :: [Offset] -> ShowS
show :: Offset -> String
$cshow :: Offset -> String
showsPrec :: Int -> Offset -> ShowS
$cshowsPrec :: Int -> Offset -> ShowS
Show, (forall x. Offset -> Rep Offset x)
-> (forall x. Rep Offset x -> Offset) -> Generic Offset
forall x. Rep Offset x -> Offset
forall x. Offset -> Rep Offset x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Offset x -> Offset
$cfrom :: forall x. Offset -> Rep Offset x
Generic)
instance WithDefaultSvg Offset where
defaultSvg :: Offset
defaultSvg =
Offset :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> Number
-> Number
-> Offset
Offset
{ _offsetDrawAttributes :: DrawAttributes
_offsetDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_offsetFilterAttr :: FilterAttributes
_offsetFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_offsetIn :: Maybe FilterSource
_offsetIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_offsetDX :: Number
_offsetDX = Coord -> Number
Num Coord
0,
_offsetDY :: Number
_offsetDY = Coord -> Number
Num Coord
0
}
data Tile = Tile
{ Tile -> DrawAttributes
_tileDrawAttributes :: !DrawAttributes,
Tile -> FilterAttributes
_tileFilterAttr :: !FilterAttributes,
Tile -> Maybe FilterSource
_tileIn :: !(Maybe FilterSource)
}
deriving (Tile -> Tile -> Bool
(Tile -> Tile -> Bool) -> (Tile -> Tile -> Bool) -> Eq Tile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tile -> Tile -> Bool
$c/= :: Tile -> Tile -> Bool
== :: Tile -> Tile -> Bool
$c== :: Tile -> Tile -> Bool
Eq, Int -> Tile -> ShowS
[Tile] -> ShowS
Tile -> String
(Int -> Tile -> ShowS)
-> (Tile -> String) -> ([Tile] -> ShowS) -> Show Tile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tile] -> ShowS
$cshowList :: [Tile] -> ShowS
show :: Tile -> String
$cshow :: Tile -> String
showsPrec :: Int -> Tile -> ShowS
$cshowsPrec :: Int -> Tile -> ShowS
Show, (forall x. Tile -> Rep Tile x)
-> (forall x. Rep Tile x -> Tile) -> Generic Tile
forall x. Rep Tile x -> Tile
forall x. Tile -> Rep Tile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tile x -> Tile
$cfrom :: forall x. Tile -> Rep Tile x
Generic)
instance WithDefaultSvg Tile where
defaultSvg :: Tile
defaultSvg =
Tile :: DrawAttributes -> FilterAttributes -> Maybe FilterSource -> Tile
Tile
{ _tileDrawAttributes :: DrawAttributes
_tileDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_tileFilterAttr :: FilterAttributes
_tileFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_tileIn :: Maybe FilterSource
_tileIn = Maybe FilterSource
forall a. Maybe a
Nothing
}
data Merge = Merge
{ Merge -> DrawAttributes
_mergeDrawAttributes :: !DrawAttributes,
Merge -> FilterAttributes
_mergeFilterAttributes :: !FilterAttributes,
Merge -> [FilterElement]
_mergeChildren :: ![FilterElement]
}
deriving (Merge -> Merge -> Bool
(Merge -> Merge -> Bool) -> (Merge -> Merge -> Bool) -> Eq Merge
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Merge -> Merge -> Bool
$c/= :: Merge -> Merge -> Bool
== :: Merge -> Merge -> Bool
$c== :: Merge -> Merge -> Bool
Eq, Int -> Merge -> ShowS
[Merge] -> ShowS
Merge -> String
(Int -> Merge -> ShowS)
-> (Merge -> String) -> ([Merge] -> ShowS) -> Show Merge
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Merge] -> ShowS
$cshowList :: [Merge] -> ShowS
show :: Merge -> String
$cshow :: Merge -> String
showsPrec :: Int -> Merge -> ShowS
$cshowsPrec :: Int -> Merge -> ShowS
Show, (forall x. Merge -> Rep Merge x)
-> (forall x. Rep Merge x -> Merge) -> Generic Merge
forall x. Rep Merge x -> Merge
forall x. Merge -> Rep Merge x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Merge x -> Merge
$cfrom :: forall x. Merge -> Rep Merge x
Generic)
instance WithDefaultSvg Merge where
defaultSvg :: Merge
defaultSvg =
Merge :: DrawAttributes -> FilterAttributes -> [FilterElement] -> Merge
Merge
{ _mergeDrawAttributes :: DrawAttributes
_mergeDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_mergeFilterAttributes :: FilterAttributes
_mergeFilterAttributes = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_mergeChildren :: [FilterElement]
_mergeChildren = []
}
data MergeNode = MergeNode
{ MergeNode -> DrawAttributes
_mergeNodeDrawAttributes :: !DrawAttributes,
MergeNode -> Maybe FilterSource
_mergeNodeIn :: !(Maybe FilterSource)
}
deriving (MergeNode -> MergeNode -> Bool
(MergeNode -> MergeNode -> Bool)
-> (MergeNode -> MergeNode -> Bool) -> Eq MergeNode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MergeNode -> MergeNode -> Bool
$c/= :: MergeNode -> MergeNode -> Bool
== :: MergeNode -> MergeNode -> Bool
$c== :: MergeNode -> MergeNode -> Bool
Eq, Int -> MergeNode -> ShowS
[MergeNode] -> ShowS
MergeNode -> String
(Int -> MergeNode -> ShowS)
-> (MergeNode -> String)
-> ([MergeNode] -> ShowS)
-> Show MergeNode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MergeNode] -> ShowS
$cshowList :: [MergeNode] -> ShowS
show :: MergeNode -> String
$cshow :: MergeNode -> String
showsPrec :: Int -> MergeNode -> ShowS
$cshowsPrec :: Int -> MergeNode -> ShowS
Show, (forall x. MergeNode -> Rep MergeNode x)
-> (forall x. Rep MergeNode x -> MergeNode) -> Generic MergeNode
forall x. Rep MergeNode x -> MergeNode
forall x. MergeNode -> Rep MergeNode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MergeNode x -> MergeNode
$cfrom :: forall x. MergeNode -> Rep MergeNode x
Generic)
instance WithDefaultSvg MergeNode where
defaultSvg :: MergeNode
defaultSvg =
MergeNode :: DrawAttributes -> Maybe FilterSource -> MergeNode
MergeNode
{ _mergeNodeDrawAttributes :: DrawAttributes
_mergeNodeDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_mergeNodeIn :: Maybe FilterSource
_mergeNodeIn = Maybe FilterSource
forall a. Maybe a
Nothing
}
data ComponentTransfer = ComponentTransfer
{ ComponentTransfer -> DrawAttributes
_compTransferDrawAttributes :: !DrawAttributes,
ComponentTransfer -> FilterAttributes
_compTransferFilterAttr :: !FilterAttributes,
ComponentTransfer -> [FilterElement]
_compTransferChildren :: ![FilterElement],
ComponentTransfer -> Maybe FilterSource
_compTransferIn :: !(Maybe FilterSource)
}
deriving (ComponentTransfer -> ComponentTransfer -> Bool
(ComponentTransfer -> ComponentTransfer -> Bool)
-> (ComponentTransfer -> ComponentTransfer -> Bool)
-> Eq ComponentTransfer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComponentTransfer -> ComponentTransfer -> Bool
$c/= :: ComponentTransfer -> ComponentTransfer -> Bool
== :: ComponentTransfer -> ComponentTransfer -> Bool
$c== :: ComponentTransfer -> ComponentTransfer -> Bool
Eq, Int -> ComponentTransfer -> ShowS
[ComponentTransfer] -> ShowS
ComponentTransfer -> String
(Int -> ComponentTransfer -> ShowS)
-> (ComponentTransfer -> String)
-> ([ComponentTransfer] -> ShowS)
-> Show ComponentTransfer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComponentTransfer] -> ShowS
$cshowList :: [ComponentTransfer] -> ShowS
show :: ComponentTransfer -> String
$cshow :: ComponentTransfer -> String
showsPrec :: Int -> ComponentTransfer -> ShowS
$cshowsPrec :: Int -> ComponentTransfer -> ShowS
Show, (forall x. ComponentTransfer -> Rep ComponentTransfer x)
-> (forall x. Rep ComponentTransfer x -> ComponentTransfer)
-> Generic ComponentTransfer
forall x. Rep ComponentTransfer x -> ComponentTransfer
forall x. ComponentTransfer -> Rep ComponentTransfer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ComponentTransfer x -> ComponentTransfer
$cfrom :: forall x. ComponentTransfer -> Rep ComponentTransfer x
Generic)
instance WithDefaultSvg ComponentTransfer where
defaultSvg :: ComponentTransfer
defaultSvg =
ComponentTransfer :: DrawAttributes
-> FilterAttributes
-> [FilterElement]
-> Maybe FilterSource
-> ComponentTransfer
ComponentTransfer
{ _compTransferDrawAttributes :: DrawAttributes
_compTransferDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_compTransferFilterAttr :: FilterAttributes
_compTransferFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_compTransferChildren :: [FilterElement]
_compTransferChildren = [],
_compTransferIn :: Maybe FilterSource
_compTransferIn = Maybe FilterSource
forall a. Maybe a
Nothing
}
data FuncType
= FIdentity
| FTable
| FDiscrete
| FLinear
| FGamma
deriving (FuncType -> FuncType -> Bool
(FuncType -> FuncType -> Bool)
-> (FuncType -> FuncType -> Bool) -> Eq FuncType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncType -> FuncType -> Bool
$c/= :: FuncType -> FuncType -> Bool
== :: FuncType -> FuncType -> Bool
$c== :: FuncType -> FuncType -> Bool
Eq, Int -> FuncType -> ShowS
[FuncType] -> ShowS
FuncType -> String
(Int -> FuncType -> ShowS)
-> (FuncType -> String) -> ([FuncType] -> ShowS) -> Show FuncType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncType] -> ShowS
$cshowList :: [FuncType] -> ShowS
show :: FuncType -> String
$cshow :: FuncType -> String
showsPrec :: Int -> FuncType -> ShowS
$cshowsPrec :: Int -> FuncType -> ShowS
Show, (forall x. FuncType -> Rep FuncType x)
-> (forall x. Rep FuncType x -> FuncType) -> Generic FuncType
forall x. Rep FuncType x -> FuncType
forall x. FuncType -> Rep FuncType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncType x -> FuncType
$cfrom :: forall x. FuncType -> Rep FuncType x
Generic)
data FuncA = FuncA
{ FuncA -> DrawAttributes
_funcADrawAttributes :: !DrawAttributes,
FuncA -> FuncType
_funcAType :: !FuncType,
FuncA -> [Number]
_funcATableValues :: ![Number],
FuncA -> Number
_funcASlope :: !Number,
FuncA -> Number
_funcAIntercept :: !Number,
FuncA -> Number
_funcAAmplitude :: !Number,
FuncA -> Number
_funcAExponent :: !Number
}
deriving (FuncA -> FuncA -> Bool
(FuncA -> FuncA -> Bool) -> (FuncA -> FuncA -> Bool) -> Eq FuncA
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncA -> FuncA -> Bool
$c/= :: FuncA -> FuncA -> Bool
== :: FuncA -> FuncA -> Bool
$c== :: FuncA -> FuncA -> Bool
Eq, Int -> FuncA -> ShowS
[FuncA] -> ShowS
FuncA -> String
(Int -> FuncA -> ShowS)
-> (FuncA -> String) -> ([FuncA] -> ShowS) -> Show FuncA
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncA] -> ShowS
$cshowList :: [FuncA] -> ShowS
show :: FuncA -> String
$cshow :: FuncA -> String
showsPrec :: Int -> FuncA -> ShowS
$cshowsPrec :: Int -> FuncA -> ShowS
Show, (forall x. FuncA -> Rep FuncA x)
-> (forall x. Rep FuncA x -> FuncA) -> Generic FuncA
forall x. Rep FuncA x -> FuncA
forall x. FuncA -> Rep FuncA x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncA x -> FuncA
$cfrom :: forall x. FuncA -> Rep FuncA x
Generic)
instance WithDefaultSvg FuncA where
defaultSvg :: FuncA
defaultSvg =
FuncA :: DrawAttributes
-> FuncType
-> [Number]
-> Number
-> Number
-> Number
-> Number
-> FuncA
FuncA
{ _funcADrawAttributes :: DrawAttributes
_funcADrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_funcAType :: FuncType
_funcAType = FuncType
FIdentity,
_funcATableValues :: [Number]
_funcATableValues = [],
_funcASlope :: Number
_funcASlope = Coord -> Number
Num Coord
0,
_funcAIntercept :: Number
_funcAIntercept = Coord -> Number
Num Coord
0,
_funcAAmplitude :: Number
_funcAAmplitude = Coord -> Number
Num Coord
1,
_funcAExponent :: Number
_funcAExponent = Coord -> Number
Num Coord
1
}
data FuncR = FuncR
{ FuncR -> DrawAttributes
_funcRDrawAttributes :: !DrawAttributes,
FuncR -> FuncType
_funcRType :: !FuncType,
FuncR -> [Number]
_funcRTableValues :: ![Number],
FuncR -> Number
_funcRSlope :: !Number,
FuncR -> Number
_funcRIntercept :: !Number,
FuncR -> Number
_funcRAmplitude :: !Number,
FuncR -> Number
_funcRExponent :: !Number
}
deriving (FuncR -> FuncR -> Bool
(FuncR -> FuncR -> Bool) -> (FuncR -> FuncR -> Bool) -> Eq FuncR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncR -> FuncR -> Bool
$c/= :: FuncR -> FuncR -> Bool
== :: FuncR -> FuncR -> Bool
$c== :: FuncR -> FuncR -> Bool
Eq, Int -> FuncR -> ShowS
[FuncR] -> ShowS
FuncR -> String
(Int -> FuncR -> ShowS)
-> (FuncR -> String) -> ([FuncR] -> ShowS) -> Show FuncR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncR] -> ShowS
$cshowList :: [FuncR] -> ShowS
show :: FuncR -> String
$cshow :: FuncR -> String
showsPrec :: Int -> FuncR -> ShowS
$cshowsPrec :: Int -> FuncR -> ShowS
Show, (forall x. FuncR -> Rep FuncR x)
-> (forall x. Rep FuncR x -> FuncR) -> Generic FuncR
forall x. Rep FuncR x -> FuncR
forall x. FuncR -> Rep FuncR x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncR x -> FuncR
$cfrom :: forall x. FuncR -> Rep FuncR x
Generic)
instance WithDefaultSvg FuncR where
defaultSvg :: FuncR
defaultSvg =
FuncR :: DrawAttributes
-> FuncType
-> [Number]
-> Number
-> Number
-> Number
-> Number
-> FuncR
FuncR
{ _funcRDrawAttributes :: DrawAttributes
_funcRDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_funcRType :: FuncType
_funcRType = FuncType
FIdentity,
_funcRTableValues :: [Number]
_funcRTableValues = [],
_funcRSlope :: Number
_funcRSlope = Coord -> Number
Num Coord
0,
_funcRIntercept :: Number
_funcRIntercept = Coord -> Number
Num Coord
0,
_funcRAmplitude :: Number
_funcRAmplitude = Coord -> Number
Num Coord
1,
_funcRExponent :: Number
_funcRExponent = Coord -> Number
Num Coord
1
}
data FuncG = FuncG
{ FuncG -> DrawAttributes
_funcGDrawAttributes :: !DrawAttributes,
FuncG -> FuncType
_funcGType :: !FuncType,
FuncG -> [Number]
_funcGTableValues :: ![Number],
FuncG -> Number
_funcGSlope :: !Number,
FuncG -> Number
_funcGIntercept :: !Number,
FuncG -> Number
_funcGAmplitude :: !Number,
FuncG -> Number
_funcGExponent :: !Number
}
deriving (FuncG -> FuncG -> Bool
(FuncG -> FuncG -> Bool) -> (FuncG -> FuncG -> Bool) -> Eq FuncG
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncG -> FuncG -> Bool
$c/= :: FuncG -> FuncG -> Bool
== :: FuncG -> FuncG -> Bool
$c== :: FuncG -> FuncG -> Bool
Eq, Int -> FuncG -> ShowS
[FuncG] -> ShowS
FuncG -> String
(Int -> FuncG -> ShowS)
-> (FuncG -> String) -> ([FuncG] -> ShowS) -> Show FuncG
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncG] -> ShowS
$cshowList :: [FuncG] -> ShowS
show :: FuncG -> String
$cshow :: FuncG -> String
showsPrec :: Int -> FuncG -> ShowS
$cshowsPrec :: Int -> FuncG -> ShowS
Show, (forall x. FuncG -> Rep FuncG x)
-> (forall x. Rep FuncG x -> FuncG) -> Generic FuncG
forall x. Rep FuncG x -> FuncG
forall x. FuncG -> Rep FuncG x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncG x -> FuncG
$cfrom :: forall x. FuncG -> Rep FuncG x
Generic)
instance WithDefaultSvg FuncG where
defaultSvg :: FuncG
defaultSvg =
FuncG :: DrawAttributes
-> FuncType
-> [Number]
-> Number
-> Number
-> Number
-> Number
-> FuncG
FuncG
{ _funcGDrawAttributes :: DrawAttributes
_funcGDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_funcGType :: FuncType
_funcGType = FuncType
FIdentity,
_funcGTableValues :: [Number]
_funcGTableValues = [],
_funcGSlope :: Number
_funcGSlope = Coord -> Number
Num Coord
0,
_funcGIntercept :: Number
_funcGIntercept = Coord -> Number
Num Coord
0,
_funcGAmplitude :: Number
_funcGAmplitude = Coord -> Number
Num Coord
1,
_funcGExponent :: Number
_funcGExponent = Coord -> Number
Num Coord
1
}
data FuncB = FuncB
{ FuncB -> DrawAttributes
_funcBDrawAttributes :: !DrawAttributes,
FuncB -> FuncType
_funcBType :: !FuncType,
FuncB -> [Number]
_funcBTableValues :: ![Number],
FuncB -> Number
_funcBSlope :: !Number,
FuncB -> Number
_funcBIntercept :: !Number,
FuncB -> Number
_funcBAmplitude :: !Number,
FuncB -> Number
_funcBExponent :: !Number
}
deriving (FuncB -> FuncB -> Bool
(FuncB -> FuncB -> Bool) -> (FuncB -> FuncB -> Bool) -> Eq FuncB
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncB -> FuncB -> Bool
$c/= :: FuncB -> FuncB -> Bool
== :: FuncB -> FuncB -> Bool
$c== :: FuncB -> FuncB -> Bool
Eq, Int -> FuncB -> ShowS
[FuncB] -> ShowS
FuncB -> String
(Int -> FuncB -> ShowS)
-> (FuncB -> String) -> ([FuncB] -> ShowS) -> Show FuncB
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncB] -> ShowS
$cshowList :: [FuncB] -> ShowS
show :: FuncB -> String
$cshow :: FuncB -> String
showsPrec :: Int -> FuncB -> ShowS
$cshowsPrec :: Int -> FuncB -> ShowS
Show, (forall x. FuncB -> Rep FuncB x)
-> (forall x. Rep FuncB x -> FuncB) -> Generic FuncB
forall x. Rep FuncB x -> FuncB
forall x. FuncB -> Rep FuncB x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncB x -> FuncB
$cfrom :: forall x. FuncB -> Rep FuncB x
Generic)
instance WithDefaultSvg FuncB where
defaultSvg :: FuncB
defaultSvg =
FuncB :: DrawAttributes
-> FuncType
-> [Number]
-> Number
-> Number
-> Number
-> Number
-> FuncB
FuncB
{ _funcBDrawAttributes :: DrawAttributes
_funcBDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_funcBType :: FuncType
_funcBType = FuncType
FIdentity,
_funcBTableValues :: [Number]
_funcBTableValues = [],
_funcBSlope :: Number
_funcBSlope = Coord -> Number
Num Coord
0,
_funcBIntercept :: Number
_funcBIntercept = Coord -> Number
Num Coord
0,
_funcBAmplitude :: Number
_funcBAmplitude = Coord -> Number
Num Coord
1,
_funcBExponent :: Number
_funcBExponent = Coord -> Number
Num Coord
1
}
data ColorMatrixType
= Matrix
| Saturate
| HueRotate
| LuminanceToAlpha
deriving (ColorMatrixType -> ColorMatrixType -> Bool
(ColorMatrixType -> ColorMatrixType -> Bool)
-> (ColorMatrixType -> ColorMatrixType -> Bool)
-> Eq ColorMatrixType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorMatrixType -> ColorMatrixType -> Bool
$c/= :: ColorMatrixType -> ColorMatrixType -> Bool
== :: ColorMatrixType -> ColorMatrixType -> Bool
$c== :: ColorMatrixType -> ColorMatrixType -> Bool
Eq, Int -> ColorMatrixType -> ShowS
[ColorMatrixType] -> ShowS
ColorMatrixType -> String
(Int -> ColorMatrixType -> ShowS)
-> (ColorMatrixType -> String)
-> ([ColorMatrixType] -> ShowS)
-> Show ColorMatrixType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColorMatrixType] -> ShowS
$cshowList :: [ColorMatrixType] -> ShowS
show :: ColorMatrixType -> String
$cshow :: ColorMatrixType -> String
showsPrec :: Int -> ColorMatrixType -> ShowS
$cshowsPrec :: Int -> ColorMatrixType -> ShowS
Show, (forall x. ColorMatrixType -> Rep ColorMatrixType x)
-> (forall x. Rep ColorMatrixType x -> ColorMatrixType)
-> Generic ColorMatrixType
forall x. Rep ColorMatrixType x -> ColorMatrixType
forall x. ColorMatrixType -> Rep ColorMatrixType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColorMatrixType x -> ColorMatrixType
$cfrom :: forall x. ColorMatrixType -> Rep ColorMatrixType x
Generic)
data ColorMatrix = ColorMatrix
{ ColorMatrix -> DrawAttributes
_colorMatrixDrawAttributes :: !DrawAttributes,
ColorMatrix -> FilterAttributes
_colorMatrixFilterAttr :: !FilterAttributes,
ColorMatrix -> Maybe FilterSource
_colorMatrixIn :: !(Maybe FilterSource),
ColorMatrix -> ColorMatrixType
_colorMatrixType :: !ColorMatrixType,
ColorMatrix -> String
_colorMatrixValues :: !String
}
deriving (ColorMatrix -> ColorMatrix -> Bool
(ColorMatrix -> ColorMatrix -> Bool)
-> (ColorMatrix -> ColorMatrix -> Bool) -> Eq ColorMatrix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorMatrix -> ColorMatrix -> Bool
$c/= :: ColorMatrix -> ColorMatrix -> Bool
== :: ColorMatrix -> ColorMatrix -> Bool
$c== :: ColorMatrix -> ColorMatrix -> Bool
Eq, Int -> ColorMatrix -> ShowS
[ColorMatrix] -> ShowS
ColorMatrix -> String
(Int -> ColorMatrix -> ShowS)
-> (ColorMatrix -> String)
-> ([ColorMatrix] -> ShowS)
-> Show ColorMatrix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColorMatrix] -> ShowS
$cshowList :: [ColorMatrix] -> ShowS
show :: ColorMatrix -> String
$cshow :: ColorMatrix -> String
showsPrec :: Int -> ColorMatrix -> ShowS
$cshowsPrec :: Int -> ColorMatrix -> ShowS
Show, (forall x. ColorMatrix -> Rep ColorMatrix x)
-> (forall x. Rep ColorMatrix x -> ColorMatrix)
-> Generic ColorMatrix
forall x. Rep ColorMatrix x -> ColorMatrix
forall x. ColorMatrix -> Rep ColorMatrix x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColorMatrix x -> ColorMatrix
$cfrom :: forall x. ColorMatrix -> Rep ColorMatrix x
Generic)
instance WithDefaultSvg ColorMatrix where
defaultSvg :: ColorMatrix
defaultSvg =
ColorMatrix :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> ColorMatrixType
-> String
-> ColorMatrix
ColorMatrix
{ _colorMatrixDrawAttributes :: DrawAttributes
_colorMatrixDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_colorMatrixFilterAttr :: FilterAttributes
_colorMatrixFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_colorMatrixIn :: Maybe FilterSource
_colorMatrixIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_colorMatrixType :: ColorMatrixType
_colorMatrixType = ColorMatrixType
Matrix,
_colorMatrixValues :: String
_colorMatrixValues = String
""
}
data CompositeOperator
= CompositeOver
| CompositeIn
| CompositeOut
| CompositeAtop
| CompositeXor
| CompositeArithmetic
deriving (CompositeOperator -> CompositeOperator -> Bool
(CompositeOperator -> CompositeOperator -> Bool)
-> (CompositeOperator -> CompositeOperator -> Bool)
-> Eq CompositeOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompositeOperator -> CompositeOperator -> Bool
$c/= :: CompositeOperator -> CompositeOperator -> Bool
== :: CompositeOperator -> CompositeOperator -> Bool
$c== :: CompositeOperator -> CompositeOperator -> Bool
Eq, Int -> CompositeOperator -> ShowS
[CompositeOperator] -> ShowS
CompositeOperator -> String
(Int -> CompositeOperator -> ShowS)
-> (CompositeOperator -> String)
-> ([CompositeOperator] -> ShowS)
-> Show CompositeOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompositeOperator] -> ShowS
$cshowList :: [CompositeOperator] -> ShowS
show :: CompositeOperator -> String
$cshow :: CompositeOperator -> String
showsPrec :: Int -> CompositeOperator -> ShowS
$cshowsPrec :: Int -> CompositeOperator -> ShowS
Show, (forall x. CompositeOperator -> Rep CompositeOperator x)
-> (forall x. Rep CompositeOperator x -> CompositeOperator)
-> Generic CompositeOperator
forall x. Rep CompositeOperator x -> CompositeOperator
forall x. CompositeOperator -> Rep CompositeOperator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompositeOperator x -> CompositeOperator
$cfrom :: forall x. CompositeOperator -> Rep CompositeOperator x
Generic)
data Composite = Composite
{ Composite -> DrawAttributes
_compositeDrawAttributes :: DrawAttributes,
Composite -> FilterAttributes
_compositeFilterAttr :: !FilterAttributes,
Composite -> Maybe FilterSource
_compositeIn :: Maybe FilterSource,
Composite -> Maybe FilterSource
_compositeIn2 :: Maybe FilterSource,
Composite -> CompositeOperator
_compositeOperator :: CompositeOperator,
Composite -> Number
_compositeK1 :: Number,
Composite -> Number
_compositeK2 :: Number,
Composite -> Number
_compositeK3 :: Number,
Composite -> Number
_compositeK4 :: Number
}
deriving (Composite -> Composite -> Bool
(Composite -> Composite -> Bool)
-> (Composite -> Composite -> Bool) -> Eq Composite
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Composite -> Composite -> Bool
$c/= :: Composite -> Composite -> Bool
== :: Composite -> Composite -> Bool
$c== :: Composite -> Composite -> Bool
Eq, Int -> Composite -> ShowS
[Composite] -> ShowS
Composite -> String
(Int -> Composite -> ShowS)
-> (Composite -> String)
-> ([Composite] -> ShowS)
-> Show Composite
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Composite] -> ShowS
$cshowList :: [Composite] -> ShowS
show :: Composite -> String
$cshow :: Composite -> String
showsPrec :: Int -> Composite -> ShowS
$cshowsPrec :: Int -> Composite -> ShowS
Show, (forall x. Composite -> Rep Composite x)
-> (forall x. Rep Composite x -> Composite) -> Generic Composite
forall x. Rep Composite x -> Composite
forall x. Composite -> Rep Composite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Composite x -> Composite
$cfrom :: forall x. Composite -> Rep Composite x
Generic)
instance WithDefaultSvg Composite where
defaultSvg :: Composite
defaultSvg =
Composite :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> Maybe FilterSource
-> CompositeOperator
-> Number
-> Number
-> Number
-> Number
-> Composite
Composite
{ _compositeDrawAttributes :: DrawAttributes
_compositeDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_compositeFilterAttr :: FilterAttributes
_compositeFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_compositeIn :: Maybe FilterSource
_compositeIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_compositeIn2 :: Maybe FilterSource
_compositeIn2 = Maybe FilterSource
forall a. Maybe a
Nothing,
_compositeOperator :: CompositeOperator
_compositeOperator = CompositeOperator
CompositeOver,
_compositeK1 :: Number
_compositeK1 = Coord -> Number
Num Coord
0,
_compositeK2 :: Number
_compositeK2 = Coord -> Number
Num Coord
0,
_compositeK3 :: Number
_compositeK3 = Coord -> Number
Num Coord
0,
_compositeK4 :: Number
_compositeK4 = Coord -> Number
Num Coord
0
}
data Turbulence = Turbulence
{ Turbulence -> DrawAttributes
_turbulenceDrawAttributes :: !DrawAttributes,
Turbulence -> FilterAttributes
_turbulenceFilterAttr :: !FilterAttributes,
Turbulence -> (Coord, Maybe Coord)
_turbulenceBaseFrequency :: !(Double, Maybe Double),
Turbulence -> Int
_turbulenceNumOctaves :: Int,
Turbulence -> Coord
_turbulenceSeed :: Double,
Turbulence -> StitchTiles
_turbulenceStitchTiles :: StitchTiles,
Turbulence -> TurbulenceType
_turbulenceType :: TurbulenceType
}
deriving (Turbulence -> Turbulence -> Bool
(Turbulence -> Turbulence -> Bool)
-> (Turbulence -> Turbulence -> Bool) -> Eq Turbulence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Turbulence -> Turbulence -> Bool
$c/= :: Turbulence -> Turbulence -> Bool
== :: Turbulence -> Turbulence -> Bool
$c== :: Turbulence -> Turbulence -> Bool
Eq, Int -> Turbulence -> ShowS
[Turbulence] -> ShowS
Turbulence -> String
(Int -> Turbulence -> ShowS)
-> (Turbulence -> String)
-> ([Turbulence] -> ShowS)
-> Show Turbulence
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Turbulence] -> ShowS
$cshowList :: [Turbulence] -> ShowS
show :: Turbulence -> String
$cshow :: Turbulence -> String
showsPrec :: Int -> Turbulence -> ShowS
$cshowsPrec :: Int -> Turbulence -> ShowS
Show, (forall x. Turbulence -> Rep Turbulence x)
-> (forall x. Rep Turbulence x -> Turbulence) -> Generic Turbulence
forall x. Rep Turbulence x -> Turbulence
forall x. Turbulence -> Rep Turbulence x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Turbulence x -> Turbulence
$cfrom :: forall x. Turbulence -> Rep Turbulence x
Generic)
data StitchTiles
= NoStitch
| Stitch
deriving (StitchTiles -> StitchTiles -> Bool
(StitchTiles -> StitchTiles -> Bool)
-> (StitchTiles -> StitchTiles -> Bool) -> Eq StitchTiles
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StitchTiles -> StitchTiles -> Bool
$c/= :: StitchTiles -> StitchTiles -> Bool
== :: StitchTiles -> StitchTiles -> Bool
$c== :: StitchTiles -> StitchTiles -> Bool
Eq, Int -> StitchTiles -> ShowS
[StitchTiles] -> ShowS
StitchTiles -> String
(Int -> StitchTiles -> ShowS)
-> (StitchTiles -> String)
-> ([StitchTiles] -> ShowS)
-> Show StitchTiles
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StitchTiles] -> ShowS
$cshowList :: [StitchTiles] -> ShowS
show :: StitchTiles -> String
$cshow :: StitchTiles -> String
showsPrec :: Int -> StitchTiles -> ShowS
$cshowsPrec :: Int -> StitchTiles -> ShowS
Show, (forall x. StitchTiles -> Rep StitchTiles x)
-> (forall x. Rep StitchTiles x -> StitchTiles)
-> Generic StitchTiles
forall x. Rep StitchTiles x -> StitchTiles
forall x. StitchTiles -> Rep StitchTiles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StitchTiles x -> StitchTiles
$cfrom :: forall x. StitchTiles -> Rep StitchTiles x
Generic)
data TurbulenceType
= FractalNoiseType
| TurbulenceType
deriving (TurbulenceType -> TurbulenceType -> Bool
(TurbulenceType -> TurbulenceType -> Bool)
-> (TurbulenceType -> TurbulenceType -> Bool) -> Eq TurbulenceType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TurbulenceType -> TurbulenceType -> Bool
$c/= :: TurbulenceType -> TurbulenceType -> Bool
== :: TurbulenceType -> TurbulenceType -> Bool
$c== :: TurbulenceType -> TurbulenceType -> Bool
Eq, Int -> TurbulenceType -> ShowS
[TurbulenceType] -> ShowS
TurbulenceType -> String
(Int -> TurbulenceType -> ShowS)
-> (TurbulenceType -> String)
-> ([TurbulenceType] -> ShowS)
-> Show TurbulenceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TurbulenceType] -> ShowS
$cshowList :: [TurbulenceType] -> ShowS
show :: TurbulenceType -> String
$cshow :: TurbulenceType -> String
showsPrec :: Int -> TurbulenceType -> ShowS
$cshowsPrec :: Int -> TurbulenceType -> ShowS
Show, (forall x. TurbulenceType -> Rep TurbulenceType x)
-> (forall x. Rep TurbulenceType x -> TurbulenceType)
-> Generic TurbulenceType
forall x. Rep TurbulenceType x -> TurbulenceType
forall x. TurbulenceType -> Rep TurbulenceType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TurbulenceType x -> TurbulenceType
$cfrom :: forall x. TurbulenceType -> Rep TurbulenceType x
Generic)
instance WithDefaultSvg Turbulence where
defaultSvg :: Turbulence
defaultSvg =
Turbulence :: DrawAttributes
-> FilterAttributes
-> (Coord, Maybe Coord)
-> Int
-> Coord
-> StitchTiles
-> TurbulenceType
-> Turbulence
Turbulence
{ _turbulenceDrawAttributes :: DrawAttributes
_turbulenceDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_turbulenceFilterAttr :: FilterAttributes
_turbulenceFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_turbulenceBaseFrequency :: (Coord, Maybe Coord)
_turbulenceBaseFrequency = (Coord
0, Maybe Coord
forall a. Maybe a
Nothing),
_turbulenceNumOctaves :: Int
_turbulenceNumOctaves = Int
1,
_turbulenceSeed :: Coord
_turbulenceSeed = Coord
0,
_turbulenceStitchTiles :: StitchTiles
_turbulenceStitchTiles = StitchTiles
NoStitch,
_turbulenceType :: TurbulenceType
_turbulenceType = TurbulenceType
TurbulenceType
}
data EdgeMode
= EdgeDuplicate
| EdgeWrap
| EdgeNone
deriving (EdgeMode -> EdgeMode -> Bool
(EdgeMode -> EdgeMode -> Bool)
-> (EdgeMode -> EdgeMode -> Bool) -> Eq EdgeMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EdgeMode -> EdgeMode -> Bool
$c/= :: EdgeMode -> EdgeMode -> Bool
== :: EdgeMode -> EdgeMode -> Bool
$c== :: EdgeMode -> EdgeMode -> Bool
Eq, Int -> EdgeMode -> ShowS
[EdgeMode] -> ShowS
EdgeMode -> String
(Int -> EdgeMode -> ShowS)
-> (EdgeMode -> String) -> ([EdgeMode] -> ShowS) -> Show EdgeMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EdgeMode] -> ShowS
$cshowList :: [EdgeMode] -> ShowS
show :: EdgeMode -> String
$cshow :: EdgeMode -> String
showsPrec :: Int -> EdgeMode -> ShowS
$cshowsPrec :: Int -> EdgeMode -> ShowS
Show, (forall x. EdgeMode -> Rep EdgeMode x)
-> (forall x. Rep EdgeMode x -> EdgeMode) -> Generic EdgeMode
forall x. Rep EdgeMode x -> EdgeMode
forall x. EdgeMode -> Rep EdgeMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EdgeMode x -> EdgeMode
$cfrom :: forall x. EdgeMode -> Rep EdgeMode x
Generic)
data GaussianBlur = GaussianBlur
{ GaussianBlur -> DrawAttributes
_gaussianBlurDrawAttributes :: DrawAttributes,
GaussianBlur -> FilterAttributes
_gaussianBlurFilterAttr :: !FilterAttributes,
GaussianBlur -> Maybe FilterSource
_gaussianBlurIn :: Maybe FilterSource,
GaussianBlur -> Number
_gaussianBlurStdDeviationX :: Number,
GaussianBlur -> Maybe Number
_gaussianBlurStdDeviationY :: Maybe Number,
GaussianBlur -> EdgeMode
_gaussianBlurEdgeMode :: EdgeMode
}
deriving (GaussianBlur -> GaussianBlur -> Bool
(GaussianBlur -> GaussianBlur -> Bool)
-> (GaussianBlur -> GaussianBlur -> Bool) -> Eq GaussianBlur
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GaussianBlur -> GaussianBlur -> Bool
$c/= :: GaussianBlur -> GaussianBlur -> Bool
== :: GaussianBlur -> GaussianBlur -> Bool
$c== :: GaussianBlur -> GaussianBlur -> Bool
Eq, Int -> GaussianBlur -> ShowS
[GaussianBlur] -> ShowS
GaussianBlur -> String
(Int -> GaussianBlur -> ShowS)
-> (GaussianBlur -> String)
-> ([GaussianBlur] -> ShowS)
-> Show GaussianBlur
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GaussianBlur] -> ShowS
$cshowList :: [GaussianBlur] -> ShowS
show :: GaussianBlur -> String
$cshow :: GaussianBlur -> String
showsPrec :: Int -> GaussianBlur -> ShowS
$cshowsPrec :: Int -> GaussianBlur -> ShowS
Show, (forall x. GaussianBlur -> Rep GaussianBlur x)
-> (forall x. Rep GaussianBlur x -> GaussianBlur)
-> Generic GaussianBlur
forall x. Rep GaussianBlur x -> GaussianBlur
forall x. GaussianBlur -> Rep GaussianBlur x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GaussianBlur x -> GaussianBlur
$cfrom :: forall x. GaussianBlur -> Rep GaussianBlur x
Generic)
instance WithDefaultSvg GaussianBlur where
defaultSvg :: GaussianBlur
defaultSvg =
GaussianBlur :: DrawAttributes
-> FilterAttributes
-> Maybe FilterSource
-> Number
-> Maybe Number
-> EdgeMode
-> GaussianBlur
GaussianBlur
{ _gaussianBlurDrawAttributes :: DrawAttributes
_gaussianBlurDrawAttributes = DrawAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_gaussianBlurFilterAttr :: FilterAttributes
_gaussianBlurFilterAttr = FilterAttributes
forall a. WithDefaultSvg a => a
defaultSvg,
_gaussianBlurIn :: Maybe FilterSource
_gaussianBlurIn = Maybe FilterSource
forall a. Maybe a
Nothing,
_gaussianBlurStdDeviationX :: Number
_gaussianBlurStdDeviationX = Coord -> Number
Num Coord
0,
_gaussianBlurStdDeviationY :: Maybe Number
_gaussianBlurStdDeviationY = Maybe Number
forall a. Maybe a
Nothing,
_gaussianBlurEdgeMode :: EdgeMode
_gaussianBlurEdgeMode = EdgeMode
EdgeDuplicate
}
data MarkerOrientation
=
OrientationAuto
|
OrientationAngle Coord
deriving (MarkerOrientation -> MarkerOrientation -> Bool
(MarkerOrientation -> MarkerOrientation -> Bool)
-> (MarkerOrientation -> MarkerOrientation -> Bool)
-> Eq MarkerOrientation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkerOrientation -> MarkerOrientation -> Bool
$c/= :: MarkerOrientation -> MarkerOrientation -> Bool
== :: MarkerOrientation -> MarkerOrientation -> Bool
$c== :: MarkerOrientation -> MarkerOrientation -> Bool
Eq, Int -> MarkerOrientation -> ShowS
[MarkerOrientation] -> ShowS
MarkerOrientation -> String
(Int -> MarkerOrientation -> ShowS)
-> (MarkerOrientation -> String)
-> ([MarkerOrientation] -> ShowS)
-> Show MarkerOrientation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MarkerOrientation] -> ShowS
$cshowList :: [MarkerOrientation] -> ShowS
show :: MarkerOrientation -> String
$cshow :: MarkerOrientation -> String
showsPrec :: Int -> MarkerOrientation -> ShowS
$cshowsPrec :: Int -> MarkerOrientation -> ShowS
Show, (forall x. MarkerOrientation -> Rep MarkerOrientation x)
-> (forall x. Rep MarkerOrientation x -> MarkerOrientation)
-> Generic MarkerOrientation
forall x. Rep MarkerOrientation x -> MarkerOrientation
forall x. MarkerOrientation -> Rep MarkerOrientation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MarkerOrientation x -> MarkerOrientation
$cfrom :: forall x. MarkerOrientation -> Rep MarkerOrientation x
Generic)
data MarkerUnit
=
MarkerUnitStrokeWidth
|
MarkerUnitUserSpaceOnUse
deriving (MarkerUnit -> MarkerUnit -> Bool
(MarkerUnit -> MarkerUnit -> Bool)
-> (MarkerUnit -> MarkerUnit -> Bool) -> Eq MarkerUnit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkerUnit -> MarkerUnit -> Bool
$c/= :: MarkerUnit -> MarkerUnit -> Bool
== :: MarkerUnit -> MarkerUnit -> Bool
$c== :: MarkerUnit -> MarkerUnit -> Bool
Eq, Int -> MarkerUnit -> ShowS
[MarkerUnit] -> ShowS
MarkerUnit -> String
(Int -> MarkerUnit -> ShowS)
-> (MarkerUnit -> String)
-> ([MarkerUnit] -> ShowS)
-> Show MarkerUnit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MarkerUnit] -> ShowS
$cshowList :: [MarkerUnit] -> ShowS
show :: MarkerUnit -> String
$cshow :: MarkerUnit -> String
showsPrec :: Int -> MarkerUnit -> ShowS
$cshowsPrec :: Int -> MarkerUnit -> ShowS
Show, (forall x. MarkerUnit -> Rep MarkerUnit x)
-> (forall x. Rep MarkerUnit x -> MarkerUnit) -> Generic MarkerUnit
forall x. Rep MarkerUnit x -> MarkerUnit
forall x. MarkerUnit -> Rep MarkerUnit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MarkerUnit x -> MarkerUnit
$cfrom :: forall x. MarkerUnit -> Rep MarkerUnit x
Generic)
data Overflow
=
OverflowVisible
|
OverflowHidden
deriving (Overflow -> Overflow -> Bool
(Overflow -> Overflow -> Bool)
-> (Overflow -> Overflow -> Bool) -> Eq Overflow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Overflow -> Overflow -> Bool
$c/= :: Overflow -> Overflow -> Bool
== :: Overflow -> Overflow -> Bool
$c== :: Overflow -> Overflow -> Bool
Eq, Int -> Overflow -> ShowS
[Overflow] -> ShowS
Overflow -> String
(Int -> Overflow -> ShowS)
-> (Overflow -> String) -> ([Overflow] -> ShowS) -> Show Overflow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Overflow] -> ShowS
$cshowList :: [Overflow] -> ShowS
show :: Overflow -> String
$cshow :: Overflow -> String
showsPrec :: Int -> Overflow -> ShowS
$cshowsPrec :: Int -> Overflow -> ShowS
Show, (forall x. Overflow -> Rep Overflow x)
-> (forall x. Rep Overflow x -> Overflow) -> Generic Overflow
forall x. Rep Overflow x -> Overflow
forall x. Overflow -> Rep Overflow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Overflow x -> Overflow
$cfrom :: forall x. Overflow -> Rep Overflow x
Generic)
data Marker = Marker
{ Marker -> DrawAttributes
_markerDrawAttributes :: DrawAttributes,
Marker -> Point
_markerRefPoint :: !(Number, Number),
Marker -> Maybe Number
_markerWidth :: !(Maybe Number),
Marker -> Maybe Number
_markerHeight :: !(Maybe Number),
Marker -> Maybe MarkerOrientation
_markerOrient :: !(Maybe MarkerOrientation),
Marker -> Maybe MarkerUnit
_markerUnits :: !(Maybe MarkerUnit),
Marker -> Maybe (Coord, Coord, Coord, Coord)
_markerViewBox :: !(Maybe (Double, Double, Double, Double)),
Marker -> Maybe Overflow
_markerOverflow :: !(Maybe Overflow),
Marker -> PreserveAspectRatio
_markerAspectRatio :: !PreserveAspectRatio,
Marker -> [Tree]
_markerElements :: [Tree]
}
deriving (Marker -> Marker -> Bool
(Marker -> Marker -> Bool)
-> (Marker -> Marker -> Bool) -> Eq Marker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Marker -> Marker -> Bool
$c/= :: Marker -> Marker -> Bool
== :: Marker -> Marker -> Bool
$c== :: Marker -> Marker -> Bool
Eq, Int -> Marker -> ShowS
[Marker] -> ShowS
Marker -> String
(Int -> Marker -> ShowS)
-> (Marker -> String) -> ([Marker] -> ShowS) -> Show Marker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Marker] -> ShowS
$cshowList :: [Marker] -> ShowS
show :: Marker -> String
$cshow :: Marker -> String
showsPrec :: Int -> Marker -> ShowS
$cshowsPrec :: Int -> Marker -> ShowS
Show, (forall x. Marker -> Rep Marker x)
-> (forall x. Rep Marker x -> Marker) -> Generic Marker
forall x. Rep Marker x -> Marker
forall x. Marker -> Rep Marker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Marker x -> Marker
$cfrom :: forall x. Marker -> Rep Marker x
Generic)
instance WithDefaultSvg Marker where
defaultSvg :: Marker
defaultSvg =
Marker :: DrawAttributes
-> Point
-> Maybe Number
-> Maybe Number
-> Maybe MarkerOrientation
-> Maybe MarkerUnit
-> Maybe (Coord, Coord, Coord, Coord)
-> Maybe Overflow
-> PreserveAspectRatio
-> [Tree]
-> Marker
Marker
{ _markerDrawAttributes :: DrawAttributes
_markerDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_markerRefPoint :: Point
_markerRefPoint = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0),
_markerWidth :: Maybe Number
_markerWidth = Number -> Maybe Number
forall a. a -> Maybe a
Just (Coord -> Number
Num Coord
3),
_markerHeight :: Maybe Number
_markerHeight = Number -> Maybe Number
forall a. a -> Maybe a
Just (Coord -> Number
Num Coord
3),
_markerOrient :: Maybe MarkerOrientation
_markerOrient = Maybe MarkerOrientation
forall a. Maybe a
Nothing,
_markerUnits :: Maybe MarkerUnit
_markerUnits = Maybe MarkerUnit
forall a. Maybe a
Nothing,
_markerViewBox :: Maybe (Coord, Coord, Coord, Coord)
_markerViewBox = Maybe (Coord, Coord, Coord, Coord)
forall a. Maybe a
Nothing,
_markerOverflow :: Maybe Overflow
_markerOverflow = Maybe Overflow
forall a. Maybe a
Nothing,
_markerElements :: [Tree]
_markerElements = [Tree]
forall a. Monoid a => a
mempty,
_markerAspectRatio :: PreserveAspectRatio
_markerAspectRatio = PreserveAspectRatio
forall a. WithDefaultSvg a => a
defaultSvg
}
nameOfTree :: Tree -> T.Text
nameOfTree :: Tree -> Text
nameOfTree Tree
v =
case Tree -> TreeBranch
_treeBranch Tree
v of
TreeBranch
NoNode -> Text
""
UseNode Use
_ Maybe Tree
_ -> Text
"use"
GroupNode Group
_ -> Text
"g"
SymbolNode Group
_ -> Text
"symbol"
DefinitionNode Group
_ -> Text
"defs"
FilterNode Filter
_ -> Text
"filter"
PathNode Path
_ -> Text
"path"
CircleNode Circle
_ -> Text
"circle"
PolyLineNode PolyLine
_ -> Text
"polyline"
PolygonNode Polygon
_ -> Text
"polygon"
EllipseNode Ellipse
_ -> Text
"ellipse"
LineNode Line
_ -> Text
"line"
RectangleNode Rectangle
_ -> Text
"rectangle"
TextNode Maybe TextPath
_ Text
_ -> Text
"text"
ImageNode Image
_ -> Text
"image"
LinearGradientNode LinearGradient
_ -> Text
"lineargradient"
RadialGradientNode RadialGradient
_ -> Text
"radialgradient"
MeshGradientNode MeshGradient
_ -> Text
"meshgradient"
PatternNode Pattern
_ -> Text
"pattern"
MarkerNode Marker
_ -> Text
"marker"
MaskNode Mask
_ -> Text
"mask"
ClipPathNode ClipPath
_ -> Text
"clipPath"
SvgNode {} -> Text
"svg"
data Spread
=
SpreadRepeat
|
SpreadPad
|
SpreadReflect
deriving (Spread -> Spread -> Bool
(Spread -> Spread -> Bool)
-> (Spread -> Spread -> Bool) -> Eq Spread
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Spread -> Spread -> Bool
$c/= :: Spread -> Spread -> Bool
== :: Spread -> Spread -> Bool
$c== :: Spread -> Spread -> Bool
Eq, Int -> Spread -> ShowS
[Spread] -> ShowS
Spread -> String
(Int -> Spread -> ShowS)
-> (Spread -> String) -> ([Spread] -> ShowS) -> Show Spread
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Spread] -> ShowS
$cshowList :: [Spread] -> ShowS
show :: Spread -> String
$cshow :: Spread -> String
showsPrec :: Int -> Spread -> ShowS
$cshowsPrec :: Int -> Spread -> ShowS
Show, (forall x. Spread -> Rep Spread x)
-> (forall x. Rep Spread x -> Spread) -> Generic Spread
forall x. Rep Spread x -> Spread
forall x. Spread -> Rep Spread x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Spread x -> Spread
$cfrom :: forall x. Spread -> Rep Spread x
Generic)
data LinearGradient = LinearGradient
{ LinearGradient -> DrawAttributes
_linearGradientDrawAttributes :: DrawAttributes,
LinearGradient -> CoordinateUnits
_linearGradientUnits :: CoordinateUnits,
LinearGradient -> Point
_linearGradientStart :: Point,
LinearGradient -> Point
_linearGradientStop :: Point,
LinearGradient -> Spread
_linearGradientSpread :: Spread,
LinearGradient -> [Transformation]
_linearGradientTransform :: [Transformation],
LinearGradient -> [GradientStop]
_linearGradientStops :: [GradientStop]
}
deriving (LinearGradient -> LinearGradient -> Bool
(LinearGradient -> LinearGradient -> Bool)
-> (LinearGradient -> LinearGradient -> Bool) -> Eq LinearGradient
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinearGradient -> LinearGradient -> Bool
$c/= :: LinearGradient -> LinearGradient -> Bool
== :: LinearGradient -> LinearGradient -> Bool
$c== :: LinearGradient -> LinearGradient -> Bool
Eq, Int -> LinearGradient -> ShowS
[LinearGradient] -> ShowS
LinearGradient -> String
(Int -> LinearGradient -> ShowS)
-> (LinearGradient -> String)
-> ([LinearGradient] -> ShowS)
-> Show LinearGradient
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinearGradient] -> ShowS
$cshowList :: [LinearGradient] -> ShowS
show :: LinearGradient -> String
$cshow :: LinearGradient -> String
showsPrec :: Int -> LinearGradient -> ShowS
$cshowsPrec :: Int -> LinearGradient -> ShowS
Show, (forall x. LinearGradient -> Rep LinearGradient x)
-> (forall x. Rep LinearGradient x -> LinearGradient)
-> Generic LinearGradient
forall x. Rep LinearGradient x -> LinearGradient
forall x. LinearGradient -> Rep LinearGradient x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LinearGradient x -> LinearGradient
$cfrom :: forall x. LinearGradient -> Rep LinearGradient x
Generic)
instance WithDefaultSvg LinearGradient where
defaultSvg :: LinearGradient
defaultSvg =
LinearGradient :: DrawAttributes
-> CoordinateUnits
-> Point
-> Point
-> Spread
-> [Transformation]
-> [GradientStop]
-> LinearGradient
LinearGradient
{ _linearGradientDrawAttributes :: DrawAttributes
_linearGradientDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_linearGradientUnits :: CoordinateUnits
_linearGradientUnits = CoordinateUnits
CoordBoundingBox,
_linearGradientStart :: Point
_linearGradientStart = (Coord -> Number
Percent Coord
0, Coord -> Number
Percent Coord
0),
_linearGradientStop :: Point
_linearGradientStop = (Coord -> Number
Percent Coord
1, Coord -> Number
Percent Coord
0),
_linearGradientSpread :: Spread
_linearGradientSpread = Spread
SpreadPad,
_linearGradientTransform :: [Transformation]
_linearGradientTransform = [],
_linearGradientStops :: [GradientStop]
_linearGradientStops = []
}
data RadialGradient = RadialGradient
{ RadialGradient -> DrawAttributes
_radialGradientDrawAttributes :: DrawAttributes,
RadialGradient -> CoordinateUnits
_radialGradientUnits :: CoordinateUnits,
RadialGradient -> Point
_radialGradientCenter :: Point,
RadialGradient -> Number
_radialGradientRadius :: Number,
RadialGradient -> Maybe Number
_radialGradientFocusX :: Maybe Number,
RadialGradient -> Maybe Number
_radialGradientFocusY :: Maybe Number,
RadialGradient -> Spread
_radialGradientSpread :: Spread,
RadialGradient -> [Transformation]
_radialGradientTransform :: [Transformation],
RadialGradient -> [GradientStop]
_radialGradientStops :: [GradientStop]
}
deriving (RadialGradient -> RadialGradient -> Bool
(RadialGradient -> RadialGradient -> Bool)
-> (RadialGradient -> RadialGradient -> Bool) -> Eq RadialGradient
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RadialGradient -> RadialGradient -> Bool
$c/= :: RadialGradient -> RadialGradient -> Bool
== :: RadialGradient -> RadialGradient -> Bool
$c== :: RadialGradient -> RadialGradient -> Bool
Eq, Int -> RadialGradient -> ShowS
[RadialGradient] -> ShowS
RadialGradient -> String
(Int -> RadialGradient -> ShowS)
-> (RadialGradient -> String)
-> ([RadialGradient] -> ShowS)
-> Show RadialGradient
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RadialGradient] -> ShowS
$cshowList :: [RadialGradient] -> ShowS
show :: RadialGradient -> String
$cshow :: RadialGradient -> String
showsPrec :: Int -> RadialGradient -> ShowS
$cshowsPrec :: Int -> RadialGradient -> ShowS
Show, (forall x. RadialGradient -> Rep RadialGradient x)
-> (forall x. Rep RadialGradient x -> RadialGradient)
-> Generic RadialGradient
forall x. Rep RadialGradient x -> RadialGradient
forall x. RadialGradient -> Rep RadialGradient x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RadialGradient x -> RadialGradient
$cfrom :: forall x. RadialGradient -> Rep RadialGradient x
Generic)
instance WithDefaultSvg RadialGradient where
defaultSvg :: RadialGradient
defaultSvg =
RadialGradient :: DrawAttributes
-> CoordinateUnits
-> Point
-> Number
-> Maybe Number
-> Maybe Number
-> Spread
-> [Transformation]
-> [GradientStop]
-> RadialGradient
RadialGradient
{ _radialGradientDrawAttributes :: DrawAttributes
_radialGradientDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_radialGradientUnits :: CoordinateUnits
_radialGradientUnits = CoordinateUnits
CoordBoundingBox,
_radialGradientCenter :: Point
_radialGradientCenter = (Coord -> Number
Percent Coord
0.5, Coord -> Number
Percent Coord
0.5),
_radialGradientRadius :: Number
_radialGradientRadius = Coord -> Number
Percent Coord
0.5,
_radialGradientFocusX :: Maybe Number
_radialGradientFocusX = Maybe Number
forall a. Maybe a
Nothing,
_radialGradientFocusY :: Maybe Number
_radialGradientFocusY = Maybe Number
forall a. Maybe a
Nothing,
_radialGradientSpread :: Spread
_radialGradientSpread = Spread
SpreadPad,
_radialGradientTransform :: [Transformation]
_radialGradientTransform = [],
_radialGradientStops :: [GradientStop]
_radialGradientStops = []
}
data Mask = Mask
{ Mask -> DrawAttributes
_maskDrawAttributes :: DrawAttributes,
Mask -> CoordinateUnits
_maskContentUnits :: CoordinateUnits,
Mask -> CoordinateUnits
_maskUnits :: CoordinateUnits,
Mask -> Point
_maskPosition :: Point,
Mask -> Number
_maskWidth :: Number,
Mask -> Number
_maskHeight :: Number,
Mask -> [Tree]
_maskContent :: [Tree]
}
deriving (Mask -> Mask -> Bool
(Mask -> Mask -> Bool) -> (Mask -> Mask -> Bool) -> Eq Mask
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mask -> Mask -> Bool
$c/= :: Mask -> Mask -> Bool
== :: Mask -> Mask -> Bool
$c== :: Mask -> Mask -> Bool
Eq, Int -> Mask -> ShowS
[Mask] -> ShowS
Mask -> String
(Int -> Mask -> ShowS)
-> (Mask -> String) -> ([Mask] -> ShowS) -> Show Mask
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mask] -> ShowS
$cshowList :: [Mask] -> ShowS
show :: Mask -> String
$cshow :: Mask -> String
showsPrec :: Int -> Mask -> ShowS
$cshowsPrec :: Int -> Mask -> ShowS
Show, (forall x. Mask -> Rep Mask x)
-> (forall x. Rep Mask x -> Mask) -> Generic Mask
forall x. Rep Mask x -> Mask
forall x. Mask -> Rep Mask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Mask x -> Mask
$cfrom :: forall x. Mask -> Rep Mask x
Generic)
instance WithDefaultSvg Mask where
defaultSvg :: Mask
defaultSvg =
Mask :: DrawAttributes
-> CoordinateUnits
-> CoordinateUnits
-> Point
-> Number
-> Number
-> [Tree]
-> Mask
Mask
{ _maskDrawAttributes :: DrawAttributes
_maskDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_maskContentUnits :: CoordinateUnits
_maskContentUnits = CoordinateUnits
CoordUserSpace,
_maskUnits :: CoordinateUnits
_maskUnits = CoordinateUnits
CoordBoundingBox,
_maskPosition :: Point
_maskPosition = (Coord -> Number
Percent (-Coord
0.1), Coord -> Number
Percent (-Coord
0.1)),
_maskWidth :: Number
_maskWidth = Coord -> Number
Percent Coord
1.2,
_maskHeight :: Number
_maskHeight = Coord -> Number
Percent Coord
1.2,
_maskContent :: [Tree]
_maskContent = []
}
data ClipPath = ClipPath
{ ClipPath -> DrawAttributes
_clipPathDrawAttributes :: DrawAttributes,
ClipPath -> CoordinateUnits
_clipPathUnits :: CoordinateUnits,
ClipPath -> [Tree]
_clipPathContent :: [Tree]
}
deriving (ClipPath -> ClipPath -> Bool
(ClipPath -> ClipPath -> Bool)
-> (ClipPath -> ClipPath -> Bool) -> Eq ClipPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClipPath -> ClipPath -> Bool
$c/= :: ClipPath -> ClipPath -> Bool
== :: ClipPath -> ClipPath -> Bool
$c== :: ClipPath -> ClipPath -> Bool
Eq, Int -> ClipPath -> ShowS
[ClipPath] -> ShowS
ClipPath -> String
(Int -> ClipPath -> ShowS)
-> (ClipPath -> String) -> ([ClipPath] -> ShowS) -> Show ClipPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClipPath] -> ShowS
$cshowList :: [ClipPath] -> ShowS
show :: ClipPath -> String
$cshow :: ClipPath -> String
showsPrec :: Int -> ClipPath -> ShowS
$cshowsPrec :: Int -> ClipPath -> ShowS
Show, (forall x. ClipPath -> Rep ClipPath x)
-> (forall x. Rep ClipPath x -> ClipPath) -> Generic ClipPath
forall x. Rep ClipPath x -> ClipPath
forall x. ClipPath -> Rep ClipPath x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClipPath x -> ClipPath
$cfrom :: forall x. ClipPath -> Rep ClipPath x
Generic)
instance WithDefaultSvg ClipPath where
defaultSvg :: ClipPath
defaultSvg =
ClipPath :: DrawAttributes -> CoordinateUnits -> [Tree] -> ClipPath
ClipPath
{ _clipPathDrawAttributes :: DrawAttributes
_clipPathDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_clipPathUnits :: CoordinateUnits
_clipPathUnits = CoordinateUnits
CoordUserSpace,
_clipPathContent :: [Tree]
_clipPathContent = [Tree]
forall a. Monoid a => a
mempty
}
data Pattern = Pattern
{ Pattern -> DrawAttributes
_patternDrawAttributes :: DrawAttributes,
Pattern -> Maybe (Coord, Coord, Coord, Coord)
_patternViewBox :: !(Maybe (Double, Double, Double, Double)),
Pattern -> Number
_patternWidth :: !Number,
Pattern -> Number
_patternHeight :: !Number,
Pattern -> Point
_patternPos :: !Point,
Pattern -> String
_patternHref :: !String,
Pattern -> [Tree]
_patternElements :: ![Tree],
Pattern -> CoordinateUnits
_patternUnit :: !CoordinateUnits,
Pattern -> PreserveAspectRatio
_patternAspectRatio :: !PreserveAspectRatio,
Pattern -> Maybe [Transformation]
_patternTransform :: !(Maybe [Transformation])
}
deriving (Pattern -> Pattern -> Bool
(Pattern -> Pattern -> Bool)
-> (Pattern -> Pattern -> Bool) -> Eq Pattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pattern -> Pattern -> Bool
$c/= :: Pattern -> Pattern -> Bool
== :: Pattern -> Pattern -> Bool
$c== :: Pattern -> Pattern -> Bool
Eq, Int -> Pattern -> ShowS
[Pattern] -> ShowS
Pattern -> String
(Int -> Pattern -> ShowS)
-> (Pattern -> String) -> ([Pattern] -> ShowS) -> Show Pattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pattern] -> ShowS
$cshowList :: [Pattern] -> ShowS
show :: Pattern -> String
$cshow :: Pattern -> String
showsPrec :: Int -> Pattern -> ShowS
$cshowsPrec :: Int -> Pattern -> ShowS
Show, (forall x. Pattern -> Rep Pattern x)
-> (forall x. Rep Pattern x -> Pattern) -> Generic Pattern
forall x. Rep Pattern x -> Pattern
forall x. Pattern -> Rep Pattern x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Pattern x -> Pattern
$cfrom :: forall x. Pattern -> Rep Pattern x
Generic)
instance WithDefaultSvg Pattern where
defaultSvg :: Pattern
defaultSvg =
Pattern :: DrawAttributes
-> Maybe (Coord, Coord, Coord, Coord)
-> Number
-> Number
-> Point
-> String
-> [Tree]
-> CoordinateUnits
-> PreserveAspectRatio
-> Maybe [Transformation]
-> Pattern
Pattern
{ _patternDrawAttributes :: DrawAttributes
_patternDrawAttributes = DrawAttributes
forall a. Monoid a => a
mempty,
_patternViewBox :: Maybe (Coord, Coord, Coord, Coord)
_patternViewBox = Maybe (Coord, Coord, Coord, Coord)
forall a. Maybe a
Nothing,
_patternWidth :: Number
_patternWidth = Coord -> Number
Num Coord
0,
_patternHeight :: Number
_patternHeight = Coord -> Number
Num Coord
0,
_patternPos :: Point
_patternPos = (Coord -> Number
Num Coord
0, Coord -> Number
Num Coord
0),
_patternElements :: [Tree]
_patternElements = [],
_patternUnit :: CoordinateUnits
_patternUnit = CoordinateUnits
CoordBoundingBox,
_patternAspectRatio :: PreserveAspectRatio
_patternAspectRatio = PreserveAspectRatio
forall a. WithDefaultSvg a => a
defaultSvg,
_patternHref :: String
_patternHref = String
"",
_patternTransform :: Maybe [Transformation]
_patternTransform = Maybe [Transformation]
forall a. Monoid a => a
mempty
}
data Element
= ElementLinearGradient LinearGradient
| ElementRadialGradient RadialGradient
| ElementMeshGradient MeshGradient
| ElementGeometry Tree
| ElementPattern Pattern
| ElementMarker Marker
| ElementMask Mask
| ElementClipPath ClipPath
deriving (Element -> Element -> Bool
(Element -> Element -> Bool)
-> (Element -> Element -> Bool) -> Eq Element
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Element -> Element -> Bool
$c/= :: Element -> Element -> Bool
== :: Element -> Element -> Bool
$c== :: Element -> Element -> Bool
Eq, Int -> Element -> ShowS
[Element] -> ShowS
Element -> String
(Int -> Element -> ShowS)
-> (Element -> String) -> ([Element] -> ShowS) -> Show Element
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Element] -> ShowS
$cshowList :: [Element] -> ShowS
show :: Element -> String
$cshow :: Element -> String
showsPrec :: Int -> Element -> ShowS
$cshowsPrec :: Int -> Element -> ShowS
Show, (forall x. Element -> Rep Element x)
-> (forall x. Rep Element x -> Element) -> Generic Element
forall x. Rep Element x -> Element
forall x. Element -> Rep Element x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Element x -> Element
$cfrom :: forall x. Element -> Rep Element x
Generic)
data Document = Document
{ Document -> Maybe (Coord, Coord, Coord, Coord)
_documentViewBox :: Maybe (Double, Double, Double, Double),
Document -> Maybe Number
_documentWidth :: Maybe Number,
Document -> Maybe Number
_documentHeight :: Maybe Number,
Document -> [Tree]
_documentElements :: [Tree],
Document -> String
_documentDescription :: String,
Document -> String
_documentLocation :: FilePath,
Document -> PreserveAspectRatio
_documentAspectRatio :: PreserveAspectRatio
}
deriving (Int -> Document -> ShowS
[Document] -> ShowS
Document -> String
(Int -> Document -> ShowS)
-> (Document -> String) -> ([Document] -> ShowS) -> Show Document
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Document] -> ShowS
$cshowList :: [Document] -> ShowS
show :: Document -> String
$cshow :: Document -> String
showsPrec :: Int -> Document -> ShowS
$cshowsPrec :: Int -> Document -> ShowS
Show, Document -> Document -> Bool
(Document -> Document -> Bool)
-> (Document -> Document -> Bool) -> Eq Document
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Document -> Document -> Bool
$c/= :: Document -> Document -> Bool
== :: Document -> Document -> Bool
$c== :: Document -> Document -> Bool
Eq, (forall x. Document -> Rep Document x)
-> (forall x. Rep Document x -> Document) -> Generic Document
forall x. Rep Document x -> Document
forall x. Document -> Rep Document x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Document x -> Document
$cfrom :: forall x. Document -> Rep Document x
Generic)
documentSize :: Dpi -> Document -> (Int, Int)
documentSize :: Int -> Document -> (Int, Int)
documentSize
Int
_
Document
{ _documentViewBox :: Document -> Maybe (Coord, Coord, Coord, Coord)
_documentViewBox = Just (Coord
x1, Coord
y1, Coord
x2, Coord
y2),
_documentWidth :: Document -> Maybe Number
_documentWidth = Just (Percent Coord
pw),
_documentHeight :: Document -> Maybe Number
_documentHeight = Just (Percent Coord
ph)
} =
(Coord -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Coord -> Int) -> Coord -> Int
forall a b. (a -> b) -> a -> b
$ Coord
dx Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
* Coord
pw, Coord -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Coord -> Int) -> Coord -> Int
forall a b. (a -> b) -> a -> b
$ Coord
dy Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
* Coord
ph)
where
dx :: Coord
dx = Coord -> Coord
forall a. Num a => a -> a
abs (Coord -> Coord) -> Coord -> Coord
forall a b. (a -> b) -> a -> b
$ Coord
x2 Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
- Coord
x1
dy :: Coord
dy = Coord -> Coord
forall a. Num a => a -> a
abs (Coord -> Coord) -> Coord -> Coord
forall a b. (a -> b) -> a -> b
$ Coord
y2 Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
- Coord
y1
documentSize
Int
_
Document
{ _documentWidth :: Document -> Maybe Number
_documentWidth = Just (Num Coord
w),
_documentHeight :: Document -> Maybe Number
_documentHeight = Just (Num Coord
h)
} = (Coord -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor Coord
w, Coord -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor Coord
h)
documentSize
Int
dpi
doc :: Document
doc@Document
{ _documentWidth :: Document -> Maybe Number
_documentWidth = Just Number
w,
_documentHeight :: Document -> Maybe Number
_documentHeight = Just Number
h
} =
Int -> Document -> (Int, Int)
documentSize Int
dpi (Document -> (Int, Int)) -> Document -> (Int, Int)
forall a b. (a -> b) -> a -> b
$
Document
doc
{ _documentWidth :: Maybe Number
_documentWidth = Number -> Maybe Number
forall a. a -> Maybe a
Just (Number -> Maybe Number) -> Number -> Maybe Number
forall a b. (a -> b) -> a -> b
$ Int -> Number -> Number
toUserUnit Int
dpi Number
w,
_documentHeight :: Maybe Number
_documentHeight = Number -> Maybe Number
forall a. a -> Maybe a
Just (Number -> Maybe Number) -> Number -> Maybe Number
forall a b. (a -> b) -> a -> b
$ Int -> Number -> Number
toUserUnit Int
dpi Number
h
}
documentSize Int
_ Document {_documentViewBox :: Document -> Maybe (Coord, Coord, Coord, Coord)
_documentViewBox = Just (Coord
x1, Coord
y1, Coord
x2, Coord
y2)} =
(Coord -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Coord -> Int) -> (Coord -> Coord) -> Coord -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coord -> Coord
forall a. Num a => a -> a
abs (Coord -> Int) -> Coord -> Int
forall a b. (a -> b) -> a -> b
$ Coord
x2 Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
- Coord
x1, Coord -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Coord -> Int) -> (Coord -> Coord) -> Coord -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coord -> Coord
forall a. Num a => a -> a
abs (Coord -> Int) -> Coord -> Int
forall a b. (a -> b) -> a -> b
$ Coord
y2 Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
- Coord
y1)
documentSize Int
_ Document
_ = (Int
1, Int
1)
mayMerge :: Monoid a => Maybe a -> Maybe a -> Maybe a
mayMerge :: Maybe a -> Maybe a -> Maybe a
mayMerge (Just a
a) (Just a
b) = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ a -> a -> a
forall a. Monoid a => a -> a -> a
mappend a
a a
b
mayMerge Maybe a
_ b :: Maybe a
b@(Just a
_) = Maybe a
b
mayMerge Maybe a
a Maybe a
Nothing = Maybe a
a
instance Semigroup DrawAttributes where
<> :: DrawAttributes -> DrawAttributes -> DrawAttributes
(<>) DrawAttributes
a DrawAttributes
b =
DrawAttributes :: Maybe Number
-> Maybe Texture
-> Maybe Float
-> Maybe Cap
-> Maybe LineJoin
-> Maybe Coord
-> Maybe Texture
-> Maybe Float
-> Maybe Float
-> Maybe [Transformation]
-> Maybe FillRule
-> Maybe ElementRef
-> Maybe ElementRef
-> Maybe FillRule
-> [Text]
-> Maybe String
-> Maybe Number
-> Maybe [Number]
-> Maybe Number
-> Maybe [String]
-> Maybe FontStyle
-> Maybe TextAnchor
-> Maybe ElementRef
-> Maybe ElementRef
-> Maybe ElementRef
-> Maybe ElementRef
-> DrawAttributes
DrawAttributes
{ _strokeWidth :: Maybe Number
_strokeWidth = (DrawAttributes -> Maybe Number) -> Maybe Number
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe Number
_strokeWidth,
_strokeColor :: Maybe Texture
_strokeColor = (DrawAttributes -> Maybe Texture) -> Maybe Texture
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe Texture
_strokeColor,
_strokeLineCap :: Maybe Cap
_strokeLineCap = (DrawAttributes -> Maybe Cap) -> Maybe Cap
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe Cap
_strokeLineCap,
_strokeOpacity :: Maybe Float
_strokeOpacity = (Maybe Float -> Maybe Float -> Maybe Float
forall a. Num a => Maybe a -> Maybe a -> Maybe a
opacityMappend (Maybe Float -> Maybe Float -> Maybe Float)
-> (DrawAttributes -> Maybe Float)
-> DrawAttributes
-> DrawAttributes
-> Maybe Float
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` DrawAttributes -> Maybe Float
_strokeOpacity) DrawAttributes
a DrawAttributes
b,
_strokeLineJoin :: Maybe LineJoin
_strokeLineJoin = (DrawAttributes -> Maybe LineJoin) -> Maybe LineJoin
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe LineJoin
_strokeLineJoin,
_strokeMiterLimit :: Maybe Coord
_strokeMiterLimit = (DrawAttributes -> Maybe Coord) -> Maybe Coord
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe Coord
_strokeMiterLimit,
_fillColor :: Maybe Texture
_fillColor = (DrawAttributes -> Maybe Texture) -> Maybe Texture
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe Texture
_fillColor,
_fillOpacity :: Maybe Float
_fillOpacity = (Maybe Float -> Maybe Float -> Maybe Float
forall a. Num a => Maybe a -> Maybe a -> Maybe a
opacityMappend (Maybe Float -> Maybe Float -> Maybe Float)
-> (DrawAttributes -> Maybe Float)
-> DrawAttributes
-> DrawAttributes
-> Maybe Float
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` DrawAttributes -> Maybe Float
_fillOpacity) DrawAttributes
a DrawAttributes
b,
_fontSize :: Maybe Number
_fontSize = (DrawAttributes -> Maybe Number) -> Maybe Number
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe Number
_fontSize,
_transform :: Maybe [Transformation]
_transform = (Maybe [Transformation]
-> Maybe [Transformation] -> Maybe [Transformation]
forall a. Monoid a => Maybe a -> Maybe a -> Maybe a
mayMerge (Maybe [Transformation]
-> Maybe [Transformation] -> Maybe [Transformation])
-> (DrawAttributes -> Maybe [Transformation])
-> DrawAttributes
-> DrawAttributes
-> Maybe [Transformation]
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` DrawAttributes -> Maybe [Transformation]
_transform) DrawAttributes
a DrawAttributes
b,
_fillRule :: Maybe FillRule
_fillRule = (DrawAttributes -> Maybe FillRule) -> Maybe FillRule
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe FillRule
_fillRule,
_attrClass :: [Text]
_attrClass = DrawAttributes -> [Text]
_attrClass DrawAttributes
b,
_attrId :: Maybe String
_attrId = DrawAttributes -> Maybe String
_attrId DrawAttributes
b,
_groupOpacity :: Maybe Float
_groupOpacity = DrawAttributes -> Maybe Float
_groupOpacity DrawAttributes
b,
_strokeOffset :: Maybe Number
_strokeOffset = (DrawAttributes -> Maybe Number) -> Maybe Number
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe Number
_strokeOffset,
_strokeDashArray :: Maybe [Number]
_strokeDashArray = (DrawAttributes -> Maybe [Number]) -> Maybe [Number]
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe [Number]
_strokeDashArray,
_fontFamily :: Maybe [String]
_fontFamily = (DrawAttributes -> Maybe [String]) -> Maybe [String]
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe [String]
_fontFamily,
_fontStyle :: Maybe FontStyle
_fontStyle = (DrawAttributes -> Maybe FontStyle) -> Maybe FontStyle
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe FontStyle
_fontStyle,
_textAnchor :: Maybe TextAnchor
_textAnchor = (DrawAttributes -> Maybe TextAnchor) -> Maybe TextAnchor
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe TextAnchor
_textAnchor,
_maskRef :: Maybe ElementRef
_maskRef = (DrawAttributes -> Maybe ElementRef) -> Maybe ElementRef
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe ElementRef
_maskRef,
_clipPathRef :: Maybe ElementRef
_clipPathRef = (DrawAttributes -> Maybe ElementRef) -> Maybe ElementRef
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe ElementRef
_clipPathRef,
_clipRule :: Maybe FillRule
_clipRule = (DrawAttributes -> Maybe FillRule) -> Maybe FillRule
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe FillRule
_clipRule,
_markerStart :: Maybe ElementRef
_markerStart = (DrawAttributes -> Maybe ElementRef) -> Maybe ElementRef
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe ElementRef
_markerStart,
_markerMid :: Maybe ElementRef
_markerMid = (DrawAttributes -> Maybe ElementRef) -> Maybe ElementRef
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe ElementRef
_markerMid,
_markerEnd :: Maybe ElementRef
_markerEnd = (DrawAttributes -> Maybe ElementRef) -> Maybe ElementRef
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe ElementRef
_markerEnd,
_filterRef :: Maybe ElementRef
_filterRef = (DrawAttributes -> Maybe ElementRef) -> Maybe ElementRef
forall (f :: * -> *) a.
Alternative f =>
(DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> Maybe ElementRef
_filterRef
}
where
opacityMappend :: Maybe a -> Maybe a -> Maybe a
opacityMappend Maybe a
Nothing Maybe a
Nothing = Maybe a
forall a. Maybe a
Nothing
opacityMappend (Just a
v) Maybe a
Nothing = a -> Maybe a
forall a. a -> Maybe a
Just a
v
opacityMappend Maybe a
Nothing (Just a
v) = a -> Maybe a
forall a. a -> Maybe a
Just a
v
opacityMappend (Just a
v) (Just a
v2) = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ a
v a -> a -> a
forall a. Num a => a -> a -> a
* a
v2
chooseLast :: (DrawAttributes -> f a) -> f a
chooseLast DrawAttributes -> f a
f = DrawAttributes -> f a
f DrawAttributes
b f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> DrawAttributes -> f a
f DrawAttributes
a
instance Monoid DrawAttributes where
mappend :: DrawAttributes -> DrawAttributes -> DrawAttributes
mappend = DrawAttributes -> DrawAttributes -> DrawAttributes
forall a. Semigroup a => a -> a -> a
(<>)
mempty :: DrawAttributes
mempty =
DrawAttributes :: Maybe Number
-> Maybe Texture
-> Maybe Float
-> Maybe Cap
-> Maybe LineJoin
-> Maybe Coord
-> Maybe Texture
-> Maybe Float
-> Maybe Float
-> Maybe [Transformation]
-> Maybe FillRule
-> Maybe ElementRef
-> Maybe ElementRef
-> Maybe FillRule
-> [Text]
-> Maybe String
-> Maybe Number
-> Maybe [Number]
-> Maybe Number
-> Maybe [String]
-> Maybe FontStyle
-> Maybe TextAnchor
-> Maybe ElementRef
-> Maybe ElementRef
-> Maybe ElementRef
-> Maybe ElementRef
-> DrawAttributes
DrawAttributes
{ _strokeWidth :: Maybe Number
_strokeWidth = Maybe Number
forall a. Maybe a
Nothing,
_strokeColor :: Maybe Texture
_strokeColor = Maybe Texture
forall a. Maybe a
Nothing,
_strokeOpacity :: Maybe Float
_strokeOpacity = Maybe Float
forall a. Maybe a
Nothing,
_strokeLineCap :: Maybe Cap
_strokeLineCap = Maybe Cap
forall a. Maybe a
Nothing,
_strokeLineJoin :: Maybe LineJoin
_strokeLineJoin = Maybe LineJoin
forall a. Maybe a
Nothing,
_strokeMiterLimit :: Maybe Coord
_strokeMiterLimit = Maybe Coord
forall a. Maybe a
Nothing,
_fillColor :: Maybe Texture
_fillColor = Maybe Texture
forall a. Maybe a
Nothing,
_groupOpacity :: Maybe Float
_groupOpacity = Maybe Float
forall a. Maybe a
Nothing,
_fillOpacity :: Maybe Float
_fillOpacity = Maybe Float
forall a. Maybe a
Nothing,
_fontSize :: Maybe Number
_fontSize = Maybe Number
forall a. Maybe a
Nothing,
_fontFamily :: Maybe [String]
_fontFamily = Maybe [String]
forall a. Maybe a
Nothing,
_fontStyle :: Maybe FontStyle
_fontStyle = Maybe FontStyle
forall a. Maybe a
Nothing,
_transform :: Maybe [Transformation]
_transform = Maybe [Transformation]
forall a. Maybe a
Nothing,
_fillRule :: Maybe FillRule
_fillRule = Maybe FillRule
forall a. Maybe a
Nothing,
_attrClass :: [Text]
_attrClass = [Text]
forall a. Monoid a => a
mempty,
_attrId :: Maybe String
_attrId = Maybe String
forall a. Maybe a
Nothing,
_strokeOffset :: Maybe Number
_strokeOffset = Maybe Number
forall a. Maybe a
Nothing,
_strokeDashArray :: Maybe [Number]
_strokeDashArray = Maybe [Number]
forall a. Maybe a
Nothing,
_textAnchor :: Maybe TextAnchor
_textAnchor = Maybe TextAnchor
forall a. Maybe a
Nothing,
_maskRef :: Maybe ElementRef
_maskRef = Maybe ElementRef
forall a. Maybe a
Nothing,
_clipPathRef :: Maybe ElementRef
_clipPathRef = Maybe ElementRef
forall a. Maybe a
Nothing,
_clipRule :: Maybe FillRule
_clipRule = Maybe FillRule
forall a. Maybe a
Nothing,
_markerStart :: Maybe ElementRef
_markerStart = Maybe ElementRef
forall a. Maybe a
Nothing,
_markerMid :: Maybe ElementRef
_markerMid = Maybe ElementRef
forall a. Maybe a
Nothing,
_markerEnd :: Maybe ElementRef
_markerEnd = Maybe ElementRef
forall a. Maybe a
Nothing,
_filterRef :: Maybe ElementRef
_filterRef = Maybe ElementRef
forall a. Maybe a
Nothing
}
instance WithDefaultSvg DrawAttributes where
defaultSvg :: DrawAttributes
defaultSvg = DrawAttributes
forall a. Monoid a => a
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