Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.SvgTree.Types
Description
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 :: !(Maybe Number)
- _strokeColor :: !(Maybe Texture)
- _strokeOpacity :: !(Maybe Float)
- _strokeLineCap :: !(Maybe Cap)
- _strokeLineJoin :: !(Maybe LineJoin)
- _strokeMiterLimit :: !(Maybe Double)
- _fillColor :: !(Maybe Texture)
- _fillOpacity :: !(Maybe Float)
- _groupOpacity :: !(Maybe Float)
- _transform :: !(Maybe [Transformation])
- _fillRule :: !(Maybe FillRule)
- _maskRef :: !(Maybe ElementRef)
- _clipPathRef :: !(Maybe ElementRef)
- _clipRule :: !(Maybe FillRule)
- _attrClass :: ![Text]
- _attrId :: !(Maybe String)
- _strokeOffset :: !(Maybe Number)
- _strokeDashArray :: !(Maybe [Number])
- _fontSize :: !(Maybe Number)
- _fontFamily :: !(Maybe [String])
- _fontStyle :: !(Maybe FontStyle)
- _textAnchor :: !(Maybe TextAnchor)
- _markerStart :: !(Maybe ElementRef)
- _markerMid :: !(Maybe ElementRef)
- _markerEnd :: !(Maybe ElementRef)
- _filterRef :: !(Maybe ElementRef)
- class HasDrawAttributes c where
- drawAttributes :: Lens' c DrawAttributes
- attrClass :: Lens' c [Text]
- attrId :: Lens' c (Maybe String)
- clipPathRef :: Lens' c (Maybe ElementRef)
- clipRule :: Lens' c (Maybe FillRule)
- fillColor :: Lens' c (Maybe Texture)
- fillOpacity :: Lens' c (Maybe Float)
- fillRule :: Lens' c (Maybe FillRule)
- filterRef :: Lens' c (Maybe ElementRef)
- fontFamily :: Lens' c (Maybe [String])
- fontSize :: Lens' c (Maybe Number)
- fontStyle :: Lens' c (Maybe FontStyle)
- groupOpacity :: Lens' c (Maybe Float)
- markerEnd :: Lens' c (Maybe ElementRef)
- markerMid :: Lens' c (Maybe ElementRef)
- markerStart :: Lens' c (Maybe ElementRef)
- maskRef :: Lens' c (Maybe ElementRef)
- strokeColor :: Lens' c (Maybe Texture)
- strokeDashArray :: Lens' c (Maybe [Number])
- strokeLineCap :: Lens' c (Maybe Cap)
- strokeLineJoin :: Lens' c (Maybe LineJoin)
- strokeMiterLimit :: Lens' c (Maybe Double)
- strokeOffset :: Lens' c (Maybe Number)
- strokeOpacity :: Lens' c (Maybe Float)
- strokeWidth :: Lens' c (Maybe Number)
- textAnchor :: Lens' c (Maybe TextAnchor)
- transform :: Lens' c (Maybe [Transformation])
- data FilterElement
- = FEBlend Blend
- | FEColorMatrix ColorMatrix
- | FEComponentTransfer ComponentTransfer
- | FEComposite Composite
- | FEConvolveMatrix ConvolveMatrix
- | FEDiffuseLighting DiffuseLighting
- | FEDisplacementMap DisplacementMap
- | FEDropShadow DropShadow
- | FEFlood Flood
- | FEFuncA FuncA
- | FEFuncB FuncB
- | FEFuncG FuncG
- | FEFuncR FuncR
- | FEGaussianBlur GaussianBlur
- | FEImage ImageF
- | FEMerge Merge
- | FEMergeNode MergeNode
- | FEMorphology Morphology
- | FEOffset Offset
- | FESpecularLighting SpecularLighting
- | FETile Tile
- | FETurbulence Turbulence
- | FENone
- data FilterAttributes = FilterAttributes {
- _filterHeight :: !(Maybe Number)
- _filterResult :: !(Maybe String)
- _filterWidth :: !(Maybe Number)
- _filterX :: !(Maybe Number)
- _filterY :: !(Maybe Number)
- class HasFilterAttributes c where
- filterAttributes :: Lens' c FilterAttributes
- filterHeight :: Lens' c (Maybe Number)
- filterResult :: Lens' c (Maybe String)
- filterWidth :: Lens' c (Maybe Number)
- filterX :: Lens' c (Maybe Number)
- filterY :: Lens' c (Maybe Number)
- data FilterSource
- data Blend = Blend {}
- data BlendMode
- = Normal
- | Multiply
- | Screen
- | Overlay
- | Darken
- | Lighten
- | ColorDodge
- | ColorBurn
- | HardLight
- | SoftLight
- | Difference
- | Exclusion
- | Hue
- | Saturation
- | Color
- | Luminosity
- blendDrawAttributes :: Lens' Blend DrawAttributes
- blendFilterAttr :: Lens' Blend FilterAttributes
- blendIn :: Lens' Blend (Maybe FilterSource)
- blendIn2 :: Lens' Blend (Maybe FilterSource)
- blendMode :: Lens' Blend BlendMode
- data ConvolveMatrix = ConvolveMatrix {
- _convolveMatrixDrawAttributes :: DrawAttributes
- _convolveMatrixFilterAttr :: !FilterAttributes
- _convolveMatrixIn :: !(Maybe FilterSource)
- _convolveMatrixOrder :: NumberOptionalNumber
- _convolveMatrixKernelMatrix :: [Double]
- _convolveMatrixDivisor :: Double
- _convolveMatrixBias :: Double
- _convolveMatrixTargetX :: Int
- _convolveMatrixTargetY :: Int
- _convolveMatrixEdgeMode :: EdgeMode
- _convolveMatrixKernelUnitLength :: NumberOptionalNumber
- _convolveMatrixPreserveAlpha :: Bool
- convolveMatrixDrawAttributes :: Lens' ConvolveMatrix DrawAttributes
- convolveMatrixFilterAttr :: Lens' ConvolveMatrix FilterAttributes
- convolveMatrixIn :: Lens' ConvolveMatrix (Maybe FilterSource)
- convolveMatrixOrder :: Lens' ConvolveMatrix NumberOptionalNumber
- convolveMatrixKernelMatrix :: Lens' ConvolveMatrix [Double]
- convolveMatrixDivisor :: Lens' ConvolveMatrix Double
- convolveMatrixBias :: Lens' ConvolveMatrix Double
- convolveMatrixTargetX :: Lens' ConvolveMatrix Int
- convolveMatrixTargetY :: Lens' ConvolveMatrix Int
- convolveMatrixEdgeMode :: Lens' ConvolveMatrix EdgeMode
- convolveMatrixKernelUnitLength :: Lens' ConvolveMatrix NumberOptionalNumber
- convolveMatrixPreserveAlpha :: Lens' ConvolveMatrix Bool
- data Morphology = Morphology {}
- data OperatorType
- data NumberOptionalNumber
- morphologyDrawAttributes :: Lens' Morphology DrawAttributes
- morphologyFilterAttr :: Lens' Morphology FilterAttributes
- morphologyIn :: Lens' Morphology (Maybe FilterSource)
- morphologyOperator :: Lens' Morphology OperatorType
- morphologyRadius :: Lens' Morphology NumberOptionalNumber
- data SpecularLighting = SpecularLighting {}
- specLightingDrawAttributes :: Lens' SpecularLighting DrawAttributes
- specLightingFilterAttr :: Lens' SpecularLighting FilterAttributes
- specLightingIn :: Lens' SpecularLighting (Maybe FilterSource)
- specLightingSurfaceScale :: Lens' SpecularLighting Double
- specLightingSpecularConst :: Lens' SpecularLighting Double
- specLightingSpecularExp :: Lens' SpecularLighting Double
- specLightingKernelUnitLength :: Lens' SpecularLighting NumberOptionalNumber
- data DiffuseLighting
- diffuseLightingDrawAttributes :: Lens' DiffuseLighting DrawAttributes
- diffuseLightingFilterAttr :: Lens' DiffuseLighting FilterAttributes
- diffuseLightingIn :: Lens' DiffuseLighting (Maybe FilterSource)
- diffuseLightingSurfaceScale :: Lens' DiffuseLighting Double
- diffuseLightingDiffuseConst :: Lens' DiffuseLighting Double
- diffuseLightingKernelUnitLength :: Lens' DiffuseLighting NumberOptionalNumber
- data DropShadow = DropShadow {}
- dropShadowDrawAttributes :: Lens' DropShadow DrawAttributes
- dropShadowFilterAttr :: Lens' DropShadow FilterAttributes
- dropShadowDx :: Lens' DropShadow Double
- dropShadowDy :: Lens' DropShadow Double
- dropShadowStdDeviation :: Lens' DropShadow NumberOptionalNumber
- data Flood = Flood {}
- floodDrawAttributes :: Lens' Flood DrawAttributes
- floodFilterAttr :: Lens' Flood FilterAttributes
- floodColor :: Lens' Flood PixelRGBA8
- floodOpacity :: Lens' Flood (Maybe Double)
- data Tile = Tile {}
- tileDrawAttributes :: Lens' Tile DrawAttributes
- tileFilterAttr :: Lens' Tile FilterAttributes
- tileIn :: Lens' Tile (Maybe FilterSource)
- data Offset = Offset {}
- offsetDrawAttributes :: Lens' Offset DrawAttributes
- offsetFilterAttr :: Lens' Offset FilterAttributes
- offsetIn :: Lens' Offset (Maybe FilterSource)
- offsetDX :: Lens' Offset Number
- offsetDY :: Lens' Offset Number
- data MergeNode = MergeNode {}
- mergeNodeDrawAttributes :: Lens' MergeNode DrawAttributes
- mergeNodeIn :: Lens' MergeNode (Maybe FilterSource)
- data Merge = Merge {}
- mergeDrawAttributes :: Lens' Merge DrawAttributes
- mergeFilterAttributes :: Lens' Merge FilterAttributes
- mergeChildren :: Lens' Merge [FilterElement]
- data ImageF = ImageF {}
- imageFDrawAttributes :: Lens' ImageF DrawAttributes
- imageFFilterAttr :: Lens' ImageF FilterAttributes
- imageFHref :: Lens' ImageF String
- imageFAspectRatio :: Lens' ImageF PreserveAspectRatio
- data ComponentTransfer = ComponentTransfer {}
- compTransferDrawAttributes :: Lens' ComponentTransfer DrawAttributes
- compTransferFilterAttr :: Lens' ComponentTransfer FilterAttributes
- compTransferChildren :: Lens' ComponentTransfer [FilterElement]
- compTransferIn :: Lens' ComponentTransfer (Maybe FilterSource)
- data FuncA = FuncA {}
- data FuncType
- funcADrawAttributes :: Lens' FuncA DrawAttributes
- funcAType :: Lens' FuncA FuncType
- funcATableValues :: Lens' FuncA [Number]
- funcASlope :: Lens' FuncA Number
- funcAIntercept :: Lens' FuncA Number
- funcAAmplitude :: Lens' FuncA Number
- funcAExponent :: Lens' FuncA Number
- data FuncR = FuncR {}
- funcRDrawAttributes :: Lens' FuncR DrawAttributes
- funcRType :: Lens' FuncR FuncType
- funcRTableValues :: Lens' FuncR [Number]
- funcRSlope :: Lens' FuncR Number
- funcRIntercept :: Lens' FuncR Number
- funcRAmplitude :: Lens' FuncR Number
- funcRExponent :: Lens' FuncR Number
- data FuncG = FuncG {}
- funcGDrawAttributes :: Lens' FuncG DrawAttributes
- funcGType :: Lens' FuncG FuncType
- funcGTableValues :: Lens' FuncG [Number]
- funcGSlope :: Lens' FuncG Number
- funcGIntercept :: Lens' FuncG Number
- funcGAmplitude :: Lens' FuncG Number
- funcGExponent :: Lens' FuncG Number
- data FuncB = FuncB {}
- funcBDrawAttributes :: Lens' FuncB DrawAttributes
- funcBType :: Lens' FuncB FuncType
- funcBTableValues :: Lens' FuncB [Number]
- funcBSlope :: Lens' FuncB Number
- funcBIntercept :: Lens' FuncB Number
- funcBAmplitude :: Lens' FuncB Number
- funcBExponent :: Lens' FuncB Number
- data ColorMatrixType
- colorMatrixDrawAttributes :: Lens' ColorMatrix DrawAttributes
- colorMatrixFilterAttr :: Lens' ColorMatrix FilterAttributes
- colorMatrixIn :: Lens' ColorMatrix (Maybe FilterSource)
- colorMatrixType :: Lens' ColorMatrix ColorMatrixType
- colorMatrixValues :: Lens' ColorMatrix String
- data ColorMatrix = ColorMatrix {}
- compositeDrawAttributes :: Lens' Composite DrawAttributes
- compositeFilterAttr :: Lens' Composite FilterAttributes
- compositeIn :: Lens' Composite (Maybe FilterSource)
- compositeIn2 :: Lens' Composite (Maybe 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 (Maybe FilterSource)
- gaussianBlurStdDeviationX :: Lens' GaussianBlur Number
- gaussianBlurStdDeviationY :: Lens' GaussianBlur (Maybe Number)
- gaussianBlurEdgeMode :: Lens' GaussianBlur EdgeMode
- data GaussianBlur = GaussianBlur {}
- turbulenceDrawAttributes :: Lens' Turbulence DrawAttributes
- turbulenceFilterAttr :: Lens' Turbulence FilterAttributes
- turbulenceBaseFrequency :: Lens' Turbulence (Double, Maybe 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 :: !(Maybe FilterSource)
- _displacementMapIn2 :: !(Maybe FilterSource)
- _displacementMapScale :: !(Maybe Double)
- _displacementMapXChannelSelector :: ChannelSelector
- _displacementMapYChannelSelector :: ChannelSelector
- displacementMapDrawAttributes :: Lens' DisplacementMap DrawAttributes
- displacementMapFilterAttr :: Lens' DisplacementMap FilterAttributes
- displacementMapIn :: Lens' DisplacementMap (Maybe FilterSource)
- displacementMapIn2 :: Lens' DisplacementMap (Maybe FilterSource)
- displacementMapScale :: Lens' DisplacementMap (Maybe 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]
- newtype MeshGradientRow = MeshGradientRow {}
- meshGradientRowPatches :: Iso' MeshGradientRow [MeshGradientPatch]
- newtype 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 point.
Constructors
OriginAbsolute | Next point in absolute coordinate |
OriginRelative | Next point relative to the previous |
type RPoint = V2 Coord Source #
Real Point, fully determined and independent of the rendering context.
data PathCommand Source #
Path command definition.
Constructors
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)] | Elliptical arc, |
EndPath | Close the path, |
Instances
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 axes 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 | Unknown transformation, like identity. |
Instances
data ElementRef Source #
Corresponds to the possible values of
the attributes which are either none
or
`url(#elem)`
Instances
Eq ElementRef Source # | |
Defined in Graphics.SvgTree.Types.Internal | |
Show ElementRef Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods showsPrec :: Int -> ElementRef -> ShowS # show :: ElementRef -> String # showList :: [ElementRef] -> ShowS # | |
Generic ElementRef Source # | |
Defined in Graphics.SvgTree.Types.Internal Associated Types type Rep ElementRef :: Type -> Type # | |
Hashable ElementRef Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep ElementRef Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep ElementRef = D1 ('MetaData "ElementRef" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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 #
Defines the possible values of various *units attributes used in the definition of the gradients and masks.
Constructors
CoordUserSpace |
|
CoordBoundingBox |
|
Instances
Eq CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Basic Methods (==) :: CoordinateUnits -> CoordinateUnits -> Bool # (/=) :: CoordinateUnits -> CoordinateUnits -> Bool # | |
Show CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Basic Methods showsPrec :: Int -> CoordinateUnits -> ShowS # show :: CoordinateUnits -> String # showList :: [CoordinateUnits] -> ShowS # | |
Generic CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Basic Associated Types type Rep CoordinateUnits :: Type -> Type # Methods from :: CoordinateUnits -> Rep CoordinateUnits x # to :: Rep CoordinateUnits x -> CoordinateUnits # | |
Hashable CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
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
Describes how the line should be terminated
when stroked. Describes the values of the
`stroke-linecap` attribute.
See _strokeLineCap
Constructors
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.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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))) |
Defines 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.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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 #
Constructors
Instances
Encode complex number possibly depending on 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
Defines the possible values for the spreadMethod
values used for the gradient definitions.
Constructors
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.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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))) |
Describes the different values which can be used
in the fill
or stroke
attributes.
Constructors
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.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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.
Constructors
Instances
Describe the possible filling algorithms. Map the values of the `fill-rule` attributes.
Constructors
FillEvenOdd | Corresponds to the |
FillNonZero | Corresponds to the |
Classify the font style, used to search a matching font in the FontCache.
Constructors
FontStyleNormal | |
FontStyleItalic | |
FontStyleOblique |
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.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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.
Instances
Main type
Represents a full svg document with style, geometry and named elements.
Constructors
Document | |
Fields |
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 defines 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
class HasDrawAttributes c where Source #
Minimal complete definition
Methods
drawAttributes :: Lens' c DrawAttributes Source #
attrClass :: Lens' c [Text] Source #
attrId :: Lens' c (Maybe String) Source #
clipPathRef :: Lens' c (Maybe ElementRef) Source #
clipRule :: Lens' c (Maybe FillRule) Source #
fillColor :: Lens' c (Maybe Texture) Source #
fillOpacity :: Lens' c (Maybe Float) Source #
fillRule :: Lens' c (Maybe FillRule) Source #
filterRef :: Lens' c (Maybe ElementRef) Source #
fontFamily :: Lens' c (Maybe [String]) Source #
fontSize :: Lens' c (Maybe Number) Source #
fontStyle :: Lens' c (Maybe FontStyle) Source #
groupOpacity :: Lens' c (Maybe Float) Source #
markerEnd :: Lens' c (Maybe ElementRef) Source #
markerMid :: Lens' c (Maybe ElementRef) Source #
markerStart :: Lens' c (Maybe ElementRef) Source #
maskRef :: Lens' c (Maybe ElementRef) Source #
strokeColor :: Lens' c (Maybe Texture) Source #
strokeDashArray :: Lens' c (Maybe [Number]) Source #
strokeLineCap :: Lens' c (Maybe Cap) Source #
strokeLineJoin :: Lens' c (Maybe LineJoin) Source #
strokeMiterLimit :: Lens' c (Maybe Double) Source #
strokeOffset :: Lens' c (Maybe Number) Source #
strokeOpacity :: Lens' c (Maybe Float) Source #
strokeWidth :: Lens' c (Maybe Number) Source #
textAnchor :: Lens' c (Maybe TextAnchor) Source #
Instances
Filters
data FilterElement Source #
Constructors
Instances
data FilterAttributes Source #
Constructors
FilterAttributes | |
Fields
|
Instances
class HasFilterAttributes c where Source #
Minimal complete definition
Methods
filterAttributes :: Lens' c FilterAttributes Source #
filterHeight :: Lens' c (Maybe Number) Source #
filterResult :: Lens' c (Maybe String) Source #
filterWidth :: Lens' c (Maybe Number) Source #
Instances
data FilterSource Source #
Constructors
SourceGraphic | |
SourceAlpha | |
BackgroundImage | |
BackgroundAlpha | |
FillPaint | |
StrokePaint | |
SourceRef String |
Instances
Constructors
Blend | |
Fields
|
Instances
Constructors
Normal | |
Multiply | |
Screen | |
Overlay | |
Darken | |
Lighten | |
ColorDodge | |
ColorBurn | |
HardLight | |
SoftLight | |
Difference | |
Exclusion | |
Hue | |
Saturation | |
Color | |
Luminosity |
Instances
data ConvolveMatrix Source #
Constructors
Instances
data Morphology Source #
Constructors
Morphology | |
Instances
data OperatorType Source #
Constructors
OperatorOver | |
OperatorIn | |
OperatorOut | |
OperatorAtop | |
OperatorXor | |
OperatorLighter | |
OperatorArithmetic |
Instances
data NumberOptionalNumber Source #
Instances
data SpecularLighting Source #
Constructors
SpecularLighting | |
Instances
data DiffuseLighting Source #
Instances
data DropShadow Source #
Constructors
DropShadow | |
Instances
Constructors
Flood | |
Fields |
Instances
Constructors
Tile | |
Fields |
Instances
Constructors
Offset | |
Fields
|
Instances
Constructors
MergeNode | |
Fields |
Instances
Constructors
Merge | |
Fields |
Instances
Constructors
ImageF | |
Instances
data ComponentTransfer Source #
Constructors
ComponentTransfer | |
Instances
Constructors
FuncA | |
Fields
|
Instances
Instances
Eq FuncType Source # | |
Show FuncType Source # | |
Generic FuncType Source # | |
Hashable FuncType Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep FuncType Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep FuncType = D1 ('MetaData "FuncType" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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)))) |
Constructors
FuncR | |
Fields
|
Instances
Constructors
FuncG | |
Fields
|
Instances
Constructors
FuncB | |
Fields
|
Instances
data ColorMatrixType Source #
Constructors
Matrix | |
Saturate | |
HueRotate | |
LuminanceToAlpha |
Instances
data ColorMatrix Source #
Constructors
ColorMatrix | |
Instances
Constructors
Composite | |
Instances
data CompositeOperator Source #
Instances
Constructors
EdgeDuplicate | |
EdgeWrap | |
EdgeNone |
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.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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 #
Constructors
GaussianBlur | |
Instances
data Turbulence Source #
Constructors
Turbulence | |
Instances
data TurbulenceType Source #
Constructors
FractalNoiseType | |
TurbulenceType |
Instances
Eq TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods (==) :: TurbulenceType -> TurbulenceType -> Bool # (/=) :: TurbulenceType -> TurbulenceType -> Bool # | |
Show TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods showsPrec :: Int -> TurbulenceType -> ShowS # show :: TurbulenceType -> String # showList :: [TurbulenceType] -> ShowS # | |
Generic TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal Associated Types type Rep TurbulenceType :: Type -> Type # Methods from :: TurbulenceType -> Rep TurbulenceType x # to :: Rep TurbulenceType x -> TurbulenceType # | |
Hashable TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep TurbulenceType Source # | |
Defined in Graphics.SvgTree.Types.Internal |
data StitchTiles Source #
Instances
Eq StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal | |
Show StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods showsPrec :: Int -> StitchTiles -> ShowS # show :: StitchTiles -> String # showList :: [StitchTiles] -> ShowS # | |
Generic StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal Associated Types type Rep StitchTiles :: Type -> Type # | |
Hashable StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep StitchTiles Source # | |
Defined in Graphics.SvgTree.Types.Internal |
data DisplacementMap Source #
Constructors
Instances
data ChannelSelector Source #
Instances
SVG drawing primitives
Rectangle
Defines a rectangle. Corresponds to `rectangle` svg tag.
Constructors
Rectangle | |
Fields
|
Instances
pattern RectangleTree :: Rectangle -> Tree Source #
rectangleTree :: Rectangle -> Tree Source #
Line
Defines a simple line. Corresponds to the `line` tag.
Constructors
Line | |
Fields
|
Instances
Polygon
Primitive decribing polygon composed of segements. Corresponds to the `polygon` tag
Constructors
Polygon | |
Fields
|
Instances
pattern PolygonTree :: Polygon -> Tree Source #
polygonTree :: Polygon -> Tree Source #
Polyline
This primitive describes an unclosed suite of segments. Correspond to the `polyline` tag.
Constructors
PolyLine | |
Fields
|
Instances
pattern PolyLineTree :: PolyLine -> Tree Source #
polyLineTree :: PolyLine -> Tree Source #
Path
Type mapping the `path` svg tag.
Constructors
Path | |
Fields
|
Instances
Circle
Defines a `circle`.
Constructors
Circle | |
Fields
|
Instances
pattern CircleTree :: Circle -> Tree Source #
circleTree :: Circle -> Tree Source #
Ellipse
Defines an `ellipse`
Constructors
Ellipse | |
Fields
|
Instances
pattern EllipseTree :: Ellipse -> Tree Source #
ellipseTree :: Ellipse -> Tree Source #
Mesh (gradient mesh)
data GradientPathCommand Source #
Description of path used in meshgradient tag
Constructors
GLine !Origin !(Maybe RPoint) | Line to, |
GCurve !Origin !RPoint !RPoint !(Maybe RPoint) | Cubic bezier, |
GClose |
|
Instances
data MeshGradientType Source #
Constructors
GradientBilinear | |
GradientBicubic |
Instances
Eq MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic Methods (==) :: MeshGradientType -> MeshGradientType -> Bool # (/=) :: MeshGradientType -> MeshGradientType -> Bool # | |
Show MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic Methods showsPrec :: Int -> MeshGradientType -> ShowS # show :: MeshGradientType -> String # showList :: [MeshGradientType] -> ShowS # | |
Generic MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic Associated Types type Rep MeshGradientType :: Type -> Type # Methods from :: MeshGradientType -> Rep MeshGradientType x # to :: Rep MeshGradientType x -> MeshGradientType # | |
Hashable MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types.Basic |
data MeshGradient Source #
Defines a `meshgradient` tag.
Constructors
MeshGradient | |
Fields
|
Instances
pattern MeshGradientTree :: MeshGradient -> Tree Source #
meshGradientTree :: MeshGradient -> Tree Source #
newtype MeshGradientRow Source #
Define a `meshrow` tag.
Constructors
MeshGradientRow | |
Fields
|
Instances
newtype MeshGradientPatch Source #
Defines `meshpatch` SVG tag
Constructors
MeshGradientPatch | |
Fields
|
Instances
Image
Defines an `image` tag.
Constructors
Image | |
Fields
|
Instances
Use
Defines an `use` for a named content. Every named content can be reused in the document using this element.
Constructors
Use | |
Fields
|
Instances
Grouping primitives
Group
Defines a SVG group, corresponds to `g` tag.
Constructors
Group | |
Fields
|
Instances
Symbol
pattern SymbolTree :: Group -> Tree Source #
symbolTree :: Group -> Tree Source #
Definitions
pattern DefinitionTree :: Group -> Tree Source #
definitionTree :: Group -> Tree Source #
Filter
Defines the `filter` tag.
Constructors
Filter | |
Instances
pattern FilterTree :: Filter -> Tree Source #
filterTree :: Filter -> Tree Source #
Text related types
Text
Defines the global `text` SVG tag.
Constructors
Text | |
Fields
|
Instances
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 *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
Eq TextAnchor Source # | |
Defined in Graphics.SvgTree.Types.Internal | |
Show TextAnchor Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods showsPrec :: Int -> TextAnchor -> ShowS # show :: TextAnchor -> String # showList :: [TextAnchor] -> ShowS # | |
Generic TextAnchor Source # | |
Defined in Graphics.SvgTree.Types.Internal Associated Types type Rep TextAnchor :: Type -> Type # | |
Hashable TextAnchor Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep TextAnchor Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextAnchor = D1 ('MetaData "TextAnchor" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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
Describes the `textpath` SVG tag.
Constructors
TextPath | |
Fields
|
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 Methods | |
type Rep TextPath Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextPath = D1 ('MetaData "TextPath" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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 #
Describes the content of the spacing
text path
attribute.
Constructors
TextPathSpacingExact | Corresponds to the |
TextPathSpacingAuto | Corresponds to the |
Instances
data TextPathMethod Source #
Describe the content of the method
attribute on
text path.
Constructors
TextPathAlign | Corresponds to the |
TextPathStretch | Corresponds to the |
Instances
Eq TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods (==) :: TextPathMethod -> TextPathMethod -> Bool # (/=) :: TextPathMethod -> TextPathMethod -> Bool # | |
Show TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods showsPrec :: Int -> TextPathMethod -> ShowS # show :: TextPathMethod -> String # showList :: [TextPathMethod] -> ShowS # | |
Generic TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal Associated Types type Rep TextPathMethod :: Type -> Type # Methods from :: TextPathMethod -> Rep TextPathMethod x # to :: Rep TextPathMethod x -> TextPathMethod # | |
Hashable TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types.Internal |
Text span.
data TextSpanContent Source #
Defines the content of a `tspan` tag.
Constructors
SpanText !Text | Raw text |
SpanTextRef !String | Equivalent to a `tref` |
SpanSub !TextSpan | Defines a `tspan` |
Instances
Defines a `tspan` tag.
Constructors
TextSpan | |
Fields
|
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 Methods | |
type Rep TextSpan Source # | |
Defined in Graphics.SvgTree.Types.Internal type Rep TextSpan = D1 ('MetaData "TextSpan" "Graphics.SvgTree.Types.Internal" "reanimate-svg-0.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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])))) |
Constructors
TextInfo | |
Fields
|
Instances
data TextAdjust Source #
Defines the possible values of the lengthAdjust
attribute.
Constructors
TextAdjustSpacing | Value |
TextAdjustSpacingAndGlyphs | Value |
Instances
Eq TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal | |
Show TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods showsPrec :: Int -> TextAdjust -> ShowS # show :: TextAdjust -> String # showList :: [TextAdjust] -> ShowS # | |
Generic TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal Associated Types type Rep TextAdjust :: Type -> Type # | |
Hashable TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep TextAdjust Source # | |
Defined in Graphics.SvgTree.Types.Internal |
Marker definition
Defines the `marker` tag.
Constructors
Marker | |
Fields
|
Instances
pattern MarkerTree :: Marker -> Tree Source #
markerTree :: Marker -> Tree Source #
Defines the content of the markerUnits
attribute
on the Marker.
Constructors
OverflowVisible | Value |
OverflowHidden | Value |
data MarkerOrientation Source #
Defines the orientation, associated to the
orient
attribute on the Marker
Constructors
OrientationAuto | Auto value |
OrientationAngle Coord | Specific angle. |
Instances
data MarkerUnit Source #
Define the content of the markerUnits
attribute
on the Marker.
Constructors
MarkerUnitStrokeWidth | Value |
MarkerUnitUserSpaceOnUse | Value |
Instances
Eq MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal | |
Show MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal Methods showsPrec :: Int -> MarkerUnit -> ShowS # show :: MarkerUnit -> String # showList :: [MarkerUnit] -> ShowS # | |
Generic MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal Associated Types type Rep MarkerUnit :: Type -> Type # | |
Hashable MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types.Internal |
markerUnits :: Lens' Marker (Maybe MarkerUnit) Source #
Gradient definition
data GradientStop Source #
Defines a color stop for the gradients. Represents the `stop` SVG tag.
Constructors
GradientStop | |
Fields
|
Instances
Linear Gradient
data LinearGradient Source #
Defines a `linearGradient` tag.
Constructors
LinearGradient | |
Fields
|
Instances
pattern LinearGradientTree :: LinearGradient -> Tree Source #
Radial Gradient
data RadialGradient Source #
Defines a `radialGradient` tag.
Constructors
RadialGradient | |
Fields
|
Instances
pattern RadialGradientTree :: RadialGradient -> Tree Source #
Pattern definition
Defines a `pattern` tag.
Constructors
Pattern | |
Fields
|
Instances
pattern PatternTree :: Pattern -> Tree Source #
patternTree :: Pattern -> Tree Source #
Mask definition
Defines a SVG `mask` tag.
Constructors
Mask | |
Fields
|
Instances
Clip path definition
Defines a `clipPath` tag.
Constructors
ClipPath | |
Fields
|
Instances
pattern ClipPathTree :: ClipPath -> Tree Source #
clipPathTree :: ClipPath -> Tree Source #
Aspect Ratio description
data PreserveAspectRatio Source #
Describe the content of the preserveAspectRatio attribute.
Constructors
PreserveAspectRatio | |
Fields |
Instances
This type represents the align information of the
preserveAspectRatio
SVGattribute
Constructors
AlignNone |
|
AlignxMinYMin |
|
AlignxMidYMin |
|
AlignxMaxYMin |
|
AlignxMinYMid |
|
AlignxMidYMid |
|
AlignxMaxYMid |
|
AlignxMinYMax |
|
AlignxMidYMax |
|
AlignxMaxYMax |
|
Instances
Eq Alignment Source # | |
Show Alignment Source # | |
Generic Alignment Source # | |
Hashable Alignment Source # | |
Defined in Graphics.SvgTree.Types.Hashable | |
type Rep Alignment Source # | |
Defined in Graphics.SvgTree.Types.Basic type Rep Alignment = D1 ('MetaData "Alignment" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.1-LCJdrqXCg704yy3oKmvLHb" '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))))) |
This type represents the "meet or slice" information
of the preserveAspectRatio
SVG attribute
MISC functions
zipTree :: ([[Tree]] -> Tree) -> Tree -> Tree Source #
Map a tree while propagating context information. The function passed in parameter receives a list representing 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.