Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.SvgTree.Types
Contents
Description
This module define all the types used in the definition of a svg scene.
Most of the types are lensified.
Synopsis
- 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
- toPoint :: Number -> Number -> Point
- serializeNumber :: Number -> String
- serializeTransformation :: Transformation -> String
- serializeTransformations :: [Transformation] -> String
- data Cap
- data LineJoin
- data Tree
- = None
- | UseTree {
- useInformation :: !Use
- useSubTree :: !(Maybe Tree)
- | GroupTree !(Group Tree)
- | SymbolTree !(Symbol Tree)
- | DefinitionTree !(Definitions Tree)
- | FilterTree !Filter
- | PathTree !Path
- | CircleTree !Circle
- | PolyLineTree !PolyLine
- | PolygonTree !Polygon
- | EllipseTree !Ellipse
- | LineTree !Line
- | RectangleTree !Rectangle
- | TextTree !(Maybe TextPath) !Text
- | ImageTree !Image
- | LinearGradientTree !LinearGradient
- | RadialGradientTree !RadialGradient
- | MeshGradientTree !MeshGradient
- | PatternTree !Pattern
- | MarkerTree !Marker
- | MaskTree !Mask
- | ClipPathTree !ClipPath
- data Number
- data Spread
- data Texture
- data Element
- data FillRule
- data FontStyle
- type Dpi = Int
- class WithDefaultSvg a where
- defaultSvg :: a
- data Document = Document {}
- class HasDocument c where
- document :: Lens' c Document
- definitions :: Lens' c (Map String Tree)
- description :: Lens' c String
- documentAspectRatio :: Lens' c PreserveAspectRatio
- documentLocation :: Lens' c FilePath
- elements :: Lens' c [Tree]
- height :: Lens' c (Maybe Number)
- viewBox :: Lens' c (Maybe (Double, Double, Double, Double))
- width :: Lens' c (Maybe Number)
- 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)
- _preRendered :: !(Maybe String)
- 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)
- preRendered :: Lens' c (Maybe String)
- 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
- | FEDropShadow
- | FEFlood
- | FEFuncA
- | FEFuncB
- | FEFuncG
- | FEFuncR
- | FEGaussianBlur GaussianBlur
- | FEImage
- | FEMerge
- | FEMergeNode
- | FEMorphology
- | FEOffset
- | FESpecularLighting
- | FETile
- | FETurbulence
- | FENone
- data FilterAttributes = FilterAttributes {
- _filterHeight :: !(Last Number)
- _filterResult :: !(Maybe String)
- _filterWidth :: !(Last Number)
- _filterX :: !(Last Number)
- _filterY :: !(Last Number)
- class HasFilterAttributes c_asYk where
- filterAttributes :: Lens' c_asYk FilterAttributes
- filterHeight :: Lens' c_asYk (Last Number)
- filterResult :: Lens' c_asYk (Maybe String)
- filterWidth :: Lens' c_asYk (Last Number)
- filterX :: Lens' c_asYk (Last Number)
- filterY :: Lens' c_asYk (Last Number)
- data FilterSource
- data ColorMatrixType
- class HasColorMatrix c where
- data ColorMatrix = ColorMatrix {}
- class HasComposite c where
- composite :: Lens' c Composite
- compositeDrawAttributes :: Lens' c DrawAttributes
- compositeFilterAttr :: Lens' c FilterAttributes
- compositeIn :: Lens' c (Last FilterSource)
- compositeIn2 :: Lens' c (Last FilterSource)
- compositeK1 :: Lens' c Number
- compositeK2 :: Lens' c Number
- compositeK3 :: Lens' c Number
- compositeK4 :: Lens' c Number
- compositeOperator :: Lens' c CompositeOperator
- data Composite = Composite {}
- data CompositeOperator
- data EdgeMode
- class HasGaussianBlur c where
- gaussianBlur :: Lens' c GaussianBlur
- gaussianBlurDrawAttributes :: Lens' c DrawAttributes
- gaussianBlurEdgeMode :: Lens' c EdgeMode
- gaussianBlurFilterAttr :: Lens' c FilterAttributes
- gaussianBlurIn :: Lens' c (Last FilterSource)
- gaussianBlurStdDeviationX :: Lens' c Number
- gaussianBlurStdDeviationY :: Lens' c (Last Number)
- data GaussianBlur = GaussianBlur {}
- data Rectangle = Rectangle {
- _rectDrawAttributes :: !DrawAttributes
- _rectUpperLeftCorner :: !Point
- _rectWidth :: !(Maybe Number)
- _rectHeight :: !(Maybe Number)
- _rectCornerRadius :: !(Maybe Number, Maybe Number)
- class HasRectangle a where
- rectangle :: Lens' a Rectangle
- rectCornerRadius :: Lens' a (Maybe Number, Maybe Number)
- rectDrawAttributes :: Lens' a DrawAttributes
- rectHeight :: Lens' a (Maybe Number)
- rectUpperLeftCorner :: Lens' a Point
- rectWidth :: Lens' a (Maybe Number)
- data Line = Line {}
- class HasLine a where
- line :: Lens' a Line
- lineDrawAttributes :: Lens' a DrawAttributes
- linePoint1 :: Lens' a Point
- linePoint2 :: Lens' a Point
- data Polygon = Polygon {}
- class HasPolygon a where
- polygon :: Lens' a Polygon
- polygonDrawAttributes :: Lens' a DrawAttributes
- polygonPoints :: Lens' a [RPoint]
- data PolyLine = PolyLine {}
- class HasPolyLine a where
- polyLine :: Lens' a PolyLine
- polyLineDrawAttributes :: Lens' a DrawAttributes
- polyLinePoints :: Lens' a [RPoint]
- data Path = Path {}
- class HasPath c_alhy where
- path :: Lens' c_alhy Path
- pathDefinition :: Lens' c_alhy [PathCommand]
- pathDrawAttributes :: Lens' c_alhy DrawAttributes
- data Circle = Circle {}
- class HasCircle a where
- circle :: Lens' a Circle
- circleCenter :: Lens' a Point
- circleDrawAttributes :: Lens' a DrawAttributes
- circleRadius :: Lens' a Number
- data Ellipse = Ellipse {}
- class HasEllipse c_amWt where
- ellipse :: Lens' c_amWt Ellipse
- ellipseCenter :: Lens' c_amWt Point
- ellipseDrawAttributes :: Lens' c_amWt DrawAttributes
- ellipseXRadius :: Lens' c_amWt Number
- ellipseYRadius :: Lens' c_amWt Number
- data GradientPathCommand
- data MeshGradientType
- data MeshGradient = MeshGradient {}
- class HasMeshGradient c_anxG where
- meshGradient :: Lens' c_anxG MeshGradient
- meshGradientDrawAttributes :: Lens' c_anxG DrawAttributes
- meshGradientRows :: Lens' c_anxG [MeshGradientRow]
- meshGradientTransform :: Lens' c_anxG [Transformation]
- meshGradientType :: Lens' c_anxG MeshGradientType
- meshGradientUnits :: Lens' c_anxG CoordinateUnits
- meshGradientX :: Lens' c_anxG Number
- meshGradientY :: Lens' c_anxG Number
- data MeshGradientRow = MeshGradientRow {}
- class HasMeshGradientRow c_antr where
- meshGradientRow :: Lens' c_antr MeshGradientRow
- meshGradientRowPatches :: Lens' c_antr [MeshGradientPatch]
- data MeshGradientPatch = MeshGradientPatch {}
- class HasMeshGradientPatch c_annx where
- meshGradientPatch :: Lens' c_annx MeshGradientPatch
- meshGradientPatchStops :: Lens' c_annx [GradientStop]
- data Image = Image {}
- class HasImage c_anI7 where
- image :: Lens' c_anI7 Image
- imageAspectRatio :: Lens' c_anI7 PreserveAspectRatio
- imageCornerUpperLeft :: Lens' c_anI7 Point
- imageDrawAttributes :: Lens' c_anI7 DrawAttributes
- imageHeight :: Lens' c_anI7 Number
- imageHref :: Lens' c_anI7 String
- imageWidth :: Lens' c_anI7 Number
- data Use = Use {}
- class HasUse c_anR3 where
- data Group a = Group {
- _groupDrawAttributes :: !DrawAttributes
- _groupChildren :: ![a]
- _groupViewBox :: !(Maybe (Double, Double, Double, Double))
- _groupAspectRatio :: !PreserveAspectRatio
- class HasGroup g a | g -> a where
- group :: Lens' g (Group a)
- groupAspectRatio :: Lens' g PreserveAspectRatio
- groupChildren :: Lens' g [a]
- groupDrawAttributes :: Lens' g DrawAttributes
- groupViewBox :: Lens' g (Maybe (Double, Double, Double, Double))
- newtype Symbol a = Symbol {
- _groupOfSymbol :: Group a
- groupOfSymbol :: Lens (Symbol s) (Symbol t) (Group s) (Group t)
- newtype Definitions a = Definitions {
- _groupOfDefinitions :: Group a
- groupOfDefinitions :: Lens (Definitions s) (Definitions t) (Group s) (Group t)
- data Filter = Filter {}
- filterChildren :: Lens' Filter [FilterElement]
- data Text = Text {
- _textAdjust :: !TextAdjust
- _textRoot :: !TextSpan
- class HasText c_aorD where
- text :: Lens' c_aorD Text
- textAdjust :: Lens' c_aorD TextAdjust
- textRoot :: Lens' c_aorD TextSpan
- data TextAnchor
- textAt :: Point -> Text -> Text
- data TextPath = TextPath {}
- class HasTextPath c where
- data TextPathSpacing
- data TextPathMethod
- data TextSpanContent
- data TextSpan = TextSpan {}
- class HasTextSpan c_aobD where
- textSpan :: Lens' c_aobD TextSpan
- spanContent :: Lens' c_aobD [TextSpanContent]
- spanDrawAttributes :: Lens' c_aobD DrawAttributes
- spanInfo :: Lens' c_aobD TextInfo
- data TextInfo = TextInfo {
- _textInfoX :: ![Number]
- _textInfoY :: ![Number]
- _textInfoDX :: ![Number]
- _textInfoDY :: ![Number]
- _textInfoRotate :: ![Double]
- _textInfoLength :: !(Maybe Number)
- class HasTextInfo c_ao0m where
- 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]
- data Overflow
- data MarkerOrientation
- data MarkerUnit
- class HasMarker c_aoKc where
- marker :: Lens' c_aoKc Marker
- markerAspectRatio :: Lens' c_aoKc PreserveAspectRatio
- markerDrawAttributes :: Lens' c_aoKc DrawAttributes
- markerElements :: Lens' c_aoKc [Tree]
- markerHeight :: Lens' c_aoKc (Maybe Number)
- markerOrient :: Lens' c_aoKc (Maybe MarkerOrientation)
- markerOverflow :: Lens' c_aoKc (Maybe Overflow)
- markerRefPoint :: Lens' c_aoKc (Number, Number)
- markerUnits :: Lens' c_aoKc (Maybe MarkerUnit)
- markerViewBox :: Lens' c_aoKc (Maybe (Double, Double, Double, Double))
- markerWidth :: Lens' c_aoKc (Maybe Number)
- data GradientStop = GradientStop {}
- class HasGradientStop c_anhM where
- gradientStop :: Lens' c_anhM GradientStop
- gradientColor :: Lens' c_anhM PixelRGBA8
- gradientOffset :: Lens' c_anhM Float
- gradientOpacity :: Lens' c_anhM (Maybe Float)
- gradientPath :: Lens' c_anhM (Maybe GradientPathCommand)
- data LinearGradient = LinearGradient {}
- class HasLinearGradient c_apmJ where
- linearGradient :: Lens' c_apmJ LinearGradient
- linearGradientDrawAttributes :: Lens' c_apmJ DrawAttributes
- linearGradientSpread :: Lens' c_apmJ Spread
- linearGradientStart :: Lens' c_apmJ Point
- linearGradientStop :: Lens' c_apmJ Point
- linearGradientStops :: Lens' c_apmJ [GradientStop]
- linearGradientTransform :: Lens' c_apmJ [Transformation]
- linearGradientUnits :: Lens' c_apmJ CoordinateUnits
- data RadialGradient = RadialGradient {
- _radialGradientDrawAttributes :: DrawAttributes
- _radialGradientUnits :: CoordinateUnits
- _radialGradientCenter :: Point
- _radialGradientRadius :: Number
- _radialGradientFocusX :: Maybe Number
- _radialGradientFocusY :: Maybe Number
- _radialGradientSpread :: Spread
- _radialGradientTransform :: [Transformation]
- _radialGradientStops :: [GradientStop]
- class HasRadialGradient c_apwt where
- radialGradient :: Lens' c_apwt RadialGradient
- radialGradientDrawAttributes :: Lens' c_apwt DrawAttributes
- radialGradientCenter :: Lens' c_apwt Point
- radialGradientFocusX :: Lens' c_apwt (Maybe Number)
- radialGradientFocusY :: Lens' c_apwt (Maybe Number)
- radialGradientRadius :: Lens' c_apwt Number
- radialGradientSpread :: Lens' c_apwt Spread
- radialGradientStops :: Lens' c_apwt [GradientStop]
- radialGradientTransform :: Lens' c_apwt [Transformation]
- radialGradientUnits :: Lens' c_apwt CoordinateUnits
- 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])
- class HasPattern c_aq6G where
- pattern :: Lens' c_aq6G Pattern
- patternAspectRatio :: Lens' c_aq6G PreserveAspectRatio
- patternDrawAttributes :: Lens' c_aq6G DrawAttributes
- patternElements :: Lens' c_aq6G [Tree]
- patternHeight :: Lens' c_aq6G Number
- patternHref :: Lens' c_aq6G String
- patternPos :: Lens' c_aq6G Point
- patternTransform :: Lens' c_aq6G (Maybe [Transformation])
- patternUnit :: Lens' c_aq6G CoordinateUnits
- patternViewBox :: Lens' c_aq6G (Maybe (Double, Double, Double, Double))
- patternWidth :: Lens' c_aq6G Number
- data Mask = Mask {}
- class HasMask c_apHI where
- mask :: Lens' c_apHI Mask
- maskContent :: Lens' c_apHI [Tree]
- maskContentUnits :: Lens' c_apHI CoordinateUnits
- maskDrawAttributes :: Lens' c_apHI DrawAttributes
- maskHeight :: Lens' c_apHI Number
- maskPosition :: Lens' c_apHI Point
- maskUnits :: Lens' c_apHI CoordinateUnits
- maskWidth :: Lens' c_apHI Number
- data ClipPath = ClipPath {}
- class HasClipPath c_apZq where
- clipPath :: Lens' c_apZq ClipPath
- clipPathContent :: Lens' c_apZq [Tree]
- clipPathDrawAttributes :: Lens' c_apZq DrawAttributes
- clipPathUnits :: Lens' c_apZq CoordinateUnits
- data PreserveAspectRatio = PreserveAspectRatio {}
- data Alignment
- data MeetSlice
- class HasPreserveAspectRatio a where
- isPathArc :: PathCommand -> Bool
- isPathWithArc :: Foldable f => f PathCommand -> Bool
- nameOfTree :: Tree -> Text
- zipTree :: ([[Tree]] -> Tree) -> Tree -> Tree
- mapTree :: (Tree -> Tree) -> Tree -> Tree
- foldTree :: (a -> Tree -> a) -> a -> Tree -> a
- 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.
Constructors
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.
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)] | Eliptical arc, |
EndPath | Close the path, |
Instances
Eq PathCommand Source # | |
Defined in Graphics.SvgTree.Types | |
Show PathCommand Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> PathCommand -> ShowS # show :: PathCommand -> String # showList :: [PathCommand] -> ShowS # |
data Transformation Source #
Describe the content of the transformation
attribute.
see _transform
and transform
.
Constructors
TransformMatrix !Coord !Coord !Coord !Coord !Coord !Coord | Directly encode the translation matrix. |
Translate !Double !Double | Translation along a vector |
Scale !Double !(Maybe Double) | Scaling on both axis or on X axis and Y axis. |
Rotate !Double !(Maybe (Double, Double)) | Rotation around `(0, 0)` or around an optional point. |
SkewX !Double | Skew transformation along the X axis. |
SkewY !Double | Skew transformation along the Y axis. |
TransformUnknown | Unkown transformation, like identity. |
Instances
Eq Transformation Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: Transformation -> Transformation -> Bool # (/=) :: Transformation -> Transformation -> Bool # | |
Show Transformation Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> Transformation -> ShowS # show :: Transformation -> String # showList :: [Transformation] -> ShowS # |
data ElementRef Source #
Correspond to the possible values of the
the attributes which are either none
or
`url(#elem)`
Instances
Eq ElementRef Source # | |
Defined in Graphics.SvgTree.Types | |
Show ElementRef Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> ElementRef -> ShowS # show :: ElementRef -> String # showList :: [ElementRef] -> ShowS # |
data CoordinateUnits Source #
Define 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 Methods (==) :: CoordinateUnits -> CoordinateUnits -> Bool # (/=) :: CoordinateUnits -> CoordinateUnits -> Bool # | |
Show CoordinateUnits Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> CoordinateUnits -> ShowS # show :: CoordinateUnits -> String # showList :: [CoordinateUnits] -> ShowS # |
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
Define the possible values of the `stroke-linejoin`
attribute.
see _strokeLineJoin
Main type for the scene description, reorient to specific type describing each tag.
Constructors
Instances
Encode complex number possibly dependant to the current render size.
Constructors
Num Double | Simple coordinate in current user coordinate. |
Px Double | With suffix "px" |
Em Double | Number relative to the current font size. |
Percent Double | Number relative to the current viewport size. |
Pc Double | |
Mm Double | Number in millimeters, relative to DPI. |
Cm Double | Number in centimeters, relative to DPI. |
Point Double | Number in points, relative to DPI. |
Inches Double | Number in inches, relative to DPI. |
Define the possible values for the spreadMethod
values used for the gradient definitions.
Constructors
SpreadRepeat |
|
SpreadPad |
|
SpreadReflect | `reflect value` |
Describe the different value 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 |
Sum types helping keeping track of all the namable elemens in a SVG document.
Constructors
Describe the possile filling algorithms. Map the values of the `fill-rule` attributes.
Constructors
FillEvenOdd | Correspond to the |
FillNonZero | Correspond to the |
Classify the font style, used to search a matching font in the FontCache.
Constructors
FontStyleNormal | |
FontStyleItalic | |
FontStyleOblique |
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
Represent a full svg document with style, geometry and named elements.
Constructors
Document | |
Fields
|
Instances
Show Document Source # | |
HasDocument Document Source # | |
Defined in Graphics.SvgTree.Types Methods document :: Lens' Document Document Source # definitions :: Lens' Document (Map String Tree) Source # description :: Lens' Document String Source # documentAspectRatio :: Lens' Document PreserveAspectRatio Source # documentLocation :: Lens' Document FilePath Source # elements :: Lens' Document [Tree] Source # height :: Lens' Document (Maybe Number) Source # viewBox :: Lens' Document (Maybe (Double, Double, Double, Double)) Source # |
class HasDocument c where Source #
Lenses associated to a SVG document.
Minimal complete definition
Methods
document :: Lens' c Document Source #
definitions :: Lens' c (Map String Tree) Source #
description :: Lens' c String Source #
documentAspectRatio :: Lens' c PreserveAspectRatio Source #
documentLocation :: Lens' c FilePath Source #
elements :: Lens' c [Tree] Source #
height :: Lens' c (Maybe Number) Source #
viewBox :: Lens' c (Maybe (Double, Double, Double, Double)) Source #
Instances
HasDocument Document Source # | |
Defined in Graphics.SvgTree.Types Methods document :: Lens' Document Document Source # definitions :: Lens' Document (Map String Tree) Source # description :: Lens' Document String Source # documentAspectRatio :: Lens' Document PreserveAspectRatio Source # documentLocation :: Lens' Document FilePath Source # elements :: Lens' Document [Tree] Source # height :: Lens' Document (Maybe Number) Source # viewBox :: Lens' Document (Maybe (Double, Double, Double, Double)) Source # |
documentSize :: Dpi -> Document -> (Int, Int) Source #
Calculate the document size in function of the different available attributes in the document.
Drawing attributes
data DrawAttributes Source #
This type define how to draw any primitives, which color to use, how to stroke the primitives and the potential transformations to use.
All these attributes are propagated to the children.
Constructors
DrawAttributes | |
Fields
|
Instances
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 (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 #
preRendered :: Lens' c (Maybe String) 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 #
Constructors
Instances
Eq FilterElement Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: FilterElement -> FilterElement -> Bool # (/=) :: FilterElement -> FilterElement -> Bool # | |
Show FilterElement Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> FilterElement -> ShowS # show :: FilterElement -> String # showList :: [FilterElement] -> ShowS # | |
WithDefaultSvg FilterElement Source # | |
Defined in Graphics.SvgTree.Types Methods | |
HasFilterAttributes FilterElement Source # | |
Defined in Graphics.SvgTree.Types |
data FilterAttributes Source #
Constructors
FilterAttributes | |
Fields
|
Instances
Eq FilterAttributes Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: FilterAttributes -> FilterAttributes -> Bool # (/=) :: FilterAttributes -> FilterAttributes -> Bool # | |
Show FilterAttributes Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> FilterAttributes -> ShowS # show :: FilterAttributes -> String # showList :: [FilterAttributes] -> ShowS # | |
WithDefaultSvg FilterAttributes Source # | |
Defined in Graphics.SvgTree.Types Methods | |
HasFilterAttributes FilterAttributes Source # | |
Defined in Graphics.SvgTree.Types Methods filterAttributes :: Lens' FilterAttributes FilterAttributes Source # filterHeight :: Lens' FilterAttributes (Last Number) Source # filterResult :: Lens' FilterAttributes (Maybe String) Source # filterWidth :: Lens' FilterAttributes (Last Number) Source # |
class HasFilterAttributes c_asYk where Source #
Lenses for the FilterAttributes type.
Minimal complete definition
Methods
filterAttributes :: Lens' c_asYk FilterAttributes Source #
filterHeight :: Lens' c_asYk (Last Number) Source #
filterResult :: Lens' c_asYk (Maybe String) Source #
filterWidth :: Lens' c_asYk (Last Number) Source #
Instances
data FilterSource Source #
Constructors
SourceGraphic | |
SourceAlpha | |
BackgroundImage | |
BackgroundAlpha | |
FillPaint | |
StrokePaint | |
SourceRef String |
Instances
Eq FilterSource Source # | |
Defined in Graphics.SvgTree.Types | |
Show FilterSource Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> FilterSource -> ShowS # show :: FilterSource -> String # showList :: [FilterSource] -> ShowS # |
data ColorMatrixType Source #
Constructors
Matrix | |
Saturate | |
HueRotate | |
LuminanceToAlpha |
Instances
Eq ColorMatrixType Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: ColorMatrixType -> ColorMatrixType -> Bool # (/=) :: ColorMatrixType -> ColorMatrixType -> Bool # | |
Show ColorMatrixType Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> ColorMatrixType -> ShowS # show :: ColorMatrixType -> String # showList :: [ColorMatrixType] -> ShowS # |
class HasColorMatrix c where Source #
Minimal complete definition
Methods
colorMatrix :: Lens' c ColorMatrix Source #
colorMatrixDrawAttributes :: Lens' c DrawAttributes Source #
colorMatrixFilterAttr :: Lens' c FilterAttributes Source #
colorMatrixIn :: Lens' c (Last FilterSource) Source #
colorMatrixType :: Lens' c ColorMatrixType Source #
colorMatrixValues :: Lens' c String Source #
Instances
data ColorMatrix Source #
Constructors
ColorMatrix | |
Instances
class HasComposite c where Source #
Minimal complete definition
Methods
composite :: Lens' c Composite Source #
compositeDrawAttributes :: Lens' c DrawAttributes Source #
compositeFilterAttr :: Lens' c FilterAttributes Source #
compositeIn :: Lens' c (Last FilterSource) Source #
compositeIn2 :: Lens' c (Last FilterSource) Source #
compositeK1 :: Lens' c Number Source #
compositeK2 :: Lens' c Number Source #
compositeK3 :: Lens' c Number Source #
compositeK4 :: Lens' c Number Source #
Instances
Constructors
Composite | |
Instances
data CompositeOperator Source #
Instances
Eq CompositeOperator Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: CompositeOperator -> CompositeOperator -> Bool # (/=) :: CompositeOperator -> CompositeOperator -> Bool # | |
Show CompositeOperator Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> CompositeOperator -> ShowS # show :: CompositeOperator -> String # showList :: [CompositeOperator] -> ShowS # |
class HasGaussianBlur c where Source #
Minimal complete definition
Methods
gaussianBlur :: Lens' c GaussianBlur Source #
gaussianBlurDrawAttributes :: Lens' c DrawAttributes Source #
gaussianBlurEdgeMode :: Lens' c EdgeMode Source #
gaussianBlurFilterAttr :: Lens' c FilterAttributes Source #
gaussianBlurIn :: Lens' c (Last FilterSource) Source #
Instances
data GaussianBlur Source #
Constructors
GaussianBlur | |
Instances
SVG drawing primitives
Rectangle
Define a rectangle. Correspond to `<rectangle>` svg tag.
Constructors
Rectangle | |
Fields
|
Instances
class HasRectangle a where Source #
Lenses for the Rectangle type.
Minimal complete definition
Methods
rectangle :: Lens' a Rectangle Source #
rectCornerRadius :: Lens' a (Maybe Number, Maybe Number) Source #
rectDrawAttributes :: Lens' a DrawAttributes Source #
rectHeight :: Lens' a (Maybe Number) Source #
rectUpperLeftCorner :: Lens' a Point Source #
Instances
HasRectangle Rectangle Source # | |
Defined in Graphics.SvgTree.Types |
Line
Define a simple line. Correspond to the `<line>` tag.
Constructors
Line | |
Fields
|
Instances
class HasLine a where Source #
Lenses for the Line type.
Minimal complete definition
Methods
lineDrawAttributes :: Lens' a DrawAttributes Source #
linePoint1 :: Lens' a Point Source #
linePoint2 :: Lens' a Point Source #
Polygon
Primitive decriving polygon composed of segements. Correspond to the `<polygon>` tag
Constructors
Polygon | |
Fields
|