Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module define all the types used in the definition of a svg scene.
Most of the types are lensified.
Synopsis
- type Coord = Double
- data Origin
- type Point = (Number, Number)
- type RPoint = V2 Coord
- data PathCommand
- = MoveTo !Origin ![RPoint]
- | LineTo !Origin ![RPoint]
- | HorizontalTo !Origin ![Coord]
- | VerticalTo !Origin ![Coord]
- | CurveTo !Origin ![(RPoint, RPoint, RPoint)]
- | SmoothCurveTo !Origin ![(RPoint, RPoint)]
- | QuadraticBezier !Origin ![(RPoint, RPoint)]
- | SmoothQuadraticBezierCurveTo !Origin ![RPoint]
- | EllipticalArc !Origin ![(Coord, Coord, Coord, Bool, Bool, RPoint)]
- | EndPath
- data Transformation
- data ElementRef
- data CoordinateUnits
- serializeNumber :: Number -> String
- serializeTransformation :: Transformation -> String
- serializeTransformations :: [Transformation] -> String
- data Cap
- data LineJoin
- data Tree
- pattern Tree :: TreeBranch -> Tree
- pattern None :: Tree
- treeBranch :: Lens' Tree TreeBranch
- data TreeBranch
- = NoNode
- | UseNode {
- useInformation :: !Use
- useSubTree :: !(Maybe Tree)
- | GroupNode !Group
- | SymbolNode !Group
- | DefinitionNode !Group
- | FilterNode !Filter
- | PathNode !Path
- | CircleNode !Circle
- | PolyLineNode !PolyLine
- | PolygonNode !Polygon
- | EllipseNode !Ellipse
- | LineNode !Line
- | RectangleNode !Rectangle
- | TextNode !(Maybe TextPath) !Text
- | ImageNode !Image
- | LinearGradientNode !LinearGradient
- | RadialGradientNode !RadialGradient
- | MeshGradientNode !MeshGradient
- | PatternNode !Pattern
- | MarkerNode !Marker
- | MaskNode !Mask
- | ClipPathNode !ClipPath
- | SvgNode !Document
- data Number
- data Spread
- data Texture
- data Element
- data FillRule
- data FontStyle
- type Dpi = Int
- class WithDefaultSvg a where
- defaultSvg :: a
- data Document = Document {}
- pattern SvgTree :: Document -> Tree
- svgTree :: Document -> Tree
- documentViewBox :: Lens' Document (Maybe (Double, Double, Double, Double))
- documentWidth :: Lens' Document (Maybe Number)
- documentHeight :: Lens' Document (Maybe Number)
- documentElements :: Lens' Document [Tree]
- documentDescription :: Lens' Document String
- documentLocation :: Lens' Document FilePath
- documentAspectRatio :: Lens' Document PreserveAspectRatio
- documentSize :: Dpi -> Document -> (Int, Int)
- data DrawAttributes = DrawAttributes {
- _strokeWidth :: !(Last Number)
- _strokeColor :: !(Last Texture)
- _strokeOpacity :: !(Maybe Float)
- _strokeLineCap :: !(Last Cap)
- _strokeLineJoin :: !(Last LineJoin)
- _strokeMiterLimit :: !(Last Double)
- _fillColor :: !(Last Texture)
- _fillOpacity :: !(Maybe Float)
- _groupOpacity :: !(Maybe Float)
- _transform :: !(Maybe [Transformation])
- _fillRule :: !(Last FillRule)
- _maskRef :: !(Last ElementRef)
- _clipPathRef :: !(Last ElementRef)
- _clipRule :: !(Last FillRule)
- _attrClass :: ![Text]
- _attrId :: !(Maybe String)
- _strokeOffset :: !(Last Number)
- _strokeDashArray :: !(Last [Number])
- _fontSize :: !(Last Number)
- _fontFamily :: !(Last [String])
- _fontStyle :: !(Last FontStyle)
- _textAnchor :: !(Last TextAnchor)
- _markerStart :: !(Last ElementRef)
- _markerMid :: !(Last ElementRef)
- _markerEnd :: !(Last ElementRef)
- _filterRef :: !(Last ElementRef)
- class HasDrawAttributes c where
- drawAttributes :: Lens' c DrawAttributes
- attrClass :: Lens' c [Text]
- attrId :: Lens' c (Maybe String)
- clipPathRef :: Lens' c (Last ElementRef)
- clipRule :: Lens' c (Last FillRule)
- fillColor :: Lens' c (Last Texture)
- fillOpacity :: Lens' c (Maybe Float)
- fillRule :: Lens' c (Last FillRule)
- filterRef :: Lens' c (Last ElementRef)
- fontFamily :: Lens' c (Last [String])
- fontSize :: Lens' c (Last Number)
- fontStyle :: Lens' c (Last FontStyle)
- groupOpacity :: Lens' c (Maybe Float)
- markerEnd :: Lens' c (Last ElementRef)
- markerMid :: Lens' c (Last ElementRef)
- markerStart :: Lens' c (Last ElementRef)
- maskRef :: Lens' c (Last ElementRef)
- strokeColor :: Lens' c (Last Texture)
- strokeDashArray :: Lens' c (Last [Number])
- strokeLineCap :: Lens' c (Last Cap)
- strokeLineJoin :: Lens' c (Last LineJoin)
- strokeMiterLimit :: Lens' c (Last Double)
- strokeOffset :: Lens' c (Last Number)
- strokeOpacity :: Lens' c (Maybe Float)
- strokeWidth :: Lens' c (Last Number)
- textAnchor :: Lens' c (Last TextAnchor)
- transform :: Lens' c (Maybe [Transformation])
- data FilterElement
- = FEBlend
- | FEColorMatrix ColorMatrix
- | FEComponentTransfer
- | FEComposite Composite
- | FEConvolveMatrix
- | FEDiffuseLighting
- | FEDisplacementMap DisplacementMap
- | FEDropShadow
- | FEFlood
- | FEFuncA
- | FEFuncB
- | FEFuncG
- | FEFuncR
- | FEGaussianBlur GaussianBlur
- | FEImage
- | FEMerge
- | FEMergeNode
- | FEMorphology
- | FEOffset
- | FESpecularLighting
- | FETile
- | FETurbulence Turbulence
- | FENone
- data FilterAttributes = FilterAttributes {
- _filterHeight :: !(Last Number)
- _filterResult :: !(Maybe String)
- _filterWidth :: !(Last Number)
- _filterX :: !(Last Number)
- _filterY :: !(Last Number)
- class HasFilterAttributes c where
- filterAttributes :: Lens' c FilterAttributes
- filterHeight :: Lens' c (Last Number)
- filterResult :: Lens' c (Maybe String)
- filterWidth :: Lens' c (Last Number)
- filterX :: Lens' c (Last Number)
- filterY :: Lens' c (Last Number)
- data FilterSource
- data ColorMatrixType
- colorMatrixDrawAttributes :: Lens' ColorMatrix DrawAttributes
- colorMatrixFilterAttr :: Lens' ColorMatrix FilterAttributes
- colorMatrixIn :: Lens' ColorMatrix (Last FilterSource)
- colorMatrixType :: Lens' ColorMatrix ColorMatrixType
- colorMatrixValues :: Lens' ColorMatrix String
- data ColorMatrix = ColorMatrix {}
- compositeDrawAttributes :: Lens' Composite DrawAttributes
- compositeFilterAttr :: Lens' Composite FilterAttributes
- compositeIn :: Lens' Composite (Last FilterSource)
- compositeIn2 :: Lens' Composite (Last FilterSource)
- compositeOperator :: Lens' Composite CompositeOperator
- compositeK1 :: Lens' Composite Number
- compositeK2 :: Lens' Composite Number
- compositeK3 :: Lens' Composite Number
- compositeK4 :: Lens' Composite Number
- data Composite = Composite {}
- data CompositeOperator
- data EdgeMode
- gaussianBlurDrawAttributes :: Lens' GaussianBlur DrawAttributes
- gaussianBlurFilterAttr :: Lens' GaussianBlur FilterAttributes
- gaussianBlurIn :: Lens' GaussianBlur (Last FilterSource)
- gaussianBlurStdDeviationX :: Lens' GaussianBlur Number
- gaussianBlurStdDeviationY :: Lens' GaussianBlur (Last Number)
- gaussianBlurEdgeMode :: Lens' GaussianBlur EdgeMode
- data GaussianBlur = GaussianBlur {}
- turbulenceDrawAttributes :: Lens' Turbulence DrawAttributes
- turbulenceFilterAttr :: Lens' Turbulence FilterAttributes
- turbulenceBaseFrequency :: Lens' Turbulence (Double, Last Double)
- turbulenceNumOctaves :: Lens' Turbulence Int
- turbulenceSeed :: Lens' Turbulence Double
- turbulenceStitchTiles :: Lens' Turbulence StitchTiles
- turbulenceType :: Lens' Turbulence TurbulenceType
- data Turbulence = Turbulence {}
- data TurbulenceType
- data StitchTiles
- data DisplacementMap = DisplacementMap {
- _displacementMapDrawAttributes :: !DrawAttributes
- _displacementMapFilterAttr :: !FilterAttributes
- _displacementMapIn :: !(Last FilterSource)
- _displacementMapIn2 :: !(Last FilterSource)
- _displacementMapScale :: !(Last Double)
- _displacementMapXChannelSelector :: ChannelSelector
- _displacementMapYChannelSelector :: ChannelSelector
- displacementMapDrawAttributes :: Lens' DisplacementMap DrawAttributes
- displacementMapFilterAttr :: Lens' DisplacementMap FilterAttributes
- displacementMapIn :: Lens' DisplacementMap (Last FilterSource)
- displacementMapIn2 :: Lens' DisplacementMap (Last FilterSource)
- displacementMapScale :: Lens' DisplacementMap (Last Double)
- displacementMapXChannelSelector :: Lens' DisplacementMap ChannelSelector
- displacementMapYChannelSelector :: Lens' DisplacementMap ChannelSelector
- data ChannelSelector
- data Rectangle = Rectangle {}
- pattern RectangleTree :: Rectangle -> Tree
- rectangleTree :: Rectangle -> Tree
- rectUpperLeftCorner :: Lens' Rectangle Point
- rectWidth :: Lens' Rectangle (Maybe Number)
- rectHeight :: Lens' Rectangle (Maybe Number)
- rectCornerRadius :: Lens' Rectangle (Maybe Number, Maybe Number)
- data Line = Line {}
- pattern LineTree :: Line -> Tree
- lineTree :: Line -> Tree
- linePoint1 :: Lens' Line Point
- linePoint2 :: Lens' Line Point
- data Polygon = Polygon {}
- pattern PolygonTree :: Polygon -> Tree
- polygonTree :: Polygon -> Tree
- polygonPoints :: Lens' Polygon [RPoint]
- data PolyLine = PolyLine {}
- pattern PolyLineTree :: PolyLine -> Tree
- polyLineTree :: PolyLine -> Tree
- polyLinePoints :: Lens' PolyLine [RPoint]
- data Path = Path {}
- pattern PathTree :: Path -> Tree
- pathTree :: Path -> Tree
- pathDefinition :: Lens' Path [PathCommand]
- data Circle = Circle {}
- pattern CircleTree :: Circle -> Tree
- circleTree :: Circle -> Tree
- circleCenter :: Lens' Circle Point
- circleRadius :: Lens' Circle Number
- data Ellipse = Ellipse {}
- pattern EllipseTree :: Ellipse -> Tree
- ellipseTree :: Ellipse -> Tree
- ellipseCenter :: Lens' Ellipse Point
- ellipseXRadius :: Lens' Ellipse Number
- ellipseYRadius :: Lens' Ellipse Number
- data GradientPathCommand
- data MeshGradientType
- data MeshGradient = MeshGradient {}
- pattern MeshGradientTree :: MeshGradient -> Tree
- meshGradientTree :: MeshGradient -> Tree
- meshGradientX :: Lens' MeshGradient Number
- meshGradientY :: Lens' MeshGradient Number
- meshGradientType :: Lens' MeshGradient MeshGradientType
- meshGradientUnits :: Lens' MeshGradient CoordinateUnits
- meshGradientTransform :: Lens' MeshGradient [Transformation]
- meshGradientRows :: Lens' MeshGradient [MeshGradientRow]
- data MeshGradientRow = MeshGradientRow {}
- meshGradientRowPatches :: Iso' MeshGradientRow [MeshGradientPatch]
- data MeshGradientPatch = MeshGradientPatch {}
- meshGradientPatchStops :: Iso' MeshGradientPatch [GradientStop]
- data Image = Image {}
- pattern ImageTree :: Image -> Tree
- imageTree :: Image -> Tree
- imageCornerUpperLeft :: Lens' Image Point
- imageWidth :: Lens' Image Number
- imageHeight :: Lens' Image Number
- imageHref :: Lens' Image String
- imageAspectRatio :: Lens' Image PreserveAspectRatio
- data Use = Use {}
- pattern UseTree :: Use -> Maybe Tree -> Tree
- useTree :: Use -> Tree
- useBase :: Lens' Use Point
- useName :: Lens' Use String
- useWidth :: Lens' Use (Maybe Number)
- useHeight :: Lens' Use (Maybe Number)
- data Group = Group {}
- pattern GroupTree :: Group -> Tree
- groupTree :: Group -> Tree
- groupDrawAttributes :: Lens' Group DrawAttributes
- groupChildren :: Lens' Group [Tree]
- groupViewBox :: Lens' Group (Maybe (Double, Double, Double, Double))
- groupAspectRatio :: Lens' Group PreserveAspectRatio
- pattern SymbolTree :: Group -> Tree
- symbolTree :: Group -> Tree
- pattern DefinitionTree :: Group -> Tree
- definitionTree :: Group -> Tree
- data Filter = Filter {}
- pattern FilterTree :: Filter -> Tree
- filterTree :: Filter -> Tree
- filterChildren :: Lens' Filter [FilterElement]
- data Text = Text {
- _textAdjust :: !TextAdjust
- _textRoot :: !TextSpan
- pattern TextTree :: Maybe TextPath -> Text -> Tree
- textTree :: Maybe TextPath -> Text -> Tree
- textAdjust :: Lens' Text TextAdjust
- textRoot :: Lens' Text TextSpan
- data TextAnchor
- textAt :: Point -> Text -> Text
- data TextPath = TextPath {}
- textPathStartOffset :: Lens' TextPath Number
- textPathName :: Lens' TextPath String
- textPathMethod :: Lens' TextPath TextPathMethod
- textPathSpacing :: Lens' TextPath TextPathSpacing
- data TextPathSpacing
- data TextPathMethod
- data TextSpanContent
- data TextSpan = TextSpan {}
- spanInfo :: Lens' TextSpan TextInfo
- spanDrawAttributes :: Lens' TextSpan DrawAttributes
- spanContent :: Lens' TextSpan [TextSpanContent]
- data TextInfo = TextInfo {
- _textInfoX :: ![Number]
- _textInfoY :: ![Number]
- _textInfoDX :: ![Number]
- _textInfoDY :: ![Number]
- _textInfoRotate :: ![Double]
- _textInfoLength :: !(Maybe Number)
- textInfoX :: Lens' TextInfo [Number]
- textInfoY :: Lens' TextInfo [Number]
- textInfoDX :: Lens' TextInfo [Number]
- textInfoDY :: Lens' TextInfo [Number]
- textInfoRotate :: Lens' TextInfo [Double]
- textInfoLength :: Lens' TextInfo (Maybe Number)
- data TextAdjust
- data Marker = Marker {
- _markerDrawAttributes :: DrawAttributes
- _markerRefPoint :: !(Number, Number)
- _markerWidth :: !(Maybe Number)
- _markerHeight :: !(Maybe Number)
- _markerOrient :: !(Maybe MarkerOrientation)
- _markerUnits :: !(Maybe MarkerUnit)
- _markerViewBox :: !(Maybe (Double, Double, Double, Double))
- _markerOverflow :: !(Maybe Overflow)
- _markerAspectRatio :: !PreserveAspectRatio
- _markerElements :: [Tree]
- pattern MarkerTree :: Marker -> Tree
- markerTree :: Marker -> Tree
- data Overflow
- data MarkerOrientation
- data MarkerUnit
- markerRefPoint :: Lens' Marker (Number, Number)
- markerWidth :: Lens' Marker (Maybe Number)
- markerHeight :: Lens' Marker (Maybe Number)
- markerOrient :: Lens' Marker (Maybe MarkerOrientation)
- markerUnits :: Lens' Marker (Maybe MarkerUnit)
- markerViewBox :: Lens' Marker (Maybe (Double, Double, Double, Double))
- markerOverflow :: Lens' Marker (Maybe Overflow)
- markerAspectRatio :: Lens' Marker PreserveAspectRatio
- markerElements :: Lens' Marker [Tree]
- data GradientStop = GradientStop {}
- gradientOffset :: Lens' GradientStop Float
- gradientColor :: Lens' GradientStop PixelRGBA8
- gradientPath :: Lens' GradientStop (Maybe GradientPathCommand)
- gradientOpacity :: Lens' GradientStop (Maybe Float)
- data LinearGradient = LinearGradient {}
- pattern LinearGradientTree :: LinearGradient -> Tree
- linearGradientTree :: LinearGradient -> Tree
- linearGradientUnits :: Lens' LinearGradient CoordinateUnits
- linearGradientStart :: Lens' LinearGradient Point
- linearGradientStop :: Lens' LinearGradient Point
- linearGradientSpread :: Lens' LinearGradient Spread
- linearGradientTransform :: Lens' LinearGradient [Transformation]
- linearGradientStops :: Lens' LinearGradient [GradientStop]
- data RadialGradient = RadialGradient {
- _radialGradientDrawAttributes :: DrawAttributes
- _radialGradientUnits :: CoordinateUnits
- _radialGradientCenter :: Point
- _radialGradientRadius :: Number
- _radialGradientFocusX :: Maybe Number
- _radialGradientFocusY :: Maybe Number
- _radialGradientSpread :: Spread
- _radialGradientTransform :: [Transformation]
- _radialGradientStops :: [GradientStop]
- pattern RadialGradientTree :: RadialGradient -> Tree
- radialGradientTree :: RadialGradient -> Tree
- radialGradientUnits :: Lens' RadialGradient CoordinateUnits
- radialGradientCenter :: Lens' RadialGradient Point
- radialGradientRadius :: Lens' RadialGradient Number
- radialGradientFocusX :: Lens' RadialGradient (Maybe Number)
- radialGradientFocusY :: Lens' RadialGradient (Maybe Number)
- radialGradientSpread :: Lens' RadialGradient Spread
- radialGradientTransform :: Lens' RadialGradient [Transformation]
- radialGradientStops :: Lens' RadialGradient [GradientStop]
- data Pattern = Pattern {
- _patternDrawAttributes :: DrawAttributes
- _patternViewBox :: !(Maybe (Double, Double, Double, Double))
- _patternWidth :: !Number
- _patternHeight :: !Number
- _patternPos :: !Point
- _patternHref :: !String
- _patternElements :: ![Tree]
- _patternUnit :: !CoordinateUnits
- _patternAspectRatio :: !PreserveAspectRatio
- _patternTransform :: !(Maybe [Transformation])
- pattern PatternTree :: Pattern -> Tree
- patternTree :: Pattern -> Tree
- patternViewBox :: Lens' Pattern (Maybe (Double, Double, Double, Double))
- patternWidth :: Lens' Pattern Number
- patternHeight :: Lens' Pattern Number
- patternPos :: Lens' Pattern Point
- patternHref :: Lens' Pattern String
- patternElements :: Lens' Pattern [Tree]
- patternUnit :: Lens' Pattern CoordinateUnits
- patternAspectRatio :: Lens' Pattern PreserveAspectRatio
- patternTransform :: Lens' Pattern (Maybe [Transformation])
- data Mask = Mask {}
- pattern MaskTree :: Mask -> Tree
- maskTree :: Mask -> Tree
- maskContentUnits :: Lens' Mask CoordinateUnits
- maskUnits :: Lens' Mask CoordinateUnits
- maskPosition :: Lens' Mask Point
- maskWidth :: Lens' Mask Number
- maskHeight :: Lens' Mask Number
- maskContent :: Lens' Mask [Tree]
- data ClipPath = ClipPath {}
- pattern ClipPathTree :: ClipPath -> Tree
- clipPathTree :: ClipPath -> Tree
- clipPathUnits :: Lens' ClipPath CoordinateUnits
- clipPathContent :: Lens' ClipPath [Tree]
- data PreserveAspectRatio = PreserveAspectRatio {}
- data Alignment
- data MeetSlice
- aspectRatioDefer :: Lens' PreserveAspectRatio Bool
- aspectRatioAlign :: Lens' PreserveAspectRatio Alignment
- aspectRatioMeetSlice :: Lens' PreserveAspectRatio (Maybe MeetSlice)
- zipTree :: ([[Tree]] -> Tree) -> Tree -> Tree
- foldTree :: (a -> Tree -> a) -> a -> Tree -> a
- mapTree :: (Tree -> Tree) -> Tree -> Tree
- mapBranch :: (TreeBranch -> TreeBranch) -> Tree -> Tree
- nameOfTree :: Tree -> Text
- toUserUnit :: Dpi -> Number -> Number
- mapNumber :: (Double -> Double) -> Number -> Number
Basic building types
Tell if a path command is absolute (in the current user coordiante) or relative to the previous poitn.
OriginAbsolute | Next point in absolute coordinate |
OriginRelative | Next point relative to the previous |
type RPoint = V2 Coord Source #
Real Point, fully determined and not dependant of the rendering context.
data PathCommand Source #
Path command definition.
MoveTo !Origin ![RPoint] |
|
LineTo !Origin ![RPoint] | Line to, |
HorizontalTo !Origin ![Coord] | Equivalent to the |
VerticalTo !Origin ![Coord] | Equivalent to the |
CurveTo !Origin ![(RPoint, RPoint, RPoint)] | Cubic bezier, |
SmoothCurveTo !Origin ![(RPoint, RPoint)] | Smooth cubic bezier, equivalent to |
QuadraticBezier !Origin ![(RPoint, RPoint)] | Quadratic bezier, |
SmoothQuadraticBezierCurveTo !Origin ![RPoint] | Quadratic bezier, |
EllipticalArc !Origin ![(Coord, Coord, Coord, Bool, Bool, RPoint)] | Eliptical arc, |
EndPath | Close the path, |
Instances
data Transformation Source #
Describe the content of the transformation
attribute.
see _transform
and transform
.
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
data ElementRef Source #
Correspond to the possible values of the
the attributes which are either none
or
`url(#elem)`
Instances
data CoordinateUnits Source #
Define the possible values of various *units attributes used in the definition of the gradients and masks.
CoordUserSpace |
|
CoordBoundingBox |
|
Instances
Eq CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Basic (==) :: CoordinateUnits -> CoordinateUnits -> Bool # (/=) :: CoordinateUnits -> CoordinateUnits -> Bool # | |
Show CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Basic showsPrec :: Int -> CoordinateUnits -> ShowS # show :: CoordinateUnits -> String # showList :: [CoordinateUnits] -> ShowS # | |
Generic CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Basic type Rep CoordinateUnits :: Type -> Type # from :: CoordinateUnits -> Rep CoordinateUnits x # to :: Rep CoordinateUnits x -> CoordinateUnits # | |
Hashable CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> CoordinateUnits -> Int # hash :: CoordinateUnits -> Int # | |
type Rep CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Basic |
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
Describe how the line should be terminated
when stroking them. Describe the values of the
`stroke-linecap` attribute.
See _strokeLineCap
CapRound | End with a round ( |
CapButt | Define straight just at the end ( |
CapSquare | Straight further of the ends ( |
Instances
Eq Cap Source # | |
Show Cap Source # | |
Generic Cap Source # | |
Hashable Cap Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep Cap Source # | |
Defined in Graphics.SvgTree.Types.Basic type Rep Cap = D1 (MetaData "Cap" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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))) |
Define the possible values of the `stroke-linejoin`
attribute.
see _strokeLineJoin
Instances
Eq LineJoin Source # | |
Show LineJoin Source # | |
Generic LineJoin Source # | |
Hashable LineJoin Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep LineJoin Source # | |
Defined in Graphics.SvgTree.Types.Basic type Rep LineJoin = D1 (MetaData "LineJoin" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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))) |
Main type for the scene description, reorient to specific type describing each tag.
Instances
pattern Tree :: TreeBranch -> Tree Source #
data TreeBranch Source #
Instances
Encode complex number possibly dependant to the current render size.
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
Define the possible values for the spreadMethod
values used for the gradient definitions.
SpreadRepeat |
|
SpreadPad |
|
SpreadReflect | `reflect value` |
Instances
Eq Spread Source # | |
Show Spread Source # | |
Generic Spread Source # | |
Hashable Spread Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep Spread Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep Spread = D1 (MetaData "Spread" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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))) |
Describe the different value which can be used
in the fill
or stroke
attributes.
ColorRef PixelRGBA8 | |
TextureRef String | Link to a complex texture (url(#name)) |
FillNone | Equivalent to the |
Instances
Eq Texture Source # | |
Show Texture Source # | |
Generic Texture Source # | |
Hashable Texture Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep Texture Source # | |
Defined in Graphics.SvgTree.Types.Basic type Rep Texture = D1 (MetaData "Texture" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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))) |
Sum types helping keeping track of all the namable elemens in a SVG document.
Instances
Describe the possile filling algorithms. Map the values of the `fill-rule` attributes.
FillEvenOdd | Correspond to the |
FillNonZero | Correspond to the |
Classify the font style, used to search a matching font in the FontCache.
Instances
Eq FontStyle Source # | |
Show FontStyle Source # | |
Generic FontStyle Source # | |
Hashable FontStyle Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep FontStyle Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep FontStyle = D1 (MetaData "FontStyle" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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))) |
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.
defaultSvg :: a Source #
The default element.
Instances
Main type
Represent a full svg document with style, geometry and named elements.
Instances
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.
DrawAttributes | |
|
Instances
class HasDrawAttributes c where Source #
drawAttributes :: Lens' c DrawAttributes Source #
attrClass :: Lens' c [Text] Source #
attrId :: Lens' c (Maybe String) Source #
clipPathRef :: Lens' c (Last ElementRef) Source #
clipRule :: Lens' c (Last FillRule) Source #
fillColor :: Lens' c (Last Texture) Source #
fillOpacity :: Lens' c (Maybe Float) Source #
fillRule :: Lens' c (Last FillRule) Source #
filterRef :: Lens' c (Last ElementRef) Source #
fontFamily :: Lens' c (Last [String]) Source #
fontSize :: Lens' c (Last Number) Source #
fontStyle :: Lens' c (Last FontStyle) Source #
groupOpacity :: Lens' c (Maybe Float) Source #
markerEnd :: Lens' c (Last ElementRef) Source #
markerMid :: Lens' c (Last ElementRef) Source #
markerStart :: Lens' c (Last ElementRef) Source #
maskRef :: Lens' c (Last ElementRef) Source #
strokeColor :: Lens' c (Last Texture) Source #
strokeDashArray :: Lens' c (Last [Number]) Source #
strokeLineCap :: Lens' c (Last Cap) Source #
strokeLineJoin :: Lens' c (Last LineJoin) Source #
strokeMiterLimit :: Lens' c (Last Double) Source #
strokeOffset :: Lens' c (Last Number) Source #
strokeOpacity :: Lens' c (Maybe Float) Source #
strokeWidth :: Lens' c (Last Number) Source #
textAnchor :: Lens' c (Last TextAnchor) Source #
Instances
Filters
data FilterElement Source #
Instances
data FilterAttributes Source #
FilterAttributes | |
|
Instances
class HasFilterAttributes c where Source #
filterAttributes :: Lens' c FilterAttributes Source #
filterHeight :: Lens' c (Last Number) Source #
filterResult :: Lens' c (Maybe String) Source #
filterWidth :: Lens' c (Last Number) Source #
Instances
data FilterSource Source #
Instances
data ColorMatrixType Source #
Instances
data ColorMatrix Source #
Instances
Instances
data CompositeOperator Source #
Instances
Instances
Eq EdgeMode Source # | |
Show EdgeMode Source # | |
Generic EdgeMode Source # | |
Hashable EdgeMode Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep EdgeMode Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep EdgeMode = D1 (MetaData "EdgeMode" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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
data Turbulence Source #
Instances
data TurbulenceType Source #
Instances
Eq TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal (==) :: TurbulenceType -> TurbulenceType -> Bool # (/=) :: TurbulenceType -> TurbulenceType -> Bool # | |
Show TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal showsPrec :: Int -> TurbulenceType -> ShowS # show :: TurbulenceType -> String # showList :: [TurbulenceType] -> ShowS # | |
Generic TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TurbulenceType :: Type -> Type # from :: TurbulenceType -> Rep TurbulenceType x # to :: Rep TurbulenceType x -> TurbulenceType # | |
Hashable TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> TurbulenceType -> Int # hash :: TurbulenceType -> Int # | |
type Rep TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal |
data StitchTiles Source #
Instances
Eq StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal (==) :: StitchTiles -> StitchTiles -> Bool # (/=) :: StitchTiles -> StitchTiles -> Bool # | |
Show StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal showsPrec :: Int -> StitchTiles -> ShowS # show :: StitchTiles -> String # showList :: [StitchTiles] -> ShowS # | |
Generic StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep StitchTiles :: Type -> Type # from :: StitchTiles -> Rep StitchTiles x # to :: Rep StitchTiles x -> StitchTiles # | |
Hashable StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> StitchTiles -> Int # hash :: StitchTiles -> Int # | |
type Rep StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal |
data DisplacementMap Source #
Instances
data ChannelSelector Source #
Instances
SVG drawing primitives
Rectangle
Define a rectangle. Correspond to `<rectangle>` svg tag.
Rectangle | |
|
Instances
pattern RectangleTree :: Rectangle -> Tree Source #
rectangleTree :: Rectangle -> Tree Source #
Line
Define a simple line. Correspond to the `<line>` tag.
Line | |
|
Instances
Polygon
Primitive decriving polygon composed of segements. Correspond to the `<polygon>` tag
Polygon | |
|
Instances
pattern PolygonTree :: Polygon -> Tree Source #
polygonTree :: Polygon -> Tree Source #
Polyline
This primitive describe an unclosed suite of segments. Correspond to the `<polyline>` tag.
PolyLine | |
|
Instances
pattern PolyLineTree :: PolyLine -> Tree Source #
polyLineTree :: PolyLine -> Tree Source #
Path
Type mapping the `<path>` svg tag.
Path | |
|
Instances
Circle
Define a `<circle>`.
Circle | |
|
Instances
pattern CircleTree :: Circle -> Tree Source #
circleTree :: Circle -> Tree Source #
Ellipse
Define an `<ellipse>`
Ellipse | |
|
Instances
pattern EllipseTree :: Ellipse -> Tree Source #
ellipseTree :: Ellipse -> Tree Source #
Mesh (gradient mesh)
data GradientPathCommand Source #
Description of path used in meshgradient tag
GLine !Origin !(Maybe RPoint) | Line to, |
GCurve !Origin !RPoint !RPoint !(Maybe RPoint) | Cubic bezier, |
GClose |
|
Instances
data MeshGradientType Source #
Instances
Eq MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic (==) :: MeshGradientType -> MeshGradientType -> Bool # (/=) :: MeshGradientType -> MeshGradientType -> Bool # | |
Show MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic showsPrec :: Int -> MeshGradientType -> ShowS # show :: MeshGradientType -> String # showList :: [MeshGradientType] -> ShowS # | |
Generic MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic type Rep MeshGradientType :: Type -> Type # from :: MeshGradientType -> Rep MeshGradientType x # to :: Rep MeshGradientType x -> MeshGradientType # | |
Hashable MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> MeshGradientType -> Int # hash :: MeshGradientType -> Int # | |
type Rep MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic |
data MeshGradient Source #
Define a `<meshgradient>` tag.
MeshGradient | |
|
Instances
pattern MeshGradientTree :: MeshGradient -> Tree Source #
meshGradientTree :: MeshGradient -> Tree Source #
data MeshGradientRow Source #
Define a `<meshrow>` tag.
MeshGradientRow | |
|
Instances
data MeshGradientPatch Source #
Define `<meshpatch>` SVG tag
MeshGradientPatch | |
|
Instances
Image
Define an `<image>` tag.
Image | |
|
Instances
Use
Define an `<use>` for a named content. Every named content can be reused in the document using this element.
Use | |
|
Instances
Grouping primitives
Group
Define a SVG group, corresponding `<g>` tag.
Group | |
|
Instances
Symbol
pattern SymbolTree :: Group -> Tree Source #
symbolTree :: Group -> Tree Source #
Definitions
pattern DefinitionTree :: Group -> Tree Source #
definitionTree :: Group -> Tree Source #
Filter
Define the `<filter>` tag.
Instances
pattern FilterTree :: Filter -> Tree Source #
filterTree :: Filter -> Tree Source #
Text related types
Text
Define the global `<text>` SVG tag.
Text | |
|
Instances
data TextAnchor Source #
Tell where to anchor the text, where the position given is realative to the text.
TextAnchorStart | The text with left aligned, or start at the postion
If the point is the *THE_TEXT_TO_PRINT Equivalent to the |
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 |
TextAnchorEnd | The text is right aligned. THE_TEXT_TO_PRINT* Equivalent to the |
Instances
textAt :: Point -> Text -> Text Source #
Little helper to create a SVG text at a given baseline position.
Text path
Describe the `<textpath>` SVG tag.
TextPath | |
|
Instances
Eq TextPath Source # | |
Show TextPath Source # | |
Generic TextPath Source # | |
Hashable TextPath Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
WithDefaultSvg TextPath Source # | |
Defined in Graphics.SvgTree.Types.Internal | |
type Rep TextPath Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextPath = D1 (MetaData "TextPath" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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.
TextPathSpacingExact | Map to the |
TextPathSpacingAuto | Map to the |
Instances
Eq TextPathSpacing Source # | |
Defined in Graphics.SvgTree.Types.Internal (==) :: TextPathSpacing -> TextPathSpacing -> Bool # (/=) :: TextPathSpacing -> TextPathSpacing -> Bool # | |
Show TextPathSpacing Source # | |
Defined in Graphics.SvgTree.Types.Internal showsPrec :: Int -> TextPathSpacing -> ShowS # show :: TextPathSpacing -> String # showList :: [TextPathSpacing] -> ShowS # | |
Generic TextPathSpacing Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextPathSpacing :: Type -> Type # from :: TextPathSpacing -> Rep TextPathSpacing x # to :: Rep TextPathSpacing x -> TextPathSpacing # | |
Hashable TextPathSpacing Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> TextPathSpacing -> Int # hash :: TextPathSpacing -> Int # | |
type Rep TextPathSpacing Source # | |
Defined in Graphics.SvgTree.Types.Internal |
data TextPathMethod Source #
Describe the content of the method
attribute on
text path.
TextPathAlign | Map to the |
TextPathStretch | Map to the |
Instances
Eq TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal (==) :: TextPathMethod -> TextPathMethod -> Bool # (/=) :: TextPathMethod -> TextPathMethod -> Bool # | |
Show TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal showsPrec :: Int -> TextPathMethod -> ShowS # show :: TextPathMethod -> String # showList :: [TextPathMethod] -> ShowS # | |
Generic TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextPathMethod :: Type -> Type # from :: TextPathMethod -> Rep TextPathMethod x # to :: Rep TextPathMethod x -> TextPathMethod # | |
Hashable TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> TextPathMethod -> Int # hash :: TextPathMethod -> Int # | |
type Rep TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal |
Text span.
data TextSpanContent Source #
Define the content of a `<tspan>` tag.
SpanText !Text | Raw text |
SpanTextRef !String | Equivalent to a `<tref>` |
SpanSub !TextSpan | Define a `<tspan>` |
Instances
Define a `<tspan>` tag.
TextSpan | |
|
Instances
Eq TextSpan Source # | |
Show TextSpan Source # | |
Generic TextSpan Source # | |
Hashable TextSpan Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
WithDefaultSvg TextSpan Source # | |
Defined in Graphics.SvgTree.Types.Internal | |
type Rep TextSpan Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextSpan = D1 (MetaData "TextSpan" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.11.0.0-8UuCEIqv3kIFj7X6j7xTER" 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])))) |
Define position information associated to `<text>` or `<tspan>` svg tag.
TextInfo | |
|
Instances
data TextAdjust Source #
Define the possible values of the lengthAdjust
attribute.
TextAdjustSpacing | Value |
TextAdjustSpacingAndGlyphs | Value |
Instances
Eq TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal (==) :: TextAdjust -> TextAdjust -> Bool # (/=) :: TextAdjust -> TextAdjust -> Bool # | |
Show TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal showsPrec :: Int -> TextAdjust -> ShowS # show :: TextAdjust -> String # showList :: [TextAdjust] -> ShowS # | |
Generic TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextAdjust :: Type -> Type # from :: TextAdjust -> Rep TextAdjust x # to :: Rep TextAdjust x -> TextAdjust # | |
Hashable TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> TextAdjust -> Int # hash :: TextAdjust -> Int # | |
type Rep TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal |
Marker definition
Define the `<marker>` tag.
Marker | |
|
Instances
pattern MarkerTree :: Marker -> Tree Source #
markerTree :: Marker -> Tree Source #
Define the content of the markerUnits
attribute
on the Marker.
OverflowVisible | Value |
OverflowHidden | Value |
data MarkerOrientation Source #
Define the orientation, associated to the
orient
attribute on the Marker
OrientationAuto | Auto value |
OrientationAngle Coord | Specific angle. |
Instances
data MarkerUnit Source #
Define the content of the markerUnits
attribute
on the Marker.
MarkerUnitStrokeWidth | Value |
MarkerUnitUserSpaceOnUse | Value |
Instances
Eq MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal (==) :: MarkerUnit -> MarkerUnit -> Bool # (/=) :: MarkerUnit -> MarkerUnit -> Bool # | |
Show MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal showsPrec :: Int -> MarkerUnit -> ShowS # show :: MarkerUnit -> String # showList :: [MarkerUnit] -> ShowS # | |
Generic MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep MarkerUnit :: Type -> Type # from :: MarkerUnit -> Rep MarkerUnit x # to :: Rep MarkerUnit x -> MarkerUnit # | |
Hashable MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Hashable hashWithSalt :: Int -> MarkerUnit -> Int # hash :: MarkerUnit -> Int # | |
type Rep MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal |
markerUnits :: Lens' Marker (Maybe MarkerUnit) Source #
Gradient definition
data GradientStop Source #
Define a color stop for the gradients. Represent the `<stop>` SVG tag.
GradientStop | |
|
Instances
Linear Gradient
data LinearGradient Source #
Define a `<linearGradient>` tag.
LinearGradient | |
|
Instances
pattern LinearGradientTree :: LinearGradient -> Tree Source #
Radial Gradient
data RadialGradient Source #
Define a `<radialGradient>` tag.
RadialGradient | |
|
Instances
pattern RadialGradientTree :: RadialGradient -> Tree Source #
Pattern definition
Define a `<pattern>` tag.
Pattern | |
|
Instances
pattern PatternTree :: Pattern -> Tree Source #
patternTree :: Pattern -> Tree Source #
Mask definition
Define a SVG `<mask>` tag.
Mask | |
|
Instances
Clip path definition
Define a `<clipPath>` tag.
ClipPath | |
|
Instances
pattern ClipPathTree :: ClipPath -> Tree Source #
clipPathTree :: ClipPath -> Tree Source #
Aspect Ratio description
data PreserveAspectRatio Source #
Describe the content of the preserveAspectRatio attribute.
Instances
This type represent the align information of the preserveAspectRatio SVGattribute
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
This type represent the "meet or slice" information of the preserveAspectRatio SVGattribute
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.
mapBranch :: (TreeBranch -> TreeBranch) -> Tree -> Tree Source #
nameOfTree :: Tree -> Text Source #
For every element of a svg tree, associate it's SVG tag name.