reanimate-svg-0.13.0.0: SVG file loader and serializer

Safe HaskellNone
LanguageHaskell2010

Graphics.SvgTree.Types

Contents

Description

This module define all the types used in the definition of a svg scene.

Most of the types are lensified.

Synopsis

Basic building types

type Coord = Double Source #

Basic coordinate type.

data Origin Source #

Tell if a path command is absolute (in the current user coordiante) or relative to the previous poitn.

Constructors

OriginAbsolute

Next point in absolute coordinate

OriginRelative

Next point relative to the previous

Instances
Eq Origin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Methods

(==) :: Origin -> Origin -> Bool #

(/=) :: Origin -> Origin -> Bool #

Show Origin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic Origin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep Origin :: Type -> Type #

Methods

from :: Origin -> Rep Origin x #

to :: Rep Origin x -> Origin #

Hashable Origin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Origin -> Int #

hash :: Origin -> Int #

type Rep Origin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep Origin = D1 (MetaData "Origin" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "OriginAbsolute" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OriginRelative" PrefixI False) (U1 :: Type -> Type))

type Point = (Number, Number) Source #

Possibly context dependant point.

type RPoint = V2 Coord Source #

Real Point, fully determined and not dependant of the rendering context.

data PathCommand Source #

Path command definition.

Constructors

MoveTo !Origin ![RPoint]

M or m command

LineTo !Origin ![RPoint]

Line to, L or l Svg path command.

HorizontalTo !Origin ![Coord]

Equivalent to the H or h svg path command.

VerticalTo !Origin ![Coord]

Equivalent to the V or v svg path command.

CurveTo !Origin ![(RPoint, RPoint, RPoint)]

Cubic bezier, C or c command

SmoothCurveTo !Origin ![(RPoint, RPoint)]

Smooth cubic bezier, equivalent to S or s command

QuadraticBezier !Origin ![(RPoint, RPoint)]

Quadratic bezier, Q or q command

SmoothQuadraticBezierCurveTo !Origin ![RPoint]

Quadratic bezier, T or t command

EllipticalArc !Origin ![(Coord, Coord, Coord, Bool, Bool, RPoint)]

Eliptical arc, A or a command.

EndPath

Close the path, Z or z svg path command.

Instances
Eq PathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show PathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic PathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep PathCommand :: Type -> Type #

Hashable PathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep PathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep PathCommand = D1 (MetaData "PathCommand" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (((C1 (MetaCons "MoveTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [RPoint])) :+: C1 (MetaCons "LineTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [RPoint]))) :+: (C1 (MetaCons "HorizontalTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Coord])) :+: (C1 (MetaCons "VerticalTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Coord])) :+: C1 (MetaCons "CurveTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(RPoint, RPoint, RPoint)]))))) :+: ((C1 (MetaCons "SmoothCurveTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(RPoint, RPoint)])) :+: C1 (MetaCons "QuadraticBezier" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(RPoint, RPoint)]))) :+: (C1 (MetaCons "SmoothQuadraticBezierCurveTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [RPoint])) :+: (C1 (MetaCons "EllipticalArc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Origin) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(Coord, Coord, Coord, Bool, Bool, RPoint)])) :+: C1 (MetaCons "EndPath" PrefixI False) (U1 :: Type -> Type)))))

data Transformation Source #

Describe the content of the transformation attribute. see _transform and transform.

Constructors

TransformMatrix !Coord !Coord !Coord !Coord !Coord !Coord

Directly encode the translation matrix.

Translate !Double !Double

Translation along a vector

Scale !Double !(Maybe Double)

Scaling on both axis or on X axis and Y axis.

Rotate !Double !(Maybe (Double, Double))

Rotation around `(0, 0)` or around an optional point.

SkewX !Double

Skew transformation along the X axis.

SkewY !Double

Skew transformation along the Y axis.

TransformUnknown

Unkown transformation, like identity.

Instances
Eq Transformation Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show Transformation Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Transformation Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Transformation :: Type -> Type #

Hashable Transformation Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep Transformation Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Transformation = D1 (MetaData "Transformation" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((C1 (MetaCons "TransformMatrix" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Coord) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Coord) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Coord))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Coord) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Coord) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Coord)))) :+: (C1 (MetaCons "Translate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :+: C1 (MetaCons "Scale" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))))) :+: ((C1 (MetaCons "Rotate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Double, Double)))) :+: C1 (MetaCons "SkewX" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: (C1 (MetaCons "SkewY" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :+: C1 (MetaCons "TransformUnknown" PrefixI False) (U1 :: Type -> Type))))

data ElementRef Source #

Correspond to the possible values of the the attributes which are either none or `url(#elem)`

Constructors

RefNone

Value for none

Ref String

Equivalent to `url()` attribute.

Instances
Eq ElementRef Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show ElementRef Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ElementRef Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ElementRef :: Type -> Type #

Hashable ElementRef Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep ElementRef Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ElementRef = D1 (MetaData "ElementRef" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "RefNone" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ref" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data CoordinateUnits Source #

Define the possible values of various *units attributes used in the definition of the gradients and masks.

Constructors

CoordUserSpace

userSpaceOnUse value

CoordBoundingBox

objectBoundingBox value

Instances
Eq CoordinateUnits Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Show CoordinateUnits Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic CoordinateUnits Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep CoordinateUnits :: Type -> Type #

Hashable CoordinateUnits Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep CoordinateUnits Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep CoordinateUnits = D1 (MetaData "CoordinateUnits" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "CoordUserSpace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CoordBoundingBox" PrefixI False) (U1 :: Type -> Type))

Building helpers

serializeNumber :: Number -> String Source #

Encode the number to string which can be used in a CSS or a svg attributes.

serializeTransformation :: Transformation -> String Source #

Convert the Transformation to a string which can be directly used in a svg attributes.

serializeTransformations :: [Transformation] -> String Source #

Transform a list of transformations to a string for svg transform attributes.

Drawing control types

data Cap Source #

Describe how the line should be terminated when stroking them. Describe the values of the `stroke-linecap` attribute. See _strokeLineCap

Constructors

CapRound

End with a round (round value)

CapButt

Define straight just at the end (butt value)

CapSquare

Straight further of the ends (square value)

Instances
Eq Cap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Methods

(==) :: Cap -> Cap -> Bool #

(/=) :: Cap -> Cap -> Bool #

Show Cap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Methods

showsPrec :: Int -> Cap -> ShowS #

show :: Cap -> String #

showList :: [Cap] -> ShowS #

Generic Cap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep Cap :: Type -> Type #

Methods

from :: Cap -> Rep Cap x #

to :: Rep Cap x -> Cap #

Hashable Cap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Cap -> Int #

hash :: Cap -> Int #

type Rep Cap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep Cap = D1 (MetaData "Cap" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "CapRound" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CapButt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CapSquare" PrefixI False) (U1 :: Type -> Type)))

data LineJoin Source #

Define the possible values of the `stroke-linejoin` attribute. see _strokeLineJoin

Constructors

JoinMiter

miter value

JoinBevel

bevel value

JoinRound

round value

Instances
Eq LineJoin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Show LineJoin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic LineJoin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep LineJoin :: Type -> Type #

Methods

from :: LineJoin -> Rep LineJoin x #

to :: Rep LineJoin x -> LineJoin #

Hashable LineJoin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> LineJoin -> Int #

hash :: LineJoin -> Int #

type Rep LineJoin Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep LineJoin = D1 (MetaData "LineJoin" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "JoinMiter" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "JoinBevel" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JoinRound" PrefixI False) (U1 :: Type -> Type)))

data Tree Source #

Main type for the scene description, reorient to specific type describing each tag.

Instances
Eq Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Tree -> Tree -> Bool #

(/=) :: Tree -> Tree -> Bool #

Show Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Tree -> ShowS #

show :: Tree -> String #

showList :: [Tree] -> ShowS #

Generic Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Tree :: Type -> Type #

Methods

from :: Tree -> Rep Tree x #

to :: Rep Tree x -> Tree #

Hashable Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Tree -> Int #

hash :: Tree -> Int #

CssMatcheable Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

WithDefaultSvg Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

HasDrawAttributes Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Tree = D1 (MetaData "Tree" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "CachedTree" PrefixI True) (S1 (MetaSel (Just "_treeBranch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TreeBranch) :*: S1 (MetaSel (Just "_treeHash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

pattern Tree :: TreeBranch -> Tree Source #

pattern None :: Tree Source #

data TreeBranch Source #

Instances
Eq TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TreeBranch :: Type -> Type #

Hashable TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TreeBranch = D1 (MetaData "TreeBranch" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((((C1 (MetaCons "NoNode" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UseNode" PrefixI True) (S1 (MetaSel (Just "useInformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Use) :*: S1 (MetaSel (Just "useSubTree") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Tree)))) :+: (C1 (MetaCons "GroupNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Group)) :+: (C1 (MetaCons "SymbolNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Group)) :+: C1 (MetaCons "DefinitionNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Group))))) :+: ((C1 (MetaCons "FilterNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Filter)) :+: (C1 (MetaCons "PathNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Path)) :+: C1 (MetaCons "CircleNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Circle)))) :+: (C1 (MetaCons "PolyLineNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PolyLine)) :+: (C1 (MetaCons "PolygonNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Polygon)) :+: C1 (MetaCons "EllipseNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Ellipse)))))) :+: (((C1 (MetaCons "LineNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Line)) :+: (C1 (MetaCons "RectangleNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Rectangle)) :+: C1 (MetaCons "TextNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextPath)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) :+: (C1 (MetaCons "ImageNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Image)) :+: (C1 (MetaCons "LinearGradientNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LinearGradient)) :+: C1 (MetaCons "RadialGradientNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RadialGradient))))) :+: ((C1 (MetaCons "MeshGradientNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MeshGradient)) :+: (C1 (MetaCons "PatternNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pattern)) :+: C1 (MetaCons "MarkerNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Marker)))) :+: (C1 (MetaCons "MaskNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Mask)) :+: (C1 (MetaCons "ClipPathNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ClipPath)) :+: C1 (MetaCons "SvgNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Document)))))))

data Number Source #

Encode complex number possibly dependant to the current render size.

Constructors

Num Double

Simple coordinate in current user coordinate.

Px Double

With suffix "px"

Em Double

Number relative to the current font size.

Percent Double

Number relative to the current viewport size.

Pc Double 
Mm Double

Number in millimeters, relative to DPI.

Cm Double

Number in centimeters, relative to DPI.

Point Double

Number in points, relative to DPI.

Inches Double

Number in inches, relative to DPI.

Instances
Eq Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Methods

(==) :: Number -> Number -> Bool #

(/=) :: Number -> Number -> Bool #

Show Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Generic Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Associated Types

type Rep Number :: Type -> Type #

Methods

from :: Number -> Rep Number x #

to :: Rep Number x -> Number #

Hashable Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Methods

hashWithSalt :: Int -> Number -> Int #

hash :: Number -> Int #

type Rep Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

data Spread Source #

Define the possible values for the spreadMethod values used for the gradient definitions.

Constructors

SpreadRepeat

reapeat value

SpreadPad

pad value

SpreadReflect

`reflect value`

Instances
Eq Spread Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Spread -> Spread -> Bool #

(/=) :: Spread -> Spread -> Bool #

Show Spread Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Spread Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Spread :: Type -> Type #

Methods

from :: Spread -> Rep Spread x #

to :: Rep Spread x -> Spread #

Hashable Spread Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Spread -> Int #

hash :: Spread -> Int #

type Rep Spread Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Spread = D1 (MetaData "Spread" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "SpreadRepeat" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SpreadPad" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SpreadReflect" PrefixI False) (U1 :: Type -> Type)))

data Texture Source #

Describe the different value which can be used in the fill or stroke attributes.

Constructors

ColorRef PixelRGBA8

Direct solid color (rgb)

TextureRef String

Link to a complex texture (url(#name))

FillNone

Equivalent to the none value.

Instances
Eq Texture Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Methods

(==) :: Texture -> Texture -> Bool #

(/=) :: Texture -> Texture -> Bool #

Show Texture Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic Texture Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep Texture :: Type -> Type #

Methods

from :: Texture -> Rep Texture x #

to :: Rep Texture x -> Texture #

Hashable Texture Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Texture -> Int #

hash :: Texture -> Int #

type Rep Texture Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep Texture = D1 (MetaData "Texture" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "ColorRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PixelRGBA8)) :+: (C1 (MetaCons "TextureRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "FillNone" PrefixI False) (U1 :: Type -> Type)))

data Element Source #

Sum types helping keeping track of all the namable elemens in a SVG document.

Instances
Eq Element Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Element -> Element -> Bool #

(/=) :: Element -> Element -> Bool #

Show Element Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Element Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Element :: Type -> Type #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

Hashable Element Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Element -> Int #

hash :: Element -> Int #

type Rep Element Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data FillRule Source #

Describe the possile filling algorithms. Map the values of the `fill-rule` attributes.

Constructors

FillEvenOdd

Correspond to the evenodd value.

FillNonZero

Correspond to the nonzero value.

Instances
Eq FillRule Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Show FillRule Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic FillRule Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep FillRule :: Type -> Type #

Methods

from :: FillRule -> Rep FillRule x #

to :: Rep FillRule x -> FillRule #

Hashable FillRule Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> FillRule -> Int #

hash :: FillRule -> Int #

type Rep FillRule Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep FillRule = D1 (MetaData "FillRule" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "FillEvenOdd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FillNonZero" PrefixI False) (U1 :: Type -> Type))

data FontStyle Source #

Classify the font style, used to search a matching font in the FontCache.

Instances
Eq FontStyle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show FontStyle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic FontStyle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FontStyle :: Type -> Type #

Hashable FontStyle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep FontStyle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep FontStyle = D1 (MetaData "FontStyle" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "FontStyleNormal" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FontStyleItalic" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FontStyleOblique" PrefixI False) (U1 :: Type -> Type)))

type Dpi = Int Source #

Alias describing a "dot per inch" information used for size calculation (see toUserUnit).

class WithDefaultSvg a where Source #

Define an empty 'default' element for the SVG tree. It is used as base when parsing the element from XML.

Methods

defaultSvg :: a Source #

The default element.

Instances
WithDefaultSvg DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg PreserveAspectRatio Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg TextPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg TextSpan Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg MeshGradientRow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg MeshGradientPatch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg GradientStop Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

WithDefaultSvg PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Main type

data Document Source #

Represent a full svg document with style, geometry and named elements.

Instances
Eq Document Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show Document Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Document Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Document :: Type -> Type #

Methods

from :: Document -> Rep Document x #

to :: Rep Document x -> Document #

Hashable Document Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Document -> Int #

hash :: Document -> Int #

type Rep Document Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

pattern SvgTree :: Document -> Tree Source #

documentSize :: Dpi -> Document -> (Int, Int) Source #

Calculate the document size in function of the different available attributes in the document.

Drawing attributes

data DrawAttributes Source #

This type define how to draw any primitives, which color to use, how to stroke the primitives and the potential transformations to use.

All these attributes are propagated to the children.

Constructors

DrawAttributes 

Fields

Instances
Eq DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep DrawAttributes :: Type -> Type #

Semigroup DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Monoid DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Hashable DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

drawAttributes :: Lens' DrawAttributes DrawAttributes Source #

attrClass :: Lens' DrawAttributes [Text] Source #

attrId :: Lens' DrawAttributes (Maybe String) Source #

clipPathRef :: Lens' DrawAttributes (Last ElementRef) Source #

clipRule :: Lens' DrawAttributes (Last FillRule) Source #

fillColor :: Lens' DrawAttributes (Last Texture) Source #

fillOpacity :: Lens' DrawAttributes (Maybe Float) Source #

fillRule :: Lens' DrawAttributes (Last FillRule) Source #

filterRef :: Lens' DrawAttributes (Last ElementRef) Source #

fontFamily :: Lens' DrawAttributes (Last [String]) Source #

fontSize :: Lens' DrawAttributes (Last Number) Source #

fontStyle :: Lens' DrawAttributes (Last FontStyle) Source #

groupOpacity :: Lens' DrawAttributes (Maybe Float) Source #

markerEnd :: Lens' DrawAttributes (Last ElementRef) Source #

markerMid :: Lens' DrawAttributes (Last ElementRef) Source #

markerStart :: Lens' DrawAttributes (Last ElementRef) Source #

maskRef :: Lens' DrawAttributes (Last ElementRef) Source #

strokeColor :: Lens' DrawAttributes (Last Texture) Source #

strokeDashArray :: Lens' DrawAttributes (Last [Number]) Source #

strokeLineCap :: Lens' DrawAttributes (Last Cap) Source #

strokeLineJoin :: Lens' DrawAttributes (Last LineJoin) Source #

strokeMiterLimit :: Lens' DrawAttributes (Last Double) Source #

strokeOffset :: Lens' DrawAttributes (Last Number) Source #

strokeOpacity :: Lens' DrawAttributes (Maybe Float) Source #

strokeWidth :: Lens' DrawAttributes (Last Number) Source #

textAnchor :: Lens' DrawAttributes (Last TextAnchor) Source #

transform :: Lens' DrawAttributes (Maybe [Transformation]) Source #

type Rep DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep DrawAttributes = D1 (MetaData "DrawAttributes" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "DrawAttributes" PrefixI True) ((((S1 (MetaSel (Just "_strokeWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Number)) :*: (S1 (MetaSel (Just "_strokeColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Texture)) :*: S1 (MetaSel (Just "_strokeOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Float)))) :*: (S1 (MetaSel (Just "_strokeLineCap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Cap)) :*: (S1 (MetaSel (Just "_strokeLineJoin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last LineJoin)) :*: S1 (MetaSel (Just "_strokeMiterLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Double))))) :*: ((S1 (MetaSel (Just "_fillColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Texture)) :*: (S1 (MetaSel (Just "_fillOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Float)) :*: S1 (MetaSel (Just "_groupOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Float)))) :*: ((S1 (MetaSel (Just "_transform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Transformation])) :*: S1 (MetaSel (Just "_fillRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FillRule))) :*: (S1 (MetaSel (Just "_maskRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last ElementRef)) :*: S1 (MetaSel (Just "_clipPathRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last ElementRef)))))) :*: (((S1 (MetaSel (Just "_clipRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FillRule)) :*: (S1 (MetaSel (Just "_attrClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Just "_attrId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe String)))) :*: (S1 (MetaSel (Just "_strokeOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Number)) :*: (S1 (MetaSel (Just "_strokeDashArray") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last [Number])) :*: S1 (MetaSel (Just "_fontSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Number))))) :*: ((S1 (MetaSel (Just "_fontFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last [String])) :*: (S1 (MetaSel (Just "_fontStyle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FontStyle)) :*: S1 (MetaSel (Just "_textAnchor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last TextAnchor)))) :*: ((S1 (MetaSel (Just "_markerStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last ElementRef)) :*: S1 (MetaSel (Just "_markerMid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last ElementRef))) :*: (S1 (MetaSel (Just "_markerEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last ElementRef)) :*: S1 (MetaSel (Just "_filterRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last ElementRef))))))))

class HasDrawAttributes c where Source #

Minimal complete definition

drawAttributes

Instances
HasDrawAttributes DrawAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

drawAttributes :: Lens' DrawAttributes DrawAttributes Source #

attrClass :: Lens' DrawAttributes [Text] Source #

attrId :: Lens' DrawAttributes (Maybe String) Source #

clipPathRef :: Lens' DrawAttributes (Last ElementRef) Source #

clipRule :: Lens' DrawAttributes (Last FillRule) Source #

fillColor :: Lens' DrawAttributes (Last Texture) Source #

fillOpacity :: Lens' DrawAttributes (Maybe Float) Source #

fillRule :: Lens' DrawAttributes (Last FillRule) Source #

filterRef :: Lens' DrawAttributes (Last ElementRef) Source #

fontFamily :: Lens' DrawAttributes (Last [String]) Source #

fontSize :: Lens' DrawAttributes (Last Number) Source #

fontStyle :: Lens' DrawAttributes (Last FontStyle) Source #

groupOpacity :: Lens' DrawAttributes (Maybe Float) Source #

markerEnd :: Lens' DrawAttributes (Last ElementRef) Source #

markerMid :: Lens' DrawAttributes (Last ElementRef) Source #

markerStart :: Lens' DrawAttributes (Last ElementRef) Source #

maskRef :: Lens' DrawAttributes (Last ElementRef) Source #

strokeColor :: Lens' DrawAttributes (Last Texture) Source #

strokeDashArray :: Lens' DrawAttributes (Last [Number]) Source #

strokeLineCap :: Lens' DrawAttributes (Last Cap) Source #

strokeLineJoin :: Lens' DrawAttributes (Last LineJoin) Source #

strokeMiterLimit :: Lens' DrawAttributes (Last Double) Source #

strokeOffset :: Lens' DrawAttributes (Last Number) Source #

strokeOpacity :: Lens' DrawAttributes (Maybe Float) Source #

strokeWidth :: Lens' DrawAttributes (Last Number) Source #

textAnchor :: Lens' DrawAttributes (Last TextAnchor) Source #

transform :: Lens' DrawAttributes (Maybe [Transformation]) Source #

HasDrawAttributes Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' RadialGradient DrawAttributes Source #

attrClass :: Lens' RadialGradient [Text] Source #

attrId :: Lens' RadialGradient (Maybe String) Source #

clipPathRef :: Lens' RadialGradient (Last ElementRef) Source #

clipRule :: Lens' RadialGradient (Last FillRule) Source #

fillColor :: Lens' RadialGradient (Last Texture) Source #

fillOpacity :: Lens' RadialGradient (Maybe Float) Source #

fillRule :: Lens' RadialGradient (Last FillRule) Source #

filterRef :: Lens' RadialGradient (Last ElementRef) Source #

fontFamily :: Lens' RadialGradient (Last [String]) Source #

fontSize :: Lens' RadialGradient (Last Number) Source #

fontStyle :: Lens' RadialGradient (Last FontStyle) Source #

groupOpacity :: Lens' RadialGradient (Maybe Float) Source #

markerEnd :: Lens' RadialGradient (Last ElementRef) Source #

markerMid :: Lens' RadialGradient (Last ElementRef) Source #

markerStart :: Lens' RadialGradient (Last ElementRef) Source #

maskRef :: Lens' RadialGradient (Last ElementRef) Source #

strokeColor :: Lens' RadialGradient (Last Texture) Source #

strokeDashArray :: Lens' RadialGradient (Last [Number]) Source #

strokeLineCap :: Lens' RadialGradient (Last Cap) Source #

strokeLineJoin :: Lens' RadialGradient (Last LineJoin) Source #

strokeMiterLimit :: Lens' RadialGradient (Last Double) Source #

strokeOffset :: Lens' RadialGradient (Last Number) Source #

strokeOpacity :: Lens' RadialGradient (Maybe Float) Source #

strokeWidth :: Lens' RadialGradient (Last Number) Source #

textAnchor :: Lens' RadialGradient (Last TextAnchor) Source #

transform :: Lens' RadialGradient (Maybe [Transformation]) Source #

HasDrawAttributes LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' LinearGradient DrawAttributes Source #

attrClass :: Lens' LinearGradient [Text] Source #

attrId :: Lens' LinearGradient (Maybe String) Source #

clipPathRef :: Lens' LinearGradient (Last ElementRef) Source #

clipRule :: Lens' LinearGradient (Last FillRule) Source #

fillColor :: Lens' LinearGradient (Last Texture) Source #

fillOpacity :: Lens' LinearGradient (Maybe Float) Source #

fillRule :: Lens' LinearGradient (Last FillRule) Source #

filterRef :: Lens' LinearGradient (Last ElementRef) Source #

fontFamily :: Lens' LinearGradient (Last [String]) Source #

fontSize :: Lens' LinearGradient (Last Number) Source #

fontStyle :: Lens' LinearGradient (Last FontStyle) Source #

groupOpacity :: Lens' LinearGradient (Maybe Float) Source #

markerEnd :: Lens' LinearGradient (Last ElementRef) Source #

markerMid :: Lens' LinearGradient (Last ElementRef) Source #

markerStart :: Lens' LinearGradient (Last ElementRef) Source #

maskRef :: Lens' LinearGradient (Last ElementRef) Source #

strokeColor :: Lens' LinearGradient (Last Texture) Source #

strokeDashArray :: Lens' LinearGradient (Last [Number]) Source #

strokeLineCap :: Lens' LinearGradient (Last Cap) Source #

strokeLineJoin :: Lens' LinearGradient (Last LineJoin) Source #

strokeMiterLimit :: Lens' LinearGradient (Last Double) Source #

strokeOffset :: Lens' LinearGradient (Last Number) Source #

strokeOpacity :: Lens' LinearGradient (Maybe Float) Source #

strokeWidth :: Lens' LinearGradient (Last Number) Source #

textAnchor :: Lens' LinearGradient (Last TextAnchor) Source #

transform :: Lens' LinearGradient (Maybe [Transformation]) Source #

HasDrawAttributes Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' GaussianBlur DrawAttributes Source #

attrClass :: Lens' GaussianBlur [Text] Source #

attrId :: Lens' GaussianBlur (Maybe String) Source #

clipPathRef :: Lens' GaussianBlur (Last ElementRef) Source #

clipRule :: Lens' GaussianBlur (Last FillRule) Source #

fillColor :: Lens' GaussianBlur (Last Texture) Source #

fillOpacity :: Lens' GaussianBlur (Maybe Float) Source #

fillRule :: Lens' GaussianBlur (Last FillRule) Source #

filterRef :: Lens' GaussianBlur (Last ElementRef) Source #

fontFamily :: Lens' GaussianBlur (Last [String]) Source #

fontSize :: Lens' GaussianBlur (Last Number) Source #

fontStyle :: Lens' GaussianBlur (Last FontStyle) Source #

groupOpacity :: Lens' GaussianBlur (Maybe Float) Source #

markerEnd :: Lens' GaussianBlur (Last ElementRef) Source #

markerMid :: Lens' GaussianBlur (Last ElementRef) Source #

markerStart :: Lens' GaussianBlur (Last ElementRef) Source #

maskRef :: Lens' GaussianBlur (Last ElementRef) Source #

strokeColor :: Lens' GaussianBlur (Last Texture) Source #

strokeDashArray :: Lens' GaussianBlur (Last [Number]) Source #

strokeLineCap :: Lens' GaussianBlur (Last Cap) Source #

strokeLineJoin :: Lens' GaussianBlur (Last LineJoin) Source #

strokeMiterLimit :: Lens' GaussianBlur (Last Double) Source #

strokeOffset :: Lens' GaussianBlur (Last Number) Source #

strokeOpacity :: Lens' GaussianBlur (Maybe Float) Source #

strokeWidth :: Lens' GaussianBlur (Last Number) Source #

textAnchor :: Lens' GaussianBlur (Last TextAnchor) Source #

transform :: Lens' GaussianBlur (Maybe [Transformation]) Source #

HasDrawAttributes Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' ColorMatrix DrawAttributes Source #

attrClass :: Lens' ColorMatrix [Text] Source #

attrId :: Lens' ColorMatrix (Maybe String) Source #

clipPathRef :: Lens' ColorMatrix (Last ElementRef) Source #

clipRule :: Lens' ColorMatrix (Last FillRule) Source #

fillColor :: Lens' ColorMatrix (Last Texture) Source #

fillOpacity :: Lens' ColorMatrix (Maybe Float) Source #

fillRule :: Lens' ColorMatrix (Last FillRule) Source #

filterRef :: Lens' ColorMatrix (Last ElementRef) Source #

fontFamily :: Lens' ColorMatrix (Last [String]) Source #

fontSize :: Lens' ColorMatrix (Last Number) Source #

fontStyle :: Lens' ColorMatrix (Last FontStyle) Source #

groupOpacity :: Lens' ColorMatrix (Maybe Float) Source #

markerEnd :: Lens' ColorMatrix (Last ElementRef) Source #

markerMid :: Lens' ColorMatrix (Last ElementRef) Source #

markerStart :: Lens' ColorMatrix (Last ElementRef) Source #

maskRef :: Lens' ColorMatrix (Last ElementRef) Source #

strokeColor :: Lens' ColorMatrix (Last Texture) Source #

strokeDashArray :: Lens' ColorMatrix (Last [Number]) Source #

strokeLineCap :: Lens' ColorMatrix (Last Cap) Source #

strokeLineJoin :: Lens' ColorMatrix (Last LineJoin) Source #

strokeMiterLimit :: Lens' ColorMatrix (Last Double) Source #

strokeOffset :: Lens' ColorMatrix (Last Number) Source #

strokeOpacity :: Lens' ColorMatrix (Maybe Float) Source #

strokeWidth :: Lens' ColorMatrix (Last Number) Source #

textAnchor :: Lens' ColorMatrix (Last TextAnchor) Source #

transform :: Lens' ColorMatrix (Maybe [Transformation]) Source #

HasDrawAttributes FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' ComponentTransfer DrawAttributes Source #

attrClass :: Lens' ComponentTransfer [Text] Source #

attrId :: Lens' ComponentTransfer (Maybe String) Source #

clipPathRef :: Lens' ComponentTransfer (Last ElementRef) Source #

clipRule :: Lens' ComponentTransfer (Last FillRule) Source #

fillColor :: Lens' ComponentTransfer (Last Texture) Source #

fillOpacity :: Lens' ComponentTransfer (Maybe Float) Source #

fillRule :: Lens' ComponentTransfer (Last FillRule) Source #

filterRef :: Lens' ComponentTransfer (Last ElementRef) Source #

fontFamily :: Lens' ComponentTransfer (Last [String]) Source #

fontSize :: Lens' ComponentTransfer (Last Number) Source #

fontStyle :: Lens' ComponentTransfer (Last FontStyle) Source #

groupOpacity :: Lens' ComponentTransfer (Maybe Float) Source #

markerEnd :: Lens' ComponentTransfer (Last ElementRef) Source #

markerMid :: Lens' ComponentTransfer (Last ElementRef) Source #

markerStart :: Lens' ComponentTransfer (Last ElementRef) Source #

maskRef :: Lens' ComponentTransfer (Last ElementRef) Source #

strokeColor :: Lens' ComponentTransfer (Last Texture) Source #

strokeDashArray :: Lens' ComponentTransfer (Last [Number]) Source #

strokeLineCap :: Lens' ComponentTransfer (Last Cap) Source #

strokeLineJoin :: Lens' ComponentTransfer (Last LineJoin) Source #

strokeMiterLimit :: Lens' ComponentTransfer (Last Double) Source #

strokeOffset :: Lens' ComponentTransfer (Last Number) Source #

strokeOpacity :: Lens' ComponentTransfer (Maybe Float) Source #

strokeWidth :: Lens' ComponentTransfer (Last Number) Source #

textAnchor :: Lens' ComponentTransfer (Last TextAnchor) Source #

transform :: Lens' ComponentTransfer (Maybe [Transformation]) Source #

HasDrawAttributes MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' DisplacementMap DrawAttributes Source #

attrClass :: Lens' DisplacementMap [Text] Source #

attrId :: Lens' DisplacementMap (Maybe String) Source #

clipPathRef :: Lens' DisplacementMap (Last ElementRef) Source #

clipRule :: Lens' DisplacementMap (Last FillRule) Source #

fillColor :: Lens' DisplacementMap (Last Texture) Source #

fillOpacity :: Lens' DisplacementMap (Maybe Float) Source #

fillRule :: Lens' DisplacementMap (Last FillRule) Source #

filterRef :: Lens' DisplacementMap (Last ElementRef) Source #

fontFamily :: Lens' DisplacementMap (Last [String]) Source #

fontSize :: Lens' DisplacementMap (Last Number) Source #

fontStyle :: Lens' DisplacementMap (Last FontStyle) Source #

groupOpacity :: Lens' DisplacementMap (Maybe Float) Source #

markerEnd :: Lens' DisplacementMap (Last ElementRef) Source #

markerMid :: Lens' DisplacementMap (Last ElementRef) Source #

markerStart :: Lens' DisplacementMap (Last ElementRef) Source #

maskRef :: Lens' DisplacementMap (Last ElementRef) Source #

strokeColor :: Lens' DisplacementMap (Last Texture) Source #

strokeDashArray :: Lens' DisplacementMap (Last [Number]) Source #

strokeLineCap :: Lens' DisplacementMap (Last Cap) Source #

strokeLineJoin :: Lens' DisplacementMap (Last LineJoin) Source #

strokeMiterLimit :: Lens' DisplacementMap (Last Double) Source #

strokeOffset :: Lens' DisplacementMap (Last Number) Source #

strokeOpacity :: Lens' DisplacementMap (Maybe Float) Source #

strokeWidth :: Lens' DisplacementMap (Last Number) Source #

textAnchor :: Lens' DisplacementMap (Last TextAnchor) Source #

transform :: Lens' DisplacementMap (Maybe [Transformation]) Source #

HasDrawAttributes ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' DiffuseLighting DrawAttributes Source #

attrClass :: Lens' DiffuseLighting [Text] Source #

attrId :: Lens' DiffuseLighting (Maybe String) Source #

clipPathRef :: Lens' DiffuseLighting (Last ElementRef) Source #

clipRule :: Lens' DiffuseLighting (Last FillRule) Source #

fillColor :: Lens' DiffuseLighting (Last Texture) Source #

fillOpacity :: Lens' DiffuseLighting (Maybe Float) Source #

fillRule :: Lens' DiffuseLighting (Last FillRule) Source #

filterRef :: Lens' DiffuseLighting (Last ElementRef) Source #

fontFamily :: Lens' DiffuseLighting (Last [String]) Source #

fontSize :: Lens' DiffuseLighting (Last Number) Source #

fontStyle :: Lens' DiffuseLighting (Last FontStyle) Source #

groupOpacity :: Lens' DiffuseLighting (Maybe Float) Source #

markerEnd :: Lens' DiffuseLighting (Last ElementRef) Source #

markerMid :: Lens' DiffuseLighting (Last ElementRef) Source #

markerStart :: Lens' DiffuseLighting (Last ElementRef) Source #

maskRef :: Lens' DiffuseLighting (Last ElementRef) Source #

strokeColor :: Lens' DiffuseLighting (Last Texture) Source #

strokeDashArray :: Lens' DiffuseLighting (Last [Number]) Source #

strokeLineCap :: Lens' DiffuseLighting (Last Cap) Source #

strokeLineJoin :: Lens' DiffuseLighting (Last LineJoin) Source #

strokeMiterLimit :: Lens' DiffuseLighting (Last Double) Source #

strokeOffset :: Lens' DiffuseLighting (Last Number) Source #

strokeOpacity :: Lens' DiffuseLighting (Maybe Float) Source #

strokeWidth :: Lens' DiffuseLighting (Last Number) Source #

textAnchor :: Lens' DiffuseLighting (Last TextAnchor) Source #

transform :: Lens' DiffuseLighting (Maybe [Transformation]) Source #

HasDrawAttributes ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' ConvolveMatrix DrawAttributes Source #

attrClass :: Lens' ConvolveMatrix [Text] Source #

attrId :: Lens' ConvolveMatrix (Maybe String) Source #

clipPathRef :: Lens' ConvolveMatrix (Last ElementRef) Source #

clipRule :: Lens' ConvolveMatrix (Last FillRule) Source #

fillColor :: Lens' ConvolveMatrix (Last Texture) Source #

fillOpacity :: Lens' ConvolveMatrix (Maybe Float) Source #

fillRule :: Lens' ConvolveMatrix (Last FillRule) Source #

filterRef :: Lens' ConvolveMatrix (Last ElementRef) Source #

fontFamily :: Lens' ConvolveMatrix (Last [String]) Source #

fontSize :: Lens' ConvolveMatrix (Last Number) Source #

fontStyle :: Lens' ConvolveMatrix (Last FontStyle) Source #

groupOpacity :: Lens' ConvolveMatrix (Maybe Float) Source #

markerEnd :: Lens' ConvolveMatrix (Last ElementRef) Source #

markerMid :: Lens' ConvolveMatrix (Last ElementRef) Source #

markerStart :: Lens' ConvolveMatrix (Last ElementRef) Source #

maskRef :: Lens' ConvolveMatrix (Last ElementRef) Source #

strokeColor :: Lens' ConvolveMatrix (Last Texture) Source #

strokeDashArray :: Lens' ConvolveMatrix (Last [Number]) Source #

strokeLineCap :: Lens' ConvolveMatrix (Last Cap) Source #

strokeLineJoin :: Lens' ConvolveMatrix (Last LineJoin) Source #

strokeMiterLimit :: Lens' ConvolveMatrix (Last Double) Source #

strokeOffset :: Lens' ConvolveMatrix (Last Number) Source #

strokeOpacity :: Lens' ConvolveMatrix (Maybe Float) Source #

strokeWidth :: Lens' ConvolveMatrix (Last Number) Source #

textAnchor :: Lens' ConvolveMatrix (Last TextAnchor) Source #

transform :: Lens' ConvolveMatrix (Maybe [Transformation]) Source #

HasDrawAttributes SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' SpecularLighting DrawAttributes Source #

attrClass :: Lens' SpecularLighting [Text] Source #

attrId :: Lens' SpecularLighting (Maybe String) Source #

clipPathRef :: Lens' SpecularLighting (Last ElementRef) Source #

clipRule :: Lens' SpecularLighting (Last FillRule) Source #

fillColor :: Lens' SpecularLighting (Last Texture) Source #

fillOpacity :: Lens' SpecularLighting (Maybe Float) Source #

fillRule :: Lens' SpecularLighting (Last FillRule) Source #

filterRef :: Lens' SpecularLighting (Last ElementRef) Source #

fontFamily :: Lens' SpecularLighting (Last [String]) Source #

fontSize :: Lens' SpecularLighting (Last Number) Source #

fontStyle :: Lens' SpecularLighting (Last FontStyle) Source #

groupOpacity :: Lens' SpecularLighting (Maybe Float) Source #

markerEnd :: Lens' SpecularLighting (Last ElementRef) Source #

markerMid :: Lens' SpecularLighting (Last ElementRef) Source #

markerStart :: Lens' SpecularLighting (Last ElementRef) Source #

maskRef :: Lens' SpecularLighting (Last ElementRef) Source #

strokeColor :: Lens' SpecularLighting (Last Texture) Source #

strokeDashArray :: Lens' SpecularLighting (Last [Number]) Source #

strokeLineCap :: Lens' SpecularLighting (Last Cap) Source #

strokeLineJoin :: Lens' SpecularLighting (Last LineJoin) Source #

strokeMiterLimit :: Lens' SpecularLighting (Last Double) Source #

strokeOffset :: Lens' SpecularLighting (Last Number) Source #

strokeOpacity :: Lens' SpecularLighting (Maybe Float) Source #

strokeWidth :: Lens' SpecularLighting (Last Number) Source #

textAnchor :: Lens' SpecularLighting (Last TextAnchor) Source #

transform :: Lens' SpecularLighting (Maybe [Transformation]) Source #

HasDrawAttributes TreeBranch Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' MeshGradient DrawAttributes Source #

attrClass :: Lens' MeshGradient [Text] Source #

attrId :: Lens' MeshGradient (Maybe String) Source #

clipPathRef :: Lens' MeshGradient (Last ElementRef) Source #

clipRule :: Lens' MeshGradient (Last FillRule) Source #

fillColor :: Lens' MeshGradient (Last Texture) Source #

fillOpacity :: Lens' MeshGradient (Maybe Float) Source #

fillRule :: Lens' MeshGradient (Last FillRule) Source #

filterRef :: Lens' MeshGradient (Last ElementRef) Source #

fontFamily :: Lens' MeshGradient (Last [String]) Source #

fontSize :: Lens' MeshGradient (Last Number) Source #

fontStyle :: Lens' MeshGradient (Last FontStyle) Source #

groupOpacity :: Lens' MeshGradient (Maybe Float) Source #

markerEnd :: Lens' MeshGradient (Last ElementRef) Source #

markerMid :: Lens' MeshGradient (Last ElementRef) Source #

markerStart :: Lens' MeshGradient (Last ElementRef) Source #

maskRef :: Lens' MeshGradient (Last ElementRef) Source #

strokeColor :: Lens' MeshGradient (Last Texture) Source #

strokeDashArray :: Lens' MeshGradient (Last [Number]) Source #

strokeLineCap :: Lens' MeshGradient (Last Cap) Source #

strokeLineJoin :: Lens' MeshGradient (Last LineJoin) Source #

strokeMiterLimit :: Lens' MeshGradient (Last Double) Source #

strokeOffset :: Lens' MeshGradient (Last Number) Source #

strokeOpacity :: Lens' MeshGradient (Maybe Float) Source #

strokeWidth :: Lens' MeshGradient (Last Number) Source #

textAnchor :: Lens' MeshGradient (Last TextAnchor) Source #

transform :: Lens' MeshGradient (Maybe [Transformation]) Source #

HasDrawAttributes Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasDrawAttributes PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Filters

data FilterElement Source #

Instances
Eq FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FilterElement :: Type -> Type #

Hashable FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasFilterAttributes FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep FilterElement = D1 (MetaData "FilterElement" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((((C1 (MetaCons "FEBlend" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Blend)) :+: C1 (MetaCons "FEColorMatrix" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ColorMatrix))) :+: (C1 (MetaCons "FEComponentTransfer" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ComponentTransfer)) :+: (C1 (MetaCons "FEComposite" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Composite)) :+: C1 (MetaCons "FEConvolveMatrix" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConvolveMatrix))))) :+: ((C1 (MetaCons "FEDiffuseLighting" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DiffuseLighting)) :+: (C1 (MetaCons "FEDisplacementMap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DisplacementMap)) :+: C1 (MetaCons "FEDropShadow" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DropShadow)))) :+: (C1 (MetaCons "FEFlood" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Flood)) :+: (C1 (MetaCons "FEFuncA" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FuncA)) :+: C1 (MetaCons "FEFuncB" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FuncB)))))) :+: (((C1 (MetaCons "FEFuncG" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FuncG)) :+: (C1 (MetaCons "FEFuncR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FuncR)) :+: C1 (MetaCons "FEGaussianBlur" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GaussianBlur)))) :+: (C1 (MetaCons "FEImage" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageF)) :+: (C1 (MetaCons "FEMerge" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Merge)) :+: C1 (MetaCons "FEMergeNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MergeNode))))) :+: ((C1 (MetaCons "FEMorphology" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Morphology)) :+: (C1 (MetaCons "FEOffset" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Offset)) :+: C1 (MetaCons "FESpecularLighting" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SpecularLighting)))) :+: (C1 (MetaCons "FETile" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tile)) :+: (C1 (MetaCons "FETurbulence" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Turbulence)) :+: C1 (MetaCons "FENone" PrefixI False) (U1 :: Type -> Type))))))

data FilterAttributes Source #

Instances
Eq FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FilterAttributes :: Type -> Type #

Hashable FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasFilterAttributes FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep FilterAttributes = D1 (MetaData "FilterAttributes" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "FilterAttributes" PrefixI True) ((S1 (MetaSel (Just "_filterHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Number)) :*: S1 (MetaSel (Just "_filterResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe String))) :*: (S1 (MetaSel (Just "_filterWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Number)) :*: (S1 (MetaSel (Just "_filterX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Number)) :*: S1 (MetaSel (Just "_filterY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Number))))))

class HasFilterAttributes c where Source #

Minimal complete definition

filterAttributes

Instances
HasFilterAttributes FilterAttributes Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasFilterAttributes GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes FilterElement Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

data FilterSource Source #

Instances
Eq FilterSource Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show FilterSource Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic FilterSource Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FilterSource :: Type -> Type #

Hashable FilterSource Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep FilterSource Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep FilterSource = D1 (MetaData "FilterSource" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((C1 (MetaCons "SourceGraphic" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SourceAlpha" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BackgroundImage" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "BackgroundAlpha" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FillPaint" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StrokePaint" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SourceRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))

data Blend Source #

Instances
Eq Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Blend -> Blend -> Bool #

(/=) :: Blend -> Blend -> Bool #

Show Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Blend -> ShowS #

show :: Blend -> String #

showList :: [Blend] -> ShowS #

Generic Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Blend :: Type -> Type #

Methods

from :: Blend -> Rep Blend x #

to :: Rep Blend x -> Blend #

Hashable Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Blend -> Int #

hash :: Blend -> Int #

WithDefaultSvg Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Blend Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data BlendMode Source #

Instances
Eq BlendMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show BlendMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic BlendMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep BlendMode :: Type -> Type #

Hashable BlendMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep BlendMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep BlendMode = D1 (MetaData "BlendMode" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((((C1 (MetaCons "Normal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Multiply" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Screen" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Overlay" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Darken" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Lighten" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ColorDodge" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ColorBurn" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "HardLight" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SoftLight" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Difference" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Exclusion" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Hue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Saturation" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Color" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Luminosity" PrefixI False) (U1 :: Type -> Type)))))

data ConvolveMatrix Source #

Instances
Eq ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ConvolveMatrix :: Type -> Type #

Hashable ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' ConvolveMatrix DrawAttributes Source #

attrClass :: Lens' ConvolveMatrix [Text] Source #

attrId :: Lens' ConvolveMatrix (Maybe String) Source #

clipPathRef :: Lens' ConvolveMatrix (Last ElementRef) Source #

clipRule :: Lens' ConvolveMatrix (Last FillRule) Source #

fillColor :: Lens' ConvolveMatrix (Last Texture) Source #

fillOpacity :: Lens' ConvolveMatrix (Maybe Float) Source #

fillRule :: Lens' ConvolveMatrix (Last FillRule) Source #

filterRef :: Lens' ConvolveMatrix (Last ElementRef) Source #

fontFamily :: Lens' ConvolveMatrix (Last [String]) Source #

fontSize :: Lens' ConvolveMatrix (Last Number) Source #

fontStyle :: Lens' ConvolveMatrix (Last FontStyle) Source #

groupOpacity :: Lens' ConvolveMatrix (Maybe Float) Source #

markerEnd :: Lens' ConvolveMatrix (Last ElementRef) Source #

markerMid :: Lens' ConvolveMatrix (Last ElementRef) Source #

markerStart :: Lens' ConvolveMatrix (Last ElementRef) Source #

maskRef :: Lens' ConvolveMatrix (Last ElementRef) Source #

strokeColor :: Lens' ConvolveMatrix (Last Texture) Source #

strokeDashArray :: Lens' ConvolveMatrix (Last [Number]) Source #

strokeLineCap :: Lens' ConvolveMatrix (Last Cap) Source #

strokeLineJoin :: Lens' ConvolveMatrix (Last LineJoin) Source #

strokeMiterLimit :: Lens' ConvolveMatrix (Last Double) Source #

strokeOffset :: Lens' ConvolveMatrix (Last Number) Source #

strokeOpacity :: Lens' ConvolveMatrix (Maybe Float) Source #

strokeWidth :: Lens' ConvolveMatrix (Last Number) Source #

textAnchor :: Lens' ConvolveMatrix (Last TextAnchor) Source #

transform :: Lens' ConvolveMatrix (Maybe [Transformation]) Source #

HasFilterAttributes ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep ConvolveMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ConvolveMatrix = D1 (MetaData "ConvolveMatrix" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "ConvolveMatrix" PrefixI True) (((S1 (MetaSel (Just "_convolveMatrixDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_convolveMatrixFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_convolveMatrixIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)))) :*: (S1 (MetaSel (Just "_convolveMatrixOrder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumberOptionalNumber) :*: (S1 (MetaSel (Just "_convolveMatrixKernelMatrix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Double]) :*: S1 (MetaSel (Just "_convolveMatrixDivisor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))) :*: ((S1 (MetaSel (Just "_convolveMatrixBias") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Just "_convolveMatrixTargetX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "_convolveMatrixTargetY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :*: (S1 (MetaSel (Just "_convolveMatrixEdgeMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EdgeMode) :*: (S1 (MetaSel (Just "_convolveMatrixKernelUnitLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumberOptionalNumber) :*: S1 (MetaSel (Just "_convolveMatrixPreserveAlpha") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))))

data Morphology Source #

Instances
Eq Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Morphology :: Type -> Type #

Hashable Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Morphology Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Morphology = D1 (MetaData "Morphology" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Morphology" PrefixI True) ((S1 (MetaSel (Just "_morphologyDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_morphologyFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes)) :*: (S1 (MetaSel (Just "_morphologyIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)) :*: (S1 (MetaSel (Just "_morphologyOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OperatorType) :*: S1 (MetaSel (Just "_morphologyRadius") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumberOptionalNumber)))))

data OperatorType Source #

Instances
Eq OperatorType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show OperatorType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic OperatorType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep OperatorType :: Type -> Type #

Hashable OperatorType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep OperatorType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep OperatorType = D1 (MetaData "OperatorType" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((C1 (MetaCons "OperatorOver" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OperatorIn" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OperatorOut" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "OperatorAtop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OperatorXor" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OperatorLighter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OperatorArithmetic" PrefixI False) (U1 :: Type -> Type))))

data NumberOptionalNumber Source #

Constructors

Num1 Double 
Num2 Double Double 
Instances
Eq NumberOptionalNumber Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show NumberOptionalNumber Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic NumberOptionalNumber Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep NumberOptionalNumber :: Type -> Type #

Hashable NumberOptionalNumber Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep NumberOptionalNumber Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data SpecularLighting Source #

Instances
Eq SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep SpecularLighting :: Type -> Type #

Hashable SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' SpecularLighting DrawAttributes Source #

attrClass :: Lens' SpecularLighting [Text] Source #

attrId :: Lens' SpecularLighting (Maybe String) Source #

clipPathRef :: Lens' SpecularLighting (Last ElementRef) Source #

clipRule :: Lens' SpecularLighting (Last FillRule) Source #

fillColor :: Lens' SpecularLighting (Last Texture) Source #

fillOpacity :: Lens' SpecularLighting (Maybe Float) Source #

fillRule :: Lens' SpecularLighting (Last FillRule) Source #

filterRef :: Lens' SpecularLighting (Last ElementRef) Source #

fontFamily :: Lens' SpecularLighting (Last [String]) Source #

fontSize :: Lens' SpecularLighting (Last Number) Source #

fontStyle :: Lens' SpecularLighting (Last FontStyle) Source #

groupOpacity :: Lens' SpecularLighting (Maybe Float) Source #

markerEnd :: Lens' SpecularLighting (Last ElementRef) Source #

markerMid :: Lens' SpecularLighting (Last ElementRef) Source #

markerStart :: Lens' SpecularLighting (Last ElementRef) Source #

maskRef :: Lens' SpecularLighting (Last ElementRef) Source #

strokeColor :: Lens' SpecularLighting (Last Texture) Source #

strokeDashArray :: Lens' SpecularLighting (Last [Number]) Source #

strokeLineCap :: Lens' SpecularLighting (Last Cap) Source #

strokeLineJoin :: Lens' SpecularLighting (Last LineJoin) Source #

strokeMiterLimit :: Lens' SpecularLighting (Last Double) Source #

strokeOffset :: Lens' SpecularLighting (Last Number) Source #

strokeOpacity :: Lens' SpecularLighting (Maybe Float) Source #

strokeWidth :: Lens' SpecularLighting (Last Number) Source #

textAnchor :: Lens' SpecularLighting (Last TextAnchor) Source #

transform :: Lens' SpecularLighting (Maybe [Transformation]) Source #

HasFilterAttributes SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep SpecularLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep SpecularLighting = D1 (MetaData "SpecularLighting" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "SpecularLighting" PrefixI True) ((S1 (MetaSel (Just "_specLightingDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_specLightingFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_specLightingIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)))) :*: ((S1 (MetaSel (Just "_specLightingSurfaceScale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "_specLightingSpecularConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :*: (S1 (MetaSel (Just "_specLightingSpecularExp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "_specLightingKernelUnitLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumberOptionalNumber)))))

data DiffuseLighting Source #

Instances
Eq DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep DiffuseLighting :: Type -> Type #

Hashable DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' DiffuseLighting DrawAttributes Source #

attrClass :: Lens' DiffuseLighting [Text] Source #

attrId :: Lens' DiffuseLighting (Maybe String) Source #

clipPathRef :: Lens' DiffuseLighting (Last ElementRef) Source #

clipRule :: Lens' DiffuseLighting (Last FillRule) Source #

fillColor :: Lens' DiffuseLighting (Last Texture) Source #

fillOpacity :: Lens' DiffuseLighting (Maybe Float) Source #

fillRule :: Lens' DiffuseLighting (Last FillRule) Source #

filterRef :: Lens' DiffuseLighting (Last ElementRef) Source #

fontFamily :: Lens' DiffuseLighting (Last [String]) Source #

fontSize :: Lens' DiffuseLighting (Last Number) Source #

fontStyle :: Lens' DiffuseLighting (Last FontStyle) Source #

groupOpacity :: Lens' DiffuseLighting (Maybe Float) Source #

markerEnd :: Lens' DiffuseLighting (Last ElementRef) Source #

markerMid :: Lens' DiffuseLighting (Last ElementRef) Source #

markerStart :: Lens' DiffuseLighting (Last ElementRef) Source #

maskRef :: Lens' DiffuseLighting (Last ElementRef) Source #

strokeColor :: Lens' DiffuseLighting (Last Texture) Source #

strokeDashArray :: Lens' DiffuseLighting (Last [Number]) Source #

strokeLineCap :: Lens' DiffuseLighting (Last Cap) Source #

strokeLineJoin :: Lens' DiffuseLighting (Last LineJoin) Source #

strokeMiterLimit :: Lens' DiffuseLighting (Last Double) Source #

strokeOffset :: Lens' DiffuseLighting (Last Number) Source #

strokeOpacity :: Lens' DiffuseLighting (Maybe Float) Source #

strokeWidth :: Lens' DiffuseLighting (Last Number) Source #

textAnchor :: Lens' DiffuseLighting (Last TextAnchor) Source #

transform :: Lens' DiffuseLighting (Maybe [Transformation]) Source #

HasFilterAttributes DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep DiffuseLighting Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep DiffuseLighting = D1 (MetaData "DiffuseLighting" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "DiffuseLighting" PrefixI True) ((S1 (MetaSel (Just "_diffuseLightingDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_diffuseLightingFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_diffuseLightingIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)))) :*: (S1 (MetaSel (Just "_diffuseLightingSurfaceScale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Just "_diffuseLightingDiffuseConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "_diffuseLightingKernelUnitLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumberOptionalNumber)))))

data DropShadow Source #

Instances
Eq DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep DropShadow :: Type -> Type #

Hashable DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep DropShadow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep DropShadow = D1 (MetaData "DropShadow" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "DropShadow" PrefixI True) ((S1 (MetaSel (Just "_dropShadowDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_dropShadowFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes)) :*: (S1 (MetaSel (Just "_dropShadowDx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Just "_dropShadowDy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "_dropShadowStdDeviation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumberOptionalNumber)))))

data Flood Source #

Instances
Eq Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Flood -> Flood -> Bool #

(/=) :: Flood -> Flood -> Bool #

Show Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Flood -> ShowS #

show :: Flood -> String #

showList :: [Flood] -> ShowS #

Generic Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Flood :: Type -> Type #

Methods

from :: Flood -> Rep Flood x #

to :: Rep Flood x -> Flood #

Hashable Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Flood -> Int #

hash :: Flood -> Int #

WithDefaultSvg Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Flood Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Flood = D1 (MetaData "Flood" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Flood" PrefixI True) ((S1 (MetaSel (Just "_floodDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_floodFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes)) :*: (S1 (MetaSel (Just "_floodColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PixelRGBA8) :*: S1 (MetaSel (Just "_floodOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)))))

data Tile Source #

Instances
Eq Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Tile -> Tile -> Bool #

(/=) :: Tile -> Tile -> Bool #

Show Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Tile -> ShowS #

show :: Tile -> String #

showList :: [Tile] -> ShowS #

Generic Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Tile :: Type -> Type #

Methods

from :: Tile -> Rep Tile x #

to :: Rep Tile x -> Tile #

Hashable Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Tile -> Int #

hash :: Tile -> Int #

WithDefaultSvg Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Tile Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Tile = D1 (MetaData "Tile" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Tile" PrefixI True) (S1 (MetaSel (Just "_tileDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_tileFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_tileIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)))))

data Offset Source #

Instances
Eq Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Show Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Hashable Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Offset -> Int #

hash :: Offset -> Int #

WithDefaultSvg Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Offset Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Offset = D1 (MetaData "Offset" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Offset" PrefixI True) ((S1 (MetaSel (Just "_offsetDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_offsetFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes)) :*: (S1 (MetaSel (Just "_offsetIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)) :*: (S1 (MetaSel (Just "_offsetDX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number) :*: S1 (MetaSel (Just "_offsetDY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number)))))

data MergeNode Source #

Instances
Eq MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep MergeNode :: Type -> Type #

Hashable MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep MergeNode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep MergeNode = D1 (MetaData "MergeNode" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "MergeNode" PrefixI True) (S1 (MetaSel (Just "_mergeNodeDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_mergeNodeIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource))))

data Merge Source #

Instances
Eq Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Merge -> Merge -> Bool #

(/=) :: Merge -> Merge -> Bool #

Show Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Merge -> ShowS #

show :: Merge -> String #

showList :: [Merge] -> ShowS #

Generic Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Merge :: Type -> Type #

Methods

from :: Merge -> Rep Merge x #

to :: Rep Merge x -> Merge #

Hashable Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Merge -> Int #

hash :: Merge -> Int #

WithDefaultSvg Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Merge Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Merge = D1 (MetaData "Merge" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Merge" PrefixI True) (S1 (MetaSel (Just "_mergeDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_mergeFilterAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_mergeChildren") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [FilterElement]))))

data ImageF Source #

Instances
Eq ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: ImageF -> ImageF -> Bool #

(/=) :: ImageF -> ImageF -> Bool #

Show ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ImageF :: Type -> Type #

Methods

from :: ImageF -> Rep ImageF x #

to :: Rep ImageF x -> ImageF #

Hashable ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> ImageF -> Int #

hash :: ImageF -> Int #

WithDefaultSvg ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep ImageF Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ImageF = D1 (MetaData "ImageF" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "ImageF" PrefixI True) ((S1 (MetaSel (Just "_imageFDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_imageFFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes)) :*: (S1 (MetaSel (Just "_imageFHref") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String) :*: S1 (MetaSel (Just "_imageFAspectRatio") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PreserveAspectRatio))))

data ComponentTransfer Source #

Instances
Eq ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ComponentTransfer :: Type -> Type #

Hashable ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' ComponentTransfer DrawAttributes Source #

attrClass :: Lens' ComponentTransfer [Text] Source #

attrId :: Lens' ComponentTransfer (Maybe String) Source #

clipPathRef :: Lens' ComponentTransfer (Last ElementRef) Source #

clipRule :: Lens' ComponentTransfer (Last FillRule) Source #

fillColor :: Lens' ComponentTransfer (Last Texture) Source #

fillOpacity :: Lens' ComponentTransfer (Maybe Float) Source #

fillRule :: Lens' ComponentTransfer (Last FillRule) Source #

filterRef :: Lens' ComponentTransfer (Last ElementRef) Source #

fontFamily :: Lens' ComponentTransfer (Last [String]) Source #

fontSize :: Lens' ComponentTransfer (Last Number) Source #

fontStyle :: Lens' ComponentTransfer (Last FontStyle) Source #

groupOpacity :: Lens' ComponentTransfer (Maybe Float) Source #

markerEnd :: Lens' ComponentTransfer (Last ElementRef) Source #

markerMid :: Lens' ComponentTransfer (Last ElementRef) Source #

markerStart :: Lens' ComponentTransfer (Last ElementRef) Source #

maskRef :: Lens' ComponentTransfer (Last ElementRef) Source #

strokeColor :: Lens' ComponentTransfer (Last Texture) Source #

strokeDashArray :: Lens' ComponentTransfer (Last [Number]) Source #

strokeLineCap :: Lens' ComponentTransfer (Last Cap) Source #

strokeLineJoin :: Lens' ComponentTransfer (Last LineJoin) Source #

strokeMiterLimit :: Lens' ComponentTransfer (Last Double) Source #

strokeOffset :: Lens' ComponentTransfer (Last Number) Source #

strokeOpacity :: Lens' ComponentTransfer (Maybe Float) Source #

strokeWidth :: Lens' ComponentTransfer (Last Number) Source #

textAnchor :: Lens' ComponentTransfer (Last TextAnchor) Source #

transform :: Lens' ComponentTransfer (Maybe [Transformation]) Source #

HasFilterAttributes ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep ComponentTransfer Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ComponentTransfer = D1 (MetaData "ComponentTransfer" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "ComponentTransfer" PrefixI True) ((S1 (MetaSel (Just "_compTransferDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_compTransferFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes)) :*: (S1 (MetaSel (Just "_compTransferChildren") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [FilterElement]) :*: S1 (MetaSel (Just "_compTransferIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)))))

data FuncA Source #

Instances
Eq FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: FuncA -> FuncA -> Bool #

(/=) :: FuncA -> FuncA -> Bool #

Show FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> FuncA -> ShowS #

show :: FuncA -> String #

showList :: [FuncA] -> ShowS #

Generic FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FuncA :: Type -> Type #

Methods

from :: FuncA -> Rep FuncA x #

to :: Rep FuncA x -> FuncA #

Hashable FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> FuncA -> Int #

hash :: FuncA -> Int #

WithDefaultSvg FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep FuncA Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data FuncType Source #

Instances
Eq FuncType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show FuncType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic FuncType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FuncType :: Type -> Type #

Methods

from :: FuncType -> Rep FuncType x #

to :: Rep FuncType x -> FuncType #

Hashable FuncType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> FuncType -> Int #

hash :: FuncType -> Int #

type Rep FuncType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep FuncType = D1 (MetaData "FuncType" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((C1 (MetaCons "FIdentity" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FTable" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FDiscrete" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FLinear" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FGamma" PrefixI False) (U1 :: Type -> Type))))

data FuncR Source #

Instances
Eq FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: FuncR -> FuncR -> Bool #

(/=) :: FuncR -> FuncR -> Bool #

Show FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> FuncR -> ShowS #

show :: FuncR -> String #

showList :: [FuncR] -> ShowS #

Generic FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FuncR :: Type -> Type #

Methods

from :: FuncR -> Rep FuncR x #

to :: Rep FuncR x -> FuncR #

Hashable FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> FuncR -> Int #

hash :: FuncR -> Int #

WithDefaultSvg FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep FuncR Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data FuncG Source #

Instances
Eq FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: FuncG -> FuncG -> Bool #

(/=) :: FuncG -> FuncG -> Bool #

Show FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> FuncG -> ShowS #

show :: FuncG -> String #

showList :: [FuncG] -> ShowS #

Generic FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FuncG :: Type -> Type #

Methods

from :: FuncG -> Rep FuncG x #

to :: Rep FuncG x -> FuncG #

Hashable FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> FuncG -> Int #

hash :: FuncG -> Int #

WithDefaultSvg FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep FuncG Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data FuncB Source #

Instances
Eq FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: FuncB -> FuncB -> Bool #

(/=) :: FuncB -> FuncB -> Bool #

Show FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> FuncB -> ShowS #

show :: FuncB -> String #

showList :: [FuncB] -> ShowS #

Generic FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep FuncB :: Type -> Type #

Methods

from :: FuncB -> Rep FuncB x #

to :: Rep FuncB x -> FuncB #

Hashable FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> FuncB -> Int #

hash :: FuncB -> Int #

WithDefaultSvg FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep FuncB Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data ColorMatrixType Source #

Instances
Eq ColorMatrixType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show ColorMatrixType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ColorMatrixType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ColorMatrixType :: Type -> Type #

Hashable ColorMatrixType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep ColorMatrixType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ColorMatrixType = D1 (MetaData "ColorMatrixType" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((C1 (MetaCons "Matrix" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Saturate" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "HueRotate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LuminanceToAlpha" PrefixI False) (U1 :: Type -> Type)))

data ColorMatrix Source #

Instances
Eq ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ColorMatrix :: Type -> Type #

Hashable ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' ColorMatrix DrawAttributes Source #

attrClass :: Lens' ColorMatrix [Text] Source #

attrId :: Lens' ColorMatrix (Maybe String) Source #

clipPathRef :: Lens' ColorMatrix (Last ElementRef) Source #

clipRule :: Lens' ColorMatrix (Last FillRule) Source #

fillColor :: Lens' ColorMatrix (Last Texture) Source #

fillOpacity :: Lens' ColorMatrix (Maybe Float) Source #

fillRule :: Lens' ColorMatrix (Last FillRule) Source #

filterRef :: Lens' ColorMatrix (Last ElementRef) Source #

fontFamily :: Lens' ColorMatrix (Last [String]) Source #

fontSize :: Lens' ColorMatrix (Last Number) Source #

fontStyle :: Lens' ColorMatrix (Last FontStyle) Source #

groupOpacity :: Lens' ColorMatrix (Maybe Float) Source #

markerEnd :: Lens' ColorMatrix (Last ElementRef) Source #

markerMid :: Lens' ColorMatrix (Last ElementRef) Source #

markerStart :: Lens' ColorMatrix (Last ElementRef) Source #

maskRef :: Lens' ColorMatrix (Last ElementRef) Source #

strokeColor :: Lens' ColorMatrix (Last Texture) Source #

strokeDashArray :: Lens' ColorMatrix (Last [Number]) Source #

strokeLineCap :: Lens' ColorMatrix (Last Cap) Source #

strokeLineJoin :: Lens' ColorMatrix (Last LineJoin) Source #

strokeMiterLimit :: Lens' ColorMatrix (Last Double) Source #

strokeOffset :: Lens' ColorMatrix (Last Number) Source #

strokeOpacity :: Lens' ColorMatrix (Maybe Float) Source #

strokeWidth :: Lens' ColorMatrix (Last Number) Source #

textAnchor :: Lens' ColorMatrix (Last TextAnchor) Source #

transform :: Lens' ColorMatrix (Maybe [Transformation]) Source #

HasFilterAttributes ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep ColorMatrix Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ColorMatrix = D1 (MetaData "ColorMatrix" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "ColorMatrix" PrefixI True) ((S1 (MetaSel (Just "_colorMatrixDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_colorMatrixFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes)) :*: (S1 (MetaSel (Just "_colorMatrixIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)) :*: (S1 (MetaSel (Just "_colorMatrixType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ColorMatrixType) :*: S1 (MetaSel (Just "_colorMatrixValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))))

data Composite Source #

Instances
Eq Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Composite :: Type -> Type #

Hashable Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Composite Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data CompositeOperator Source #

Instances
Eq CompositeOperator Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show CompositeOperator Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic CompositeOperator Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep CompositeOperator :: Type -> Type #

Hashable CompositeOperator Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep CompositeOperator Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep CompositeOperator = D1 (MetaData "CompositeOperator" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((C1 (MetaCons "CompositeOver" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CompositeIn" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CompositeOut" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "CompositeAtop" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CompositeXor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CompositeArithmetic" PrefixI False) (U1 :: Type -> Type))))

data EdgeMode Source #

Instances
Eq EdgeMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show EdgeMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic EdgeMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep EdgeMode :: Type -> Type #

Methods

from :: EdgeMode -> Rep EdgeMode x #

to :: Rep EdgeMode x -> EdgeMode #

Hashable EdgeMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> EdgeMode -> Int #

hash :: EdgeMode -> Int #

type Rep EdgeMode Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep EdgeMode = D1 (MetaData "EdgeMode" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "EdgeDuplicate" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EdgeWrap" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EdgeNone" PrefixI False) (U1 :: Type -> Type)))

data GaussianBlur Source #

Instances
Eq GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep GaussianBlur :: Type -> Type #

Hashable GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' GaussianBlur DrawAttributes Source #

attrClass :: Lens' GaussianBlur [Text] Source #

attrId :: Lens' GaussianBlur (Maybe String) Source #

clipPathRef :: Lens' GaussianBlur (Last ElementRef) Source #

clipRule :: Lens' GaussianBlur (Last FillRule) Source #

fillColor :: Lens' GaussianBlur (Last Texture) Source #

fillOpacity :: Lens' GaussianBlur (Maybe Float) Source #

fillRule :: Lens' GaussianBlur (Last FillRule) Source #

filterRef :: Lens' GaussianBlur (Last ElementRef) Source #

fontFamily :: Lens' GaussianBlur (Last [String]) Source #

fontSize :: Lens' GaussianBlur (Last Number) Source #

fontStyle :: Lens' GaussianBlur (Last FontStyle) Source #

groupOpacity :: Lens' GaussianBlur (Maybe Float) Source #

markerEnd :: Lens' GaussianBlur (Last ElementRef) Source #

markerMid :: Lens' GaussianBlur (Last ElementRef) Source #

markerStart :: Lens' GaussianBlur (Last ElementRef) Source #

maskRef :: Lens' GaussianBlur (Last ElementRef) Source #

strokeColor :: Lens' GaussianBlur (Last Texture) Source #

strokeDashArray :: Lens' GaussianBlur (Last [Number]) Source #

strokeLineCap :: Lens' GaussianBlur (Last Cap) Source #

strokeLineJoin :: Lens' GaussianBlur (Last LineJoin) Source #

strokeMiterLimit :: Lens' GaussianBlur (Last Double) Source #

strokeOffset :: Lens' GaussianBlur (Last Number) Source #

strokeOpacity :: Lens' GaussianBlur (Maybe Float) Source #

strokeWidth :: Lens' GaussianBlur (Last Number) Source #

textAnchor :: Lens' GaussianBlur (Last TextAnchor) Source #

transform :: Lens' GaussianBlur (Maybe [Transformation]) Source #

HasFilterAttributes GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep GaussianBlur Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep GaussianBlur = D1 (MetaData "GaussianBlur" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "GaussianBlur" PrefixI True) ((S1 (MetaSel (Just "_gaussianBlurDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_gaussianBlurFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_gaussianBlurIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last FilterSource)))) :*: (S1 (MetaSel (Just "_gaussianBlurStdDeviationX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Number) :*: (S1 (MetaSel (Just "_gaussianBlurStdDeviationY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Number)) :*: S1 (MetaSel (Just "_gaussianBlurEdgeMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EdgeMode)))))

data Turbulence Source #

Instances
Eq Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Turbulence :: Type -> Type #

Hashable Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Turbulence Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Turbulence = D1 (MetaData "Turbulence" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Turbulence" PrefixI True) ((S1 (MetaSel (Just "_turbulenceDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_turbulenceFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_turbulenceBaseFrequency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Double, Last Double)))) :*: ((S1 (MetaSel (Just "_turbulenceNumOctaves") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "_turbulenceSeed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :*: (S1 (MetaSel (Just "_turbulenceStitchTiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StitchTiles) :*: S1 (MetaSel (Just "_turbulenceType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TurbulenceType)))))

data TurbulenceType Source #

Instances
Eq TurbulenceType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TurbulenceType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TurbulenceType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TurbulenceType :: Type -> Type #

Hashable TurbulenceType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep TurbulenceType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TurbulenceType = D1 (MetaData "TurbulenceType" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "FractalNoiseType" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TurbulenceType" PrefixI False) (U1 :: Type -> Type))

data StitchTiles Source #

Constructors

NoStitch 
Stitch 
Instances
Eq StitchTiles Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show StitchTiles Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic StitchTiles Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep StitchTiles :: Type -> Type #

Hashable StitchTiles Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep StitchTiles Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep StitchTiles = D1 (MetaData "StitchTiles" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "NoStitch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Stitch" PrefixI False) (U1 :: Type -> Type))

data DisplacementMap Source #

Instances
Eq DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep DisplacementMap :: Type -> Type #

Hashable DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' DisplacementMap DrawAttributes Source #

attrClass :: Lens' DisplacementMap [Text] Source #

attrId :: Lens' DisplacementMap (Maybe String) Source #

clipPathRef :: Lens' DisplacementMap (Last ElementRef) Source #

clipRule :: Lens' DisplacementMap (Last FillRule) Source #

fillColor :: Lens' DisplacementMap (Last Texture) Source #

fillOpacity :: Lens' DisplacementMap (Maybe Float) Source #

fillRule :: Lens' DisplacementMap (Last FillRule) Source #

filterRef :: Lens' DisplacementMap (Last ElementRef) Source #

fontFamily :: Lens' DisplacementMap (Last [String]) Source #

fontSize :: Lens' DisplacementMap (Last Number) Source #

fontStyle :: Lens' DisplacementMap (Last FontStyle) Source #

groupOpacity :: Lens' DisplacementMap (Maybe Float) Source #

markerEnd :: Lens' DisplacementMap (Last ElementRef) Source #

markerMid :: Lens' DisplacementMap (Last ElementRef) Source #

markerStart :: Lens' DisplacementMap (Last ElementRef) Source #

maskRef :: Lens' DisplacementMap (Last ElementRef) Source #

strokeColor :: Lens' DisplacementMap (Last Texture) Source #

strokeDashArray :: Lens' DisplacementMap (Last [Number]) Source #

strokeLineCap :: Lens' DisplacementMap (Last Cap) Source #

strokeLineJoin :: Lens' DisplacementMap (Last LineJoin) Source #

strokeMiterLimit :: Lens' DisplacementMap (Last Double) Source #

strokeOffset :: Lens' DisplacementMap (Last Number) Source #

strokeOpacity :: Lens' DisplacementMap (Maybe Float) Source #

strokeWidth :: Lens' DisplacementMap (Last Number) Source #

textAnchor :: Lens' DisplacementMap (Last TextAnchor) Source #

transform :: Lens' DisplacementMap (Maybe [Transformation]) Source #

HasFilterAttributes DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep DisplacementMap Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep DisplacementMap = D1 (MetaData "DisplacementMap" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "DisplacementMap" PrefixI True) ((S1 (MetaSel (Just "_displacementMapDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_displacementMapFilterAttr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_displacementMapIn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)))) :*: ((S1 (MetaSel (Just "_displacementMapIn2") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last FilterSource)) :*: S1 (MetaSel (Just "_displacementMapScale") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Last Double))) :*: (S1 (MetaSel (Just "_displacementMapXChannelSelector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChannelSelector) :*: S1 (MetaSel (Just "_displacementMapYChannelSelector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChannelSelector)))))

data ChannelSelector Source #

Instances
Eq ChannelSelector Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show ChannelSelector Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ChannelSelector Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ChannelSelector :: Type -> Type #

Hashable ChannelSelector Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep ChannelSelector Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ChannelSelector = D1 (MetaData "ChannelSelector" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) ((C1 (MetaCons "ChannelR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ChannelG" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ChannelB" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ChannelA" PrefixI False) (U1 :: Type -> Type)))

SVG drawing primitives

Rectangle

data Rectangle Source #

Define a rectangle. Correspond to `<rectangle>` svg tag.

Constructors

Rectangle 

Fields

Instances
Eq Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Rectangle :: Type -> Type #

Hashable Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Rectangle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Rectangle = D1 (MetaData "Rectangle" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Rectangle" PrefixI True) ((S1 (MetaSel (Just "_rectangleDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_rectUpperLeftCorner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Point)) :*: (S1 (MetaSel (Just "_rectWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Number)) :*: (S1 (MetaSel (Just "_rectHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Number)) :*: S1 (MetaSel (Just "_rectCornerRadius") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Number, Maybe Number))))))

Line

data Line Source #

Define a simple line. Correspond to the `<line>` tag.

Constructors

Line 

Fields

Instances
Eq Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Line -> Line -> Bool #

(/=) :: Line -> Line -> Bool #

Show Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Generic Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Line :: Type -> Type #

Methods

from :: Line -> Rep Line x #

to :: Rep Line x -> Line #

Hashable Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Line -> Int #

hash :: Line -> Int #

WithDefaultSvg Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Line Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Line = D1 (MetaData "Line" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Line" PrefixI True) (S1 (MetaSel (Just "_lineDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_linePoint1") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Point) :*: S1 (MetaSel (Just "_linePoint2") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Point))))

pattern LineTree :: Line -> Tree Source #

Polygon

data Polygon Source #

Primitive decriving polygon composed of segements. Correspond to the `<polygon>` tag

Constructors

Polygon 

Fields

Instances
Eq Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Polygon -> Polygon -> Bool #

(/=) :: Polygon -> Polygon -> Bool #

Show Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Polygon :: Type -> Type #

Methods

from :: Polygon -> Rep Polygon x #

to :: Rep Polygon x -> Polygon #

Hashable Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Polygon -> Int #

hash :: Polygon -> Int #

WithDefaultSvg Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Polygon Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Polygon = D1 (MetaData "Polygon" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Polygon" PrefixI True) (S1 (MetaSel (Just "_polygonDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_polygonPoints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RPoint])))

Polyline

data PolyLine Source #

This primitive describe an unclosed suite of segments. Correspond to the `<polyline>` tag.

Constructors

PolyLine 

Fields

Instances
Eq PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep PolyLine :: Type -> Type #

Methods

from :: PolyLine -> Rep PolyLine x #

to :: Rep PolyLine x -> PolyLine #

Hashable PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> PolyLine -> Int #

hash :: PolyLine -> Int #

WithDefaultSvg PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep PolyLine Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep PolyLine = D1 (MetaData "PolyLine" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "PolyLine" PrefixI True) (S1 (MetaSel (Just "_polyLineDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_polyLinePoints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RPoint])))

Path

data Path Source #

Type mapping the `<path>` svg tag.

Constructors

Path 

Fields

Instances
Eq Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Show Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Generic Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Path :: Type -> Type #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

Hashable Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Path -> Int #

hash :: Path -> Int #

WithDefaultSvg Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Path Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Path = D1 (MetaData "Path" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Path" PrefixI True) (S1 (MetaSel (Just "_pathDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_pathDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PathCommand])))

pattern PathTree :: Path -> Tree Source #

Circle

data Circle Source #

Define a `<circle>`.

Constructors

Circle 

Fields

Instances
Eq Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Circle -> Circle -> Bool #

(/=) :: Circle -> Circle -> Bool #

Show Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Circle :: Type -> Type #

Methods

from :: Circle -> Rep Circle x #

to :: Rep Circle x -> Circle #

Hashable Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Circle -> Int #

hash :: Circle -> Int #

WithDefaultSvg Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Circle Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Circle = D1 (MetaData "Circle" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Circle" PrefixI True) (S1 (MetaSel (Just "_circleDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_circleCenter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Point) :*: S1 (MetaSel (Just "_circleRadius") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number))))

pattern CircleTree :: Circle -> Tree Source #

Ellipse

data Ellipse Source #

Define an `<ellipse>`

Constructors

Ellipse 

Fields

Instances
Eq Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Ellipse -> Ellipse -> Bool #

(/=) :: Ellipse -> Ellipse -> Bool #

Show Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Ellipse :: Type -> Type #

Methods

from :: Ellipse -> Rep Ellipse x #

to :: Rep Ellipse x -> Ellipse #

Hashable Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Ellipse -> Int #

hash :: Ellipse -> Int #

WithDefaultSvg Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Ellipse Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Ellipse = D1 (MetaData "Ellipse" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Ellipse" PrefixI True) ((S1 (MetaSel (Just "_ellipseDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_ellipseCenter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Point)) :*: (S1 (MetaSel (Just "_ellipseXRadius") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number) :*: S1 (MetaSel (Just "_ellipseYRadius") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number))))

Mesh (gradient mesh)

data GradientPathCommand Source #

Description of path used in meshgradient tag

Constructors

GLine !Origin !(Maybe RPoint)

Line to, L or l Svg path command.

GCurve !Origin !RPoint !RPoint !(Maybe RPoint)

Cubic bezier, C or c command

GClose

Z command

Instances
Eq GradientPathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show GradientPathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic GradientPathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep GradientPathCommand :: Type -> Type #

Hashable GradientPathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep GradientPathCommand Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

data MeshGradientType Source #

Instances
Eq MeshGradientType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Show MeshGradientType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic MeshGradientType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep MeshGradientType :: Type -> Type #

Hashable MeshGradientType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep MeshGradientType Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep MeshGradientType = D1 (MetaData "MeshGradientType" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "GradientBilinear" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GradientBicubic" PrefixI False) (U1 :: Type -> Type))

data MeshGradient Source #

Define a `<meshgradient>` tag.

Constructors

MeshGradient 

Fields

Instances
Eq MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep MeshGradient :: Type -> Type #

Hashable MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' MeshGradient DrawAttributes Source #

attrClass :: Lens' MeshGradient [Text] Source #

attrId :: Lens' MeshGradient (Maybe String) Source #

clipPathRef :: Lens' MeshGradient (Last ElementRef) Source #

clipRule :: Lens' MeshGradient (Last FillRule) Source #

fillColor :: Lens' MeshGradient (Last Texture) Source #

fillOpacity :: Lens' MeshGradient (Maybe Float) Source #

fillRule :: Lens' MeshGradient (Last FillRule) Source #

filterRef :: Lens' MeshGradient (Last ElementRef) Source #

fontFamily :: Lens' MeshGradient (Last [String]) Source #

fontSize :: Lens' MeshGradient (Last Number) Source #

fontStyle :: Lens' MeshGradient (Last FontStyle) Source #

groupOpacity :: Lens' MeshGradient (Maybe Float) Source #

markerEnd :: Lens' MeshGradient (Last ElementRef) Source #

markerMid :: Lens' MeshGradient (Last ElementRef) Source #

markerStart :: Lens' MeshGradient (Last ElementRef) Source #

maskRef :: Lens' MeshGradient (Last ElementRef) Source #

strokeColor :: Lens' MeshGradient (Last Texture) Source #

strokeDashArray :: Lens' MeshGradient (Last [Number]) Source #

strokeLineCap :: Lens' MeshGradient (Last Cap) Source #

strokeLineJoin :: Lens' MeshGradient (Last LineJoin) Source #

strokeMiterLimit :: Lens' MeshGradient (Last Double) Source #

strokeOffset :: Lens' MeshGradient (Last Number) Source #

strokeOpacity :: Lens' MeshGradient (Maybe Float) Source #

strokeWidth :: Lens' MeshGradient (Last Number) Source #

textAnchor :: Lens' MeshGradient (Last TextAnchor) Source #

transform :: Lens' MeshGradient (Maybe [Transformation]) Source #

type Rep MeshGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep MeshGradient = D1 (MetaData "MeshGradient" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "MeshGradient" PrefixI True) ((S1 (MetaSel (Just "_meshGradientDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_meshGradientX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number) :*: S1 (MetaSel (Just "_meshGradientY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number))) :*: ((S1 (MetaSel (Just "_meshGradientType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MeshGradientType) :*: S1 (MetaSel (Just "_meshGradientUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CoordinateUnits)) :*: (S1 (MetaSel (Just "_meshGradientTransform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Transformation]) :*: S1 (MetaSel (Just "_meshGradientRows") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [MeshGradientRow])))))

data MeshGradientRow Source #

Define a `<meshrow>` tag.

Constructors

MeshGradientRow 

Fields

Instances
Eq MeshGradientRow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show MeshGradientRow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic MeshGradientRow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep MeshGradientRow :: Type -> Type #

Hashable MeshGradientRow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg MeshGradientRow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep MeshGradientRow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep MeshGradientRow = D1 (MetaData "MeshGradientRow" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "MeshGradientRow" PrefixI True) (S1 (MetaSel (Just "_meshGradientRowPatches") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [MeshGradientPatch])))

data MeshGradientPatch Source #

Define `<meshpatch>` SVG tag

Constructors

MeshGradientPatch 

Fields

Image

data Image Source #

Define an `<image>` tag.

Constructors

Image 

Fields

Instances
Eq Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Show Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Hashable Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Image -> Int #

hash :: Image -> Int #

WithDefaultSvg Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Image Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

pattern ImageTree :: Image -> Tree Source #

Use

data Use Source #

Define an `<use>` for a named content. Every named content can be reused in the document using this element.

Constructors

Use 

Fields

Instances
Eq Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Use -> Use -> Bool #

(/=) :: Use -> Use -> Bool #

Show Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Use -> ShowS #

show :: Use -> String #

showList :: [Use] -> ShowS #

Generic Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Use :: Type -> Type #

Methods

from :: Use -> Rep Use x #

to :: Rep Use x -> Use #

Hashable Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Use -> Int #

hash :: Use -> Int #

WithDefaultSvg Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Use Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

pattern UseTree :: Use -> Maybe Tree -> Tree Source #

Grouping primitives

Group

data Group Source #

Define a SVG group, corresponding `<g>` tag.

Constructors

Group 

Fields

Instances
Eq Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Group -> Group -> Bool #

(/=) :: Group -> Group -> Bool #

Show Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

Generic Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Group :: Type -> Type #

Methods

from :: Group -> Rep Group x #

to :: Rep Group x -> Group #

Hashable Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Group -> Int #

hash :: Group -> Int #

WithDefaultSvg Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Group Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Group = D1 (MetaData "Group" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Group" PrefixI True) ((S1 (MetaSel (Just "_groupDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_groupChildren") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Tree])) :*: (S1 (MetaSel (Just "_groupViewBox") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Double, Double, Double, Double))) :*: S1 (MetaSel (Just "_groupAspectRatio") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PreserveAspectRatio))))

pattern GroupTree :: Group -> Tree Source #

Symbol

pattern SymbolTree :: Group -> Tree Source #

Definitions

Filter

data Filter Source #

Define the `<filter>` tag.

Instances
Eq Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

Show Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Filter :: Type -> Type #

Methods

from :: Filter -> Rep Filter x #

to :: Rep Filter x -> Filter #

Hashable Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Filter -> Int #

hash :: Filter -> Int #

WithDefaultSvg Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

HasFilterAttributes Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Filter Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Filter = D1 (MetaData "Filter" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Filter" PrefixI True) (S1 (MetaSel (Just "_filterDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_filterSelfAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilterAttributes) :*: S1 (MetaSel (Just "_filterChildren") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [FilterElement]))))

pattern FilterTree :: Filter -> Tree Source #

Text related types

Text

data Text Source #

Define the global `<text>` SVG tag.

Constructors

Text 

Fields

Instances
Eq Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Text -> Text -> Bool #

(/=) :: Text -> Text -> Bool #

Show Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Text -> ShowS #

show :: Text -> String #

showList :: [Text] -> ShowS #

Generic Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Text :: Type -> Type #

Methods

from :: Text -> Rep Text x #

to :: Rep Text x -> Text #

Hashable Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

WithDefaultSvg Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Text Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Text = D1 (MetaData "Text" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Text" PrefixI True) (S1 (MetaSel (Just "_textAdjust") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextAdjust) :*: S1 (MetaSel (Just "_textRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextSpan)))

data TextAnchor Source #

Tell where to anchor the text, where the position given is realative to the text.

Constructors

TextAnchorStart

The text with left aligned, or start at the postion If the point is the * then the text will be printed this way:

 *THE_TEXT_TO_PRINT

Equivalent to the start value.

TextAnchorMiddle

The text is middle aligned, so the text will be at the left and right of the position:

  THE_TEXT*TO_PRINT

Equivalent to the middle value.

TextAnchorEnd

The text is right aligned.

  THE_TEXT_TO_PRINT*

Equivalent to the end value.

Instances
Eq TextAnchor Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextAnchor Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextAnchor Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextAnchor :: Type -> Type #

Hashable TextAnchor Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep TextAnchor Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextAnchor = D1 (MetaData "TextAnchor" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "TextAnchorStart" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TextAnchorMiddle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TextAnchorEnd" PrefixI False) (U1 :: Type -> Type)))

textAt :: Point -> Text -> Text Source #

Little helper to create a SVG text at a given baseline position.

Text path

data TextPath Source #

Describe the `<textpath>` SVG tag.

Constructors

TextPath 

Fields

Instances
Eq TextPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextPath :: Type -> Type #

Methods

from :: TextPath -> Rep TextPath x #

to :: Rep TextPath x -> TextPath #

Hashable TextPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> TextPath -> Int #

hash :: TextPath -> Int #

WithDefaultSvg TextPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextPath = D1 (MetaData "TextPath" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "TextPath" PrefixI True) ((S1 (MetaSel (Just "_textPathStartOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Number) :*: S1 (MetaSel (Just "_textPathName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) :*: (S1 (MetaSel (Just "_textPathMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextPathMethod) :*: S1 (MetaSel (Just "_textPathSpacing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextPathSpacing))))

data TextPathSpacing Source #

Describe the content of the spacing text path attribute.

Constructors

TextPathSpacingExact

Map to the exact value.

TextPathSpacingAuto

Map to the auto value.

Instances
Eq TextPathSpacing Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextPathSpacing Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextPathSpacing Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextPathSpacing :: Type -> Type #

Hashable TextPathSpacing Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep TextPathSpacing Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextPathSpacing = D1 (MetaData "TextPathSpacing" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "TextPathSpacingExact" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TextPathSpacingAuto" PrefixI False) (U1 :: Type -> Type))

data TextPathMethod Source #

Describe the content of the method attribute on text path.

Constructors

TextPathAlign

Map to the align value.

TextPathStretch

Map to the stretch value.

Instances
Eq TextPathMethod Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextPathMethod Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextPathMethod Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextPathMethod :: Type -> Type #

Hashable TextPathMethod Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep TextPathMethod Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextPathMethod = D1 (MetaData "TextPathMethod" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "TextPathAlign" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TextPathStretch" PrefixI False) (U1 :: Type -> Type))

Text span.

data TextSpanContent Source #

Define the content of a `<tspan>` tag.

Constructors

SpanText !Text

Raw text

SpanTextRef !String

Equivalent to a `<tref>`

SpanSub !TextSpan

Define a `<tspan>`

Instances
Eq TextSpanContent Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextSpanContent Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextSpanContent Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextSpanContent :: Type -> Type #

Hashable TextSpanContent Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep TextSpanContent Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextSpanContent = D1 (MetaData "TextSpanContent" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "SpanText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: (C1 (MetaCons "SpanTextRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) :+: C1 (MetaCons "SpanSub" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextSpan))))

data TextSpan Source #

Define a `<tspan>` tag.

Constructors

TextSpan 

Fields

Instances
Eq TextSpan Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextSpan Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextSpan Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextSpan :: Type -> Type #

Methods

from :: TextSpan -> Rep TextSpan x #

to :: Rep TextSpan x -> TextSpan #

Hashable TextSpan Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> TextSpan -> Int #

hash :: TextSpan -> Int #

WithDefaultSvg TextSpan Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextSpan Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextSpan = D1 (MetaData "TextSpan" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "TextSpan" PrefixI True) (S1 (MetaSel (Just "_spanInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextInfo) :*: (S1 (MetaSel (Just "_spanDrawAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_spanContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [TextSpanContent]))))

data TextInfo Source #

Define position information associated to `<text>` or `<tspan>` svg tag.

Constructors

TextInfo 

Fields

Instances
Eq TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextInfo :: Type -> Type #

Methods

from :: TextInfo -> Rep TextInfo x #

to :: Rep TextInfo x -> TextInfo #

Semigroup TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Monoid TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Hashable TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> TextInfo -> Int #

hash :: TextInfo -> Int #

WithDefaultSvg TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextInfo Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextInfo = D1 (MetaData "TextInfo" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "TextInfo" PrefixI True) ((S1 (MetaSel (Just "_textInfoX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Number]) :*: (S1 (MetaSel (Just "_textInfoY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Number]) :*: S1 (MetaSel (Just "_textInfoDX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Number]))) :*: (S1 (MetaSel (Just "_textInfoDY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Number]) :*: (S1 (MetaSel (Just "_textInfoRotate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Double]) :*: S1 (MetaSel (Just "_textInfoLength") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Number))))))

data TextAdjust Source #

Define the possible values of the lengthAdjust attribute.

Constructors

TextAdjustSpacing

Value spacing

TextAdjustSpacingAndGlyphs

Value spacingAndGlyphs

Instances
Eq TextAdjust Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show TextAdjust Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic TextAdjust Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep TextAdjust :: Type -> Type #

Hashable TextAdjust Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep TextAdjust Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep TextAdjust = D1 (MetaData "TextAdjust" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "TextAdjustSpacing" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TextAdjustSpacingAndGlyphs" PrefixI False) (U1 :: Type -> Type))

Marker definition

data Marker Source #

Define the `<marker>` tag.

Constructors

Marker 

Fields

Instances
Eq Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Marker -> Marker -> Bool #

(/=) :: Marker -> Marker -> Bool #

Show Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Marker :: Type -> Type #

Methods

from :: Marker -> Rep Marker x #

to :: Rep Marker x -> Marker #

Hashable Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Marker -> Int #

hash :: Marker -> Int #

WithDefaultSvg Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Marker Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

pattern MarkerTree :: Marker -> Tree Source #

data Overflow Source #

Define the content of the markerUnits attribute on the Marker.

Constructors

OverflowVisible

Value visible

OverflowHidden

Value hidden

Instances
Eq Overflow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show Overflow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Overflow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Overflow :: Type -> Type #

Methods

from :: Overflow -> Rep Overflow x #

to :: Rep Overflow x -> Overflow #

Hashable Overflow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Overflow -> Int #

hash :: Overflow -> Int #

type Rep Overflow Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep Overflow = D1 (MetaData "Overflow" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "OverflowVisible" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OverflowHidden" PrefixI False) (U1 :: Type -> Type))

data MarkerOrientation Source #

Define the orientation, associated to the orient attribute on the Marker

Constructors

OrientationAuto

Auto value

OrientationAngle Coord

Specific angle.

data MarkerUnit Source #

Define the content of the markerUnits attribute on the Marker.

Constructors

MarkerUnitStrokeWidth

Value strokeWidth

MarkerUnitUserSpaceOnUse

Value userSpaceOnUse

Instances
Eq MarkerUnit Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show MarkerUnit Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic MarkerUnit Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep MarkerUnit :: Type -> Type #

Hashable MarkerUnit Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep MarkerUnit Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep MarkerUnit = D1 (MetaData "MarkerUnit" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "MarkerUnitStrokeWidth" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MarkerUnitUserSpaceOnUse" PrefixI False) (U1 :: Type -> Type))

Gradient definition

data GradientStop Source #

Define a color stop for the gradients. Represent the `<stop>` SVG tag.

Constructors

GradientStop 

Fields

Instances
Eq GradientStop Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show GradientStop Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic GradientStop Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep GradientStop :: Type -> Type #

Hashable GradientStop Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg GradientStop Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep GradientStop Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep GradientStop = D1 (MetaData "GradientStop" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "GradientStop" PrefixI True) ((S1 (MetaSel (Just "_gradientOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Float) :*: S1 (MetaSel (Just "_gradientColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PixelRGBA8)) :*: (S1 (MetaSel (Just "_gradientPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GradientPathCommand)) :*: S1 (MetaSel (Just "_gradientOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Float)))))

Linear Gradient

data LinearGradient Source #

Define a `<linearGradient>` tag.

Constructors

LinearGradient 

Fields

Instances
Eq LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep LinearGradient :: Type -> Type #

Hashable LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' LinearGradient DrawAttributes Source #

attrClass :: Lens' LinearGradient [Text] Source #

attrId :: Lens' LinearGradient (Maybe String) Source #

clipPathRef :: Lens' LinearGradient (Last ElementRef) Source #

clipRule :: Lens' LinearGradient (Last FillRule) Source #

fillColor :: Lens' LinearGradient (Last Texture) Source #

fillOpacity :: Lens' LinearGradient (Maybe Float) Source #

fillRule :: Lens' LinearGradient (Last FillRule) Source #

filterRef :: Lens' LinearGradient (Last ElementRef) Source #

fontFamily :: Lens' LinearGradient (Last [String]) Source #

fontSize :: Lens' LinearGradient (Last Number) Source #

fontStyle :: Lens' LinearGradient (Last FontStyle) Source #

groupOpacity :: Lens' LinearGradient (Maybe Float) Source #

markerEnd :: Lens' LinearGradient (Last ElementRef) Source #

markerMid :: Lens' LinearGradient (Last ElementRef) Source #

markerStart :: Lens' LinearGradient (Last ElementRef) Source #

maskRef :: Lens' LinearGradient (Last ElementRef) Source #

strokeColor :: Lens' LinearGradient (Last Texture) Source #

strokeDashArray :: Lens' LinearGradient (Last [Number]) Source #

strokeLineCap :: Lens' LinearGradient (Last Cap) Source #

strokeLineJoin :: Lens' LinearGradient (Last LineJoin) Source #

strokeMiterLimit :: Lens' LinearGradient (Last Double) Source #

strokeOffset :: Lens' LinearGradient (Last Number) Source #

strokeOpacity :: Lens' LinearGradient (Maybe Float) Source #

strokeWidth :: Lens' LinearGradient (Last Number) Source #

textAnchor :: Lens' LinearGradient (Last TextAnchor) Source #

transform :: Lens' LinearGradient (Maybe [Transformation]) Source #

type Rep LinearGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep LinearGradient = D1 (MetaData "LinearGradient" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "LinearGradient" PrefixI True) ((S1 (MetaSel (Just "_linearGradientDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_linearGradientUnits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoordinateUnits) :*: S1 (MetaSel (Just "_linearGradientStart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Point))) :*: ((S1 (MetaSel (Just "_linearGradientStop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Point) :*: S1 (MetaSel (Just "_linearGradientSpread") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Spread)) :*: (S1 (MetaSel (Just "_linearGradientTransform") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Transformation]) :*: S1 (MetaSel (Just "_linearGradientStops") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [GradientStop])))))

Radial Gradient

data RadialGradient Source #

Define a `<radialGradient>` tag.

Constructors

RadialGradient 

Fields

Instances
Eq RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep RadialGradient :: Type -> Type #

Hashable RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

Methods

drawAttributes :: Lens' RadialGradient DrawAttributes Source #

attrClass :: Lens' RadialGradient [Text] Source #

attrId :: Lens' RadialGradient (Maybe String) Source #

clipPathRef :: Lens' RadialGradient (Last ElementRef) Source #

clipRule :: Lens' RadialGradient (Last FillRule) Source #

fillColor :: Lens' RadialGradient (Last Texture) Source #

fillOpacity :: Lens' RadialGradient (Maybe Float) Source #

fillRule :: Lens' RadialGradient (Last FillRule) Source #

filterRef :: Lens' RadialGradient (Last ElementRef) Source #

fontFamily :: Lens' RadialGradient (Last [String]) Source #

fontSize :: Lens' RadialGradient (Last Number) Source #

fontStyle :: Lens' RadialGradient (Last FontStyle) Source #

groupOpacity :: Lens' RadialGradient (Maybe Float) Source #

markerEnd :: Lens' RadialGradient (Last ElementRef) Source #

markerMid :: Lens' RadialGradient (Last ElementRef) Source #

markerStart :: Lens' RadialGradient (Last ElementRef) Source #

maskRef :: Lens' RadialGradient (Last ElementRef) Source #

strokeColor :: Lens' RadialGradient (Last Texture) Source #

strokeDashArray :: Lens' RadialGradient (Last [Number]) Source #

strokeLineCap :: Lens' RadialGradient (Last Cap) Source #

strokeLineJoin :: Lens' RadialGradient (Last LineJoin) Source #

strokeMiterLimit :: Lens' RadialGradient (Last Double) Source #

strokeOffset :: Lens' RadialGradient (Last Number) Source #

strokeOpacity :: Lens' RadialGradient (Maybe Float) Source #

strokeWidth :: Lens' RadialGradient (Last Number) Source #

textAnchor :: Lens' RadialGradient (Last TextAnchor) Source #

transform :: Lens' RadialGradient (Maybe [Transformation]) Source #

type Rep RadialGradient Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep RadialGradient = D1 (MetaData "RadialGradient" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "RadialGradient" PrefixI True) (((S1 (MetaSel (Just "_radialGradientDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: S1 (MetaSel (Just "_radialGradientUnits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoordinateUnits)) :*: (S1 (MetaSel (Just "_radialGradientCenter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Point) :*: S1 (MetaSel (Just "_radialGradientRadius") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Number))) :*: ((S1 (MetaSel (Just "_radialGradientFocusX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Number)) :*: S1 (MetaSel (Just "_radialGradientFocusY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Number))) :*: (S1 (MetaSel (Just "_radialGradientSpread") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Spread) :*: (S1 (MetaSel (Just "_radialGradientTransform") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Transformation]) :*: S1 (MetaSel (Just "_radialGradientStops") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [GradientStop]))))))

Pattern definition

data Pattern Source #

Define a `<pattern>` tag.

Constructors

Pattern 

Fields

Instances
Eq Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Pattern -> Pattern -> Bool #

(/=) :: Pattern -> Pattern -> Bool #

Show Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Pattern :: Type -> Type #

Methods

from :: Pattern -> Rep Pattern x #

to :: Rep Pattern x -> Pattern #

Hashable Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Pattern -> Int #

hash :: Pattern -> Int #

WithDefaultSvg Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Pattern Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Mask definition

data Mask Source #

Define a SVG `<mask>` tag.

Constructors

Mask 

Fields

Instances
Eq Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

(==) :: Mask -> Mask -> Bool #

(/=) :: Mask -> Mask -> Bool #

Show Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Methods

showsPrec :: Int -> Mask -> ShowS #

show :: Mask -> String #

showList :: [Mask] -> ShowS #

Generic Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep Mask :: Type -> Type #

Methods

from :: Mask -> Rep Mask x #

to :: Rep Mask x -> Mask #

Hashable Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> Mask -> Int #

hash :: Mask -> Int #

WithDefaultSvg Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep Mask Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

pattern MaskTree :: Mask -> Tree Source #

Clip path definition

data ClipPath Source #

Define a `<clipPath>` tag.

Constructors

ClipPath 

Fields

Instances
Eq ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep ClipPath :: Type -> Type #

Methods

from :: ClipPath -> Rep ClipPath x #

to :: Rep ClipPath x -> ClipPath #

Hashable ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

Methods

hashWithSalt :: Int -> ClipPath -> Int #

hash :: ClipPath -> Int #

WithDefaultSvg ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

HasDrawAttributes ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type Rep ClipPath Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep ClipPath = D1 (MetaData "ClipPath" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "ClipPath" PrefixI True) (S1 (MetaSel (Just "_clipPathDrawAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DrawAttributes) :*: (S1 (MetaSel (Just "_clipPathUnits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoordinateUnits) :*: S1 (MetaSel (Just "_clipPathContent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Tree]))))

Aspect Ratio description

data PreserveAspectRatio Source #

Describe the content of the preserveAspectRatio attribute.

Instances
Eq PreserveAspectRatio Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Show PreserveAspectRatio Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Generic PreserveAspectRatio Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

Associated Types

type Rep PreserveAspectRatio :: Type -> Type #

Hashable PreserveAspectRatio Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

WithDefaultSvg PreserveAspectRatio Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep PreserveAspectRatio Source # 
Instance details

Defined in Graphics.SvgTree.Types.Internal

type Rep PreserveAspectRatio = D1 (MetaData "PreserveAspectRatio" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "PreserveAspectRatio" PrefixI True) (S1 (MetaSel (Just "_aspectRatioDefer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: (S1 (MetaSel (Just "_aspectRatioAlign") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Alignment) :*: S1 (MetaSel (Just "_aspectRatioMeetSlice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MeetSlice)))))

data Alignment Source #

This type represent the align information of the preserveAspectRatio SVGattribute

Constructors

AlignNone

"none" value

AlignxMinYMin 
AlignxMidYMin

"xMidYMin" value

AlignxMaxYMin

"xMaxYMin" value

AlignxMinYMid

"xMinYMid" value

AlignxMidYMid

"xMidYMid" value

AlignxMaxYMid

"xMaxYMid" value

AlignxMinYMax

"xMinYMax" value

AlignxMidYMax

"xMidYMax" value

AlignxMaxYMax

"xMaxYMax" value

Instances
Eq Alignment Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Show Alignment Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic Alignment Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep Alignment :: Type -> Type #

Hashable Alignment Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep Alignment Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep Alignment = D1 (MetaData "Alignment" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (((C1 (MetaCons "AlignNone" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignxMinYMin" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AlignxMidYMin" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AlignxMaxYMin" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignxMinYMid" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "AlignxMidYMid" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignxMaxYMid" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AlignxMinYMax" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AlignxMidYMax" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignxMaxYMax" PrefixI False) (U1 :: Type -> Type)))))

data MeetSlice Source #

This type represent the "meet or slice" information of the preserveAspectRatio SVGattribute

Constructors

Meet 
Slice 
Instances
Eq MeetSlice Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Show MeetSlice Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic MeetSlice Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep MeetSlice :: Type -> Type #

Hashable MeetSlice Source # 
Instance details

Defined in Graphics.SvgTree.Types.Hashable

type Rep MeetSlice Source # 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep MeetSlice = D1 (MetaData "MeetSlice" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-Hn5EZrDBHcX186X2rLEalr" False) (C1 (MetaCons "Meet" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Slice" PrefixI False) (U1 :: Type -> Type))

MISC functions

zipTree :: ([[Tree]] -> Tree) -> Tree -> Tree Source #

Map a tree while propagating context information. The function passed in parameter receive a list representing the the path used to go arrive to the current node.

foldTree :: (a -> Tree -> a) -> a -> Tree -> a Source #

Fold all nodes of a SVG tree.

mapTree :: (Tree -> Tree) -> Tree -> Tree Source #

Helper function mapping every tree element.

nameOfTree :: Tree -> Text Source #

For every element of a svg tree, associate it's SVG tag name.

toUserUnit :: Dpi -> Number -> Number Source #

This function replace all device dependant units to user units given it's DPI configuration. Preserve percentage and "em" notation.

mapNumber :: (Double -> Double) -> Number -> Number Source #

Helper function to modify inner value of a number