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)
- | 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_aqpq where
- document :: Lens' c_aqpq Document
- definitions :: Lens' c_aqpq (Map String Tree)
- description :: Lens' c_aqpq String
- documentLocation :: Lens' c_aqpq FilePath
- elements :: Lens' c_aqpq [Tree]
- height :: Lens' c_aqpq (Maybe Number)
- styleRules :: Lens' c_aqpq [CssRule]
- viewBox :: Lens' c_aqpq (Maybe (Double, Double, Double, Double))
- width :: Lens' c_aqpq (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)
- class HasDrawAttributes a where
- drawAttributes :: Lens' a DrawAttributes
- attrClass :: Lens' a [Text]
- attrId :: Lens' a (Maybe String)
- clipPathRef :: Lens' a (Last ElementRef)
- clipRule :: Lens' a (Last FillRule)
- fillColor :: Lens' a (Last Texture)
- fillOpacity :: Lens' a (Maybe Float)
- fillRule :: Lens' a (Last FillRule)
- fontFamily :: Lens' a (Last [String])
- fontSize :: Lens' a (Last Number)
- fontStyle :: Lens' a (Last FontStyle)
- groupOpacity :: Lens' a (Maybe Float)
- markerEnd :: Lens' a (Last ElementRef)
- markerMid :: Lens' a (Last ElementRef)
- markerStart :: Lens' a (Last ElementRef)
- maskRef :: Lens' a (Last ElementRef)
- strokeColor :: Lens' a (Last Texture)
- strokeDashArray :: Lens' a (Last [Number])
- strokeLineCap :: Lens' a (Last Cap)
- strokeLineJoin :: Lens' a (Last LineJoin)
- strokeMiterLimit :: Lens' a (Last Double)
- strokeOffset :: Lens' a (Last Number)
- strokeOpacity :: Lens' a (Maybe Float)
- strokeWidth :: Lens' a (Last Number)
- textAnchor :: Lens' a (Last TextAnchor)
- transform :: Lens' a (Maybe [Transformation])
- class WithDrawAttributes a where
- drawAttr :: Lens' a DrawAttributes
- 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 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_aojU where
- textPath :: Lens' c_aojU TextPath
- textPathData :: Lens' c_aojU [PathCommand]
- textPathMethod :: Lens' c_aojU TextPathMethod
- textPathName :: Lens' c_aojU String
- textPathSpacing :: Lens' c_aojU TextPathSpacing
- textPathStartOffset :: Lens' c_aojU Number
- 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
Eq Tree Source # | |
Show Tree Source # | |
CssMatcheable Tree Source # | |
WithDefaultSvg Tree Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Tree Source # | |
WithDrawAttributes Tree Source # | |
Defined in Graphics.SvgTree.Types |
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 | |
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 # documentLocation :: Lens' Document FilePath Source # elements :: Lens' Document [Tree] Source # height :: Lens' Document (Maybe Number) Source # styleRules :: Lens' Document [CssRule] Source # viewBox :: Lens' Document (Maybe (Double, Double, Double, Double)) Source # |
class HasDocument c_aqpq where Source #
Lenses associated to a SVG document.
Minimal complete definition
Methods
document :: Lens' c_aqpq Document Source #
definitions :: Lens' c_aqpq (Map String Tree) Source #
description :: Lens' c_aqpq String Source #
documentLocation :: Lens' c_aqpq FilePath Source #
elements :: Lens' c_aqpq [Tree] Source #
height :: Lens' c_aqpq (Maybe Number) Source #
styleRules :: Lens' c_aqpq [CssRule] Source #
viewBox :: Lens' c_aqpq (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 # documentLocation :: Lens' Document FilePath Source # elements :: Lens' Document [Tree] Source # height :: Lens' Document (Maybe Number) Source # styleRules :: Lens' Document [CssRule] 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 a where Source #
Lenses for the DrawAttributes type.
Minimal complete definition
Methods
drawAttributes :: Lens' a DrawAttributes Source #
attrClass :: Lens' a [Text] Source #
attrId :: Lens' a (Maybe String) Source #
clipPathRef :: Lens' a (Last ElementRef) Source #
clipRule :: Lens' a (Last FillRule) Source #
fillColor :: Lens' a (Last Texture) Source #
fillOpacity :: Lens' a (Maybe Float) Source #
fillRule :: Lens' a (Last FillRule) Source #
fontFamily :: Lens' a (Last [String]) Source #
fontSize :: Lens' a (Last Number) Source #
fontStyle :: Lens' a (Last FontStyle) Source #
groupOpacity :: Lens' a (Maybe Float) Source #
markerEnd :: Lens' a (Last ElementRef) Source #
markerMid :: Lens' a (Last ElementRef) Source #
markerStart :: Lens' a (Last ElementRef) Source #
maskRef :: Lens' a (Last ElementRef) Source #
strokeColor :: Lens' a (Last Texture) Source #
strokeDashArray :: Lens' a (Last [Number]) Source #
strokeLineCap :: Lens' a (Last Cap) Source #
strokeLineJoin :: Lens' a (Last LineJoin) Source #
strokeMiterLimit :: Lens' a (Last Double) Source #
strokeOffset :: Lens' a (Last Number) Source #
strokeOpacity :: Lens' a (Maybe Float) Source #
strokeWidth :: Lens' a (Last Number) Source #
textAnchor :: Lens' a (Last TextAnchor) Source #
Instances
class WithDrawAttributes a where Source #
Class helping find the drawing attributes for all the SVG attributes.
Instances
SVG drawing primitives
Rectangle
Define a rectangle. Correspond to `<rectangle>` svg tag.
Constructors
Rectangle | |
Fields
|
Instances
Eq Rectangle Source # | |
Show Rectangle Source # | |
HasRectangle Rectangle Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg Rectangle Source # | |
Defined in Graphics.SvgTree.Types Methods | |
WithDrawAttributes Rectangle Source # | |
Defined in Graphics.SvgTree.Types |
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
Eq Line Source # | |
Show Line Source # | |
HasLine Line Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg Line Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Line Source # | |
WithDrawAttributes Line Source # | |
Defined in Graphics.SvgTree.Types |
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
|
Instances
Eq Polygon Source # | |
Show Polygon Source # | |
HasPolygon Polygon Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg Polygon Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Polygon Source # | |
WithDrawAttributes Polygon Source # | |
Defined in Graphics.SvgTree.Types |
class HasPolygon a where Source #
Lenses for the Polygon type
Minimal complete definition
Methods
polygon :: Lens' a Polygon Source #
polygonDrawAttributes :: Lens' a DrawAttributes Source #
polygonPoints :: Lens' a [RPoint] Source #
Instances
HasPolygon Polygon Source # | |
Defined in Graphics.SvgTree.Types |
Polyline
This primitive describe an unclosed suite of segments. Correspond to the `<polyline>` tag.
Constructors
PolyLine | |
Fields
|
Instances
Eq PolyLine Source # | |
Show PolyLine Source # | |
HasPolyLine PolyLine Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg PolyLine Source # | |
Defined in Graphics.SvgTree.Types Methods | |
WithDrawAttributes PolyLine Source # | |
Defined in Graphics.SvgTree.Types |
class HasPolyLine a where Source #
Lenses for the PolyLine type.
Minimal complete definition
Methods
polyLine :: Lens' a PolyLine Source #
polyLineDrawAttributes :: Lens' a DrawAttributes Source #
polyLinePoints :: Lens' a [RPoint] Source #
Instances
HasPolyLine PolyLine Source # | |
Defined in Graphics.SvgTree.Types |
Path
Type mapping the `<path>` svg tag.
Constructors
Path | |
Fields
|
Instances
Eq Path Source # | |
Show Path Source # | |
HasPath Path Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg Path Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Path Source # | |
WithDrawAttributes Path Source # | |
Defined in Graphics.SvgTree.Types |
class HasPath c_alhy where Source #
Lenses for the Path type
Minimal complete definition
Methods
path :: Lens' c_alhy Path Source #
pathDefinition :: Lens' c_alhy [PathCommand] Source #
pathDrawAttributes :: Lens' c_alhy DrawAttributes Source #
Circle
Define a `<circle>`.
Constructors
Circle | |
Fields
|
Instances
Eq Circle Source # | |
Show Circle Source # | |
HasCircle Circle Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg Circle Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Circle Source # | |
WithDrawAttributes Circle Source # | |
Defined in Graphics.SvgTree.Types |
class HasCircle a where Source #
Lenses for the Circle type.
Minimal complete definition
Methods
circle :: Lens' a Circle Source #
circleCenter :: Lens' a Point Source #
circleDrawAttributes :: Lens' a DrawAttributes Source #
circleRadius :: Lens' a Number Source #
Ellipse
Define an `<ellipse>`
Constructors
Ellipse | |
Fields
|
Instances
Eq Ellipse Source # | |
Show Ellipse Source # | |
HasEllipse Ellipse Source # | |
WithDefaultSvg Ellipse Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Ellipse Source # | |
WithDrawAttributes Ellipse Source # | |
Defined in Graphics.SvgTree.Types |
class HasEllipse c_amWt where Source #
Lenses for the ellipse type.
Minimal complete definition
Methods
ellipse :: Lens' c_amWt Ellipse Source #
ellipseCenter :: Lens' c_amWt Point Source #
ellipseDrawAttributes :: Lens' c_amWt DrawAttributes Source #
ellipseXRadius :: Lens' c_amWt Number Source #
ellipseYRadius :: Lens' c_amWt Number Source #
Instances
HasEllipse Ellipse 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
Eq GradientPathCommand Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: GradientPathCommand -> GradientPathCommand -> Bool # (/=) :: GradientPathCommand -> GradientPathCommand -> Bool # | |
Show GradientPathCommand Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> GradientPathCommand -> ShowS # show :: GradientPathCommand -> String # showList :: [GradientPathCommand] -> ShowS # |
data MeshGradientType Source #
Constructors
GradientBilinear | |
GradientBicubic |
Instances
Eq MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: MeshGradientType -> MeshGradientType -> Bool # (/=) :: MeshGradientType -> MeshGradientType -> Bool # | |
Show MeshGradientType Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> MeshGradientType -> ShowS # show :: MeshGradientType -> String # showList :: [MeshGradientType] -> ShowS # |
data MeshGradient Source #
Define a `<meshgradient>` tag.
Constructors
MeshGradient | |
Fields
|
Instances
Eq MeshGradient Source # | |
Defined in Graphics.SvgTree.Types | |
Show MeshGradient Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> MeshGradient -> ShowS # show :: MeshGradient -> String # showList :: [MeshGradient] -> ShowS # | |
HasMeshGradient MeshGradient Source # | |
Defined in Graphics.SvgTree.Types Methods meshGradient :: Lens' MeshGradient MeshGradient Source # meshGradientDrawAttributes :: Lens' MeshGradient DrawAttributes Source # meshGradientRows :: Lens' MeshGradient [MeshGradientRow] Source # meshGradientTransform :: Lens' MeshGradient [Transformation] Source # meshGradientType :: Lens' MeshGradient MeshGradientType Source # meshGradientUnits :: Lens' MeshGradient CoordinateUnits Source # | |
WithDefaultSvg MeshGradient Source # | |
Defined in Graphics.SvgTree.Types Methods | |
WithDrawAttributes MeshGradient Source # | |
Defined in Graphics.SvgTree.Types Methods |
class HasMeshGradient c_anxG where Source #
Minimal complete definition
Methods
meshGradient :: Lens' c_anxG MeshGradient Source #
meshGradientDrawAttributes :: Lens' c_anxG DrawAttributes Source #
meshGradientRows :: Lens' c_anxG [MeshGradientRow] Source #
meshGradientTransform :: Lens' c_anxG [Transformation] Source #
meshGradientType :: Lens' c_anxG MeshGradientType Source #
meshGradientUnits :: Lens' c_anxG CoordinateUnits Source #
meshGradientX :: Lens' c_anxG Number Source #
meshGradientY :: Lens' c_anxG Number Source #
Instances
data MeshGradientRow Source #
Define a `<meshrow>` tag.
Constructors
MeshGradientRow | |
Fields
|
Instances
Eq MeshGradientRow Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: MeshGradientRow -> MeshGradientRow -> Bool # (/=) :: MeshGradientRow -> MeshGradientRow -> Bool # | |
Show MeshGradientRow Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> MeshGradientRow -> ShowS # show :: MeshGradientRow -> String # showList :: [MeshGradientRow] -> ShowS # | |
HasMeshGradientRow MeshGradientRow Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg MeshGradientRow Source # | |
Defined in Graphics.SvgTree.Types Methods |
class HasMeshGradientRow c_antr where Source #
Minimal complete definition
Methods
meshGradientRow :: Lens' c_antr MeshGradientRow Source #
meshGradientRowPatches :: Lens' c_antr [MeshGradientPatch] Source #
Instances
HasMeshGradientRow MeshGradientRow Source # | |
Defined in Graphics.SvgTree.Types |
data MeshGradientPatch Source #
Define `<meshpatch>` SVG tag
Constructors
MeshGradientPatch | |
Fields
|
Instances
Eq MeshGradientPatch Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: MeshGradientPatch -> MeshGradientPatch -> Bool # (/=) :: MeshGradientPatch -> MeshGradientPatch -> Bool # | |
Show MeshGradientPatch Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> MeshGradientPatch -> ShowS # show :: MeshGradientPatch -> String # showList :: [MeshGradientPatch] -> ShowS # | |
HasMeshGradientPatch MeshGradientPatch Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg MeshGradientPatch Source # | |
Defined in Graphics.SvgTree.Types Methods |
class HasMeshGradientPatch c_annx where Source #
Minimal complete definition
Methods
meshGradientPatch :: Lens' c_annx MeshGradientPatch Source #
meshGradientPatchStops :: Lens' c_annx [GradientStop] Source #
Instances
HasMeshGradientPatch MeshGradientPatch Source # | |
Defined in Graphics.SvgTree.Types |
Image
Define an `<image>` tag.
Constructors
Image | |
Fields
|
Instances
Eq Image Source # | |
Show Image Source # | |
HasImage Image Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg Image Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Image Source # | |
WithDrawAttributes Image Source # | |
Defined in Graphics.SvgTree.Types |
class HasImage c_anI7 where Source #
Lenses for the Image type.
Minimal complete definition
Methods
image :: Lens' c_anI7 Image Source #
imageAspectRatio :: Lens' c_anI7 PreserveAspectRatio Source #
imageCornerUpperLeft :: Lens' c_anI7 Point Source #
imageDrawAttributes :: Lens' c_anI7 DrawAttributes Source #
imageHeight :: Lens' c_anI7 Number Source #
imageHref :: Lens' c_anI7 String Source #
imageWidth :: Lens' c_anI7 Number Source #
Instances
HasImage Image Source # | |
Defined in Graphics.SvgTree.Types |
Use
Define an `<use>` for a named content. Every named content can be reused in the document using this element.
Constructors
Use | |
Fields
|
class HasUse c_anR3 where Source #
Lenses for the Use type.
Minimal complete definition
Methods
use :: Lens' c_anR3 Use Source #
useBase :: Lens' c_anR3 Point Source #
useDrawAttributes :: Lens' c_anR3 DrawAttributes Source #
useHeight :: Lens' c_anR3 (Maybe Number) Source #
Grouping primitives
Group
Define a SVG group, corresponding `<g>` tag.
Constructors
Group | |
Fields
|
Instances
Eq a => Eq (Group a) Source # | |
Show a => Show (Group a) Source # | |
WithDefaultSvg (Group a) Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Group a Source # | |
WithDrawAttributes (Group a) Source # | |
Defined in Graphics.SvgTree.Types | |
HasGroup (Group a) a Source # | |
Defined in Graphics.SvgTree.Types Methods group :: Lens' (Group a) (Group a) Source # groupAspectRatio :: Lens' (Group a) PreserveAspectRatio Source # groupChildren :: Lens' (Group a) [a] Source # groupDrawAttributes :: Lens' (Group a) DrawAttributes Source # groupViewBox :: Lens' (Group a) (Maybe (Double, Double, Double, Double)) Source # |
class HasGroup g a | g -> a where Source #
Lenses associated to the Group type.
Minimal complete definition
Methods
group :: Lens' g (Group a) Source #
groupAspectRatio :: Lens' g PreserveAspectRatio Source #
groupChildren :: Lens' g [a] Source #
groupDrawAttributes :: Lens' g DrawAttributes Source #
groupViewBox :: Lens' g (Maybe (Double, Double, Double, Double)) Source #
Instances
HasGroup (Group a) a Source # | |
Defined in Graphics.SvgTree.Types Methods group :: Lens' (Group a) (Group a) Source # groupAspectRatio :: Lens' (Group a) PreserveAspectRatio Source # groupChildren :: Lens' (Group a) [a] Source # groupDrawAttributes :: Lens' (Group a) DrawAttributes Source # groupViewBox :: Lens' (Group a) (Maybe (Double, Double, Double, Double)) Source # |
Symbol
Define the `<symbol>` tag, equivalent to a hidden named group.
Constructors
Symbol | |
Fields
|
Instances
Eq a => Eq (Symbol a) Source # | |
Show a => Show (Symbol a) Source # | |
WithDefaultSvg (Symbol a) Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Symbol a Source # | |
WithDrawAttributes (Symbol a) Source # | |
Defined in Graphics.SvgTree.Types |
groupOfSymbol :: Lens (Symbol s) (Symbol t) (Group s) (Group t) Source #
Lenses associated with the Symbol type.
Definitions
newtype Definitions a Source #
Define the `<defs>` tag, equivalent to a named symbol.
Constructors
Definitions | |
Fields
|
Instances
Eq a => Eq (Definitions a) Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: Definitions a -> Definitions a -> Bool # (/=) :: Definitions a -> Definitions a -> Bool # | |
Show a => Show (Definitions a) Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> Definitions a -> ShowS # show :: Definitions a -> String # showList :: [Definitions a] -> ShowS # | |
WithDefaultSvg (Definitions a) Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Definitions a Source # | |
WithDrawAttributes (Definitions a) Source # | |
Defined in Graphics.SvgTree.Types Methods drawAttr :: Lens' (Definitions a) DrawAttributes Source # |
groupOfDefinitions :: Lens (Definitions s) (Definitions t) (Group s) (Group t) Source #
Lenses associated with the Definitions type.
Text related types
Text
Define the global `<tag>` SVG tag.
Constructors
Text | |
Fields
|
class HasText c_aorD where Source #
Lenses for the Text type.
Minimal complete definition
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 | |
Show TextAnchor Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> TextAnchor -> ShowS # show :: TextAnchor -> String # showList :: [TextAnchor] -> ShowS # |
textAt :: Point -> Text -> Text Source #
Little helper to create a SVG text at a given baseline position.
Text path
Describe the `<textpath>` SVG tag.
Constructors
TextPath | |
Fields
|
Instances
Eq TextPath Source # | |
Show TextPath Source # | |
HasTextPath TextPath Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg TextPath Source # | |
Defined in Graphics.SvgTree.Types Methods |
class HasTextPath c_aojU where Source #
Lenses for the TextPath type.
Minimal complete definition
Methods
textPath :: Lens' c_aojU TextPath Source #
textPathData :: Lens' c_aojU [PathCommand] Source #
textPathMethod :: Lens' c_aojU TextPathMethod Source #
textPathName :: Lens' c_aojU String Source #
textPathSpacing :: Lens' c_aojU TextPathSpacing Source #
textPathStartOffset :: Lens' c_aojU Number Source #
Instances
HasTextPath TextPath Source # | |
Defined in Graphics.SvgTree.Types |
data TextPathSpacing Source #
Describe the content of the spacing
text path
attribute.
Constructors
TextPathSpacingExact | Map to the |
TextPathSpacingAuto | Map to the |
Instances
Eq TextPathSpacing Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: TextPathSpacing -> TextPathSpacing -> Bool # (/=) :: TextPathSpacing -> TextPathSpacing -> Bool # | |
Show TextPathSpacing Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> TextPathSpacing -> ShowS # show :: TextPathSpacing -> String # showList :: [TextPathSpacing] -> ShowS # |
data TextPathMethod Source #
Describe the content of the method
attribute on
text path.
Constructors
TextPathAlign | Map to the |
TextPathStretch | Map to the |
Instances
Eq TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: TextPathMethod -> TextPathMethod -> Bool # (/=) :: TextPathMethod -> TextPathMethod -> Bool # | |
Show TextPathMethod Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> TextPathMethod -> ShowS # show :: TextPathMethod -> String # showList :: [TextPathMethod] -> ShowS # |
Text span.
data TextSpanContent Source #
Define the content of a `<tspan>` tag.
Constructors
SpanText !Text | Raw text |
SpanTextRef !String | Equivalent to a `<tref>` |
SpanSub !TextSpan | Define a `<tspan>` |
Instances
Eq TextSpanContent Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: TextSpanContent -> TextSpanContent -> Bool # (/=) :: TextSpanContent -> TextSpanContent -> Bool # | |
Show TextSpanContent Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> TextSpanContent -> ShowS # show :: TextSpanContent -> String # showList :: [TextSpanContent] -> ShowS # |
Define a `<tspan>` tag.
Constructors
TextSpan | |
Fields
|
Instances
Eq TextSpan Source # | |
Show TextSpan Source # | |
HasTextSpan TextSpan Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg TextSpan Source # | |
Defined in Graphics.SvgTree.Types Methods |
class HasTextSpan c_aobD where Source #
Lenses for the TextSpan type.
Minimal complete definition
Methods
textSpan :: Lens' c_aobD TextSpan Source #
spanContent :: Lens' c_aobD [TextSpanContent] Source #
spanDrawAttributes :: Lens' c_aobD DrawAttributes Source #
Instances
HasTextSpan TextSpan Source # | |
Defined in Graphics.SvgTree.Types |
Define position information associated to `<text>` or `<tspan>` svg tag.
Constructors
TextInfo | |
Fields
|
Instances
Eq TextInfo Source # | |
Show TextInfo Source # | |
Semigroup TextInfo Source # | |
Monoid TextInfo Source # | |
HasTextInfo TextInfo Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg TextInfo Source # | |
Defined in Graphics.SvgTree.Types Methods |
class HasTextInfo c_ao0m where Source #
Lenses for the TextInfo type.
Minimal complete definition
Methods
textInfo :: Lens' c_ao0m TextInfo Source #
textInfoDX :: Lens' c_ao0m [Number] Source #
textInfoDY :: Lens' c_ao0m [Number] Source #
textInfoLength :: Lens' c_ao0m (Maybe Number) Source #
textInfoRotate :: Lens' c_ao0m [Double] Source #
Instances
HasTextInfo TextInfo Source # | |
Defined in Graphics.SvgTree.Types |
data TextAdjust Source #
Define the possible values of the lengthAdjust
attribute.
Constructors
TextAdjustSpacing | Value |
TextAdjustSpacingAndGlyphs | Value |
Instances
Eq TextAdjust Source # | |
Defined in Graphics.SvgTree.Types | |
Show TextAdjust Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> TextAdjust -> ShowS # show :: TextAdjust -> String # showList :: [TextAdjust] -> ShowS # |
Marker definition
Define the `<marker>` tag.
Constructors
Marker | |
Fields
|
Instances
Eq Marker Source # | |
Show Marker Source # | |
HasMarker Marker Source # | |
Defined in Graphics.SvgTree.Types Methods marker :: Lens' Marker Marker Source # markerAspectRatio :: Lens' Marker PreserveAspectRatio Source # markerDrawAttributes :: Lens' Marker DrawAttributes Source # markerElements :: Lens' Marker [Tree] Source # markerHeight :: Lens' Marker (Maybe Number) Source # markerOrient :: Lens' Marker (Maybe MarkerOrientation) Source # markerOverflow :: Lens' Marker (Maybe Overflow) Source # markerRefPoint :: Lens' Marker (Number, Number) Source # markerUnits :: Lens' Marker (Maybe MarkerUnit) Source # markerViewBox :: Lens' Marker (Maybe (Double, Double, Double, Double)) Source # | |
WithDefaultSvg Marker Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Marker Source # | |
WithDrawAttributes Marker Source # | |
Defined in Graphics.SvgTree.Types |
Define the content of the markerUnits
attribute
on the Marker.
Constructors
OverflowVisible | Value |
OverflowHidden | Value |
data MarkerOrientation Source #
Define the orientation, associated to the
orient
attribute on the Marker
Constructors
OrientationAuto | Auto value |
OrientationAngle Coord | Specific angle. |
Instances
Eq MarkerOrientation Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: MarkerOrientation -> MarkerOrientation -> Bool # (/=) :: MarkerOrientation -> MarkerOrientation -> Bool # | |
Show MarkerOrientation Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> MarkerOrientation -> ShowS # show :: MarkerOrientation -> String # showList :: [MarkerOrientation] -> ShowS # |
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 | |
Show MarkerUnit Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> MarkerUnit -> ShowS # show :: MarkerUnit -> String # showList :: [MarkerUnit] -> ShowS # |
class HasMarker c_aoKc where Source #
Lenses for the Marker type.
Minimal complete definition
Methods
marker :: Lens' c_aoKc Marker Source #
markerAspectRatio :: Lens' c_aoKc PreserveAspectRatio Source #
markerDrawAttributes :: Lens' c_aoKc DrawAttributes Source #
markerElements :: Lens' c_aoKc [Tree] Source #
markerHeight :: Lens' c_aoKc (Maybe Number) Source #
markerOrient :: Lens' c_aoKc (Maybe MarkerOrientation) Source #
markerOverflow :: Lens' c_aoKc (Maybe Overflow) Source #
markerRefPoint :: Lens' c_aoKc (Number, Number) Source #
markerUnits :: Lens' c_aoKc (Maybe MarkerUnit) Source #
markerViewBox :: Lens' c_aoKc (Maybe (Double, Double, Double, Double)) Source #
Instances
HasMarker Marker Source # | |
Defined in Graphics.SvgTree.Types Methods marker :: Lens' Marker Marker Source # markerAspectRatio :: Lens' Marker PreserveAspectRatio Source # markerDrawAttributes :: Lens' Marker DrawAttributes Source # markerElements :: Lens' Marker [Tree] Source # markerHeight :: Lens' Marker (Maybe Number) Source # markerOrient :: Lens' Marker (Maybe MarkerOrientation) Source # markerOverflow :: Lens' Marker (Maybe Overflow) Source # markerRefPoint :: Lens' Marker (Number, Number) Source # markerUnits :: Lens' Marker (Maybe MarkerUnit) Source # markerViewBox :: Lens' Marker (Maybe (Double, Double, Double, Double)) Source # |
Gradient definition
data GradientStop Source #
Define a color stop for the gradients. Represent the `<stop>` SVG tag.
Constructors
GradientStop | |
Fields
|
Instances
Eq GradientStop Source # | |
Defined in Graphics.SvgTree.Types | |
Show GradientStop Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> GradientStop -> ShowS # show :: GradientStop -> String # showList :: [GradientStop] -> ShowS # | |
HasGradientStop GradientStop Source # | |
Defined in Graphics.SvgTree.Types Methods gradientStop :: Lens' GradientStop GradientStop Source # gradientColor :: Lens' GradientStop PixelRGBA8 Source # gradientOffset :: Lens' GradientStop Float Source # gradientOpacity :: Lens' GradientStop (Maybe Float) Source # gradientPath :: Lens' GradientStop (Maybe GradientPathCommand) Source # | |
WithDefaultSvg GradientStop Source # | |
Defined in Graphics.SvgTree.Types Methods |
class HasGradientStop c_anhM where Source #
Lenses for the GradientStop type.
Minimal complete definition
Methods
gradientStop :: Lens' c_anhM GradientStop Source #
gradientColor :: Lens' c_anhM PixelRGBA8 Source #
gradientOffset :: Lens' c_anhM Float Source #
gradientOpacity :: Lens' c_anhM (Maybe Float) Source #
gradientPath :: Lens' c_anhM (Maybe GradientPathCommand) Source #
Instances
Linear Gradient
data LinearGradient Source #
Define a `<linearGradient>` tag.
Constructors
LinearGradient | |
Fields
|
Instances
class HasLinearGradient c_apmJ where Source #
Lenses for the LinearGradient type.
Minimal complete definition
Methods
linearGradient :: Lens' c_apmJ LinearGradient Source #
linearGradientDrawAttributes :: Lens' c_apmJ DrawAttributes Source #
linearGradientSpread :: Lens' c_apmJ Spread Source #
linearGradientStart :: Lens' c_apmJ Point Source #
linearGradientStop :: Lens' c_apmJ Point Source #
linearGradientStops :: Lens' c_apmJ [GradientStop] Source #
linearGradientTransform :: Lens' c_apmJ [Transformation] Source #
linearGradientUnits :: Lens' c_apmJ CoordinateUnits Source #
Instances
Radial Gradient
data RadialGradient Source #
Define a `<radialGradient>` tag.
Constructors
RadialGradient | |
Fields
|
Instances
class HasRadialGradient c_apwt where Source #
Lenses for the RadialGradient type.
Minimal complete definition
Methods
radialGradient :: Lens' c_apwt RadialGradient Source #
radialGradientDrawAttributes :: Lens' c_apwt DrawAttributes Source #
radialGradientCenter :: Lens' c_apwt Point Source #
radialGradientFocusX :: Lens' c_apwt (Maybe Number) Source #
radialGradientFocusY :: Lens' c_apwt (Maybe Number) Source #
radialGradientRadius :: Lens' c_apwt Number Source #
radialGradientSpread :: Lens' c_apwt Spread Source #
radialGradientStops :: Lens' c_apwt [GradientStop] Source #
radialGradientTransform :: Lens' c_apwt [Transformation] Source #
radialGradientUnits :: Lens' c_apwt CoordinateUnits Source #
Instances
Pattern definition
Define a `<pattern>` tag.
Constructors
Pattern | |
Fields
|
Instances
Eq Pattern Source # | |
Show Pattern Source # | |
HasPattern Pattern Source # | |
Defined in Graphics.SvgTree.Types Methods pattern :: Lens' Pattern Pattern Source # patternAspectRatio :: Lens' Pattern PreserveAspectRatio Source # patternDrawAttributes :: Lens' Pattern DrawAttributes Source # patternElements :: Lens' Pattern [Tree] Source # patternHeight :: Lens' Pattern Number Source # patternHref :: Lens' Pattern String Source # patternPos :: Lens' Pattern Point Source # patternTransform :: Lens' Pattern (Maybe [Transformation]) Source # patternUnit :: Lens' Pattern CoordinateUnits Source # patternViewBox :: Lens' Pattern (Maybe (Double, Double, Double, Double)) Source # | |
WithDefaultSvg Pattern Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Pattern Source # | |
WithDrawAttributes Pattern Source # | |
Defined in Graphics.SvgTree.Types |
class HasPattern c_aq6G where Source #
Lenses for the Patter type.
Minimal complete definition
Methods
pattern :: Lens' c_aq6G Pattern Source #
patternAspectRatio :: Lens' c_aq6G PreserveAspectRatio Source #
patternDrawAttributes :: Lens' c_aq6G DrawAttributes Source #
patternElements :: Lens' c_aq6G [Tree] Source #
patternHeight :: Lens' c_aq6G Number Source #
patternHref :: Lens' c_aq6G String Source #
patternPos :: Lens' c_aq6G Point Source #
patternTransform :: Lens' c_aq6G (Maybe [Transformation]) Source #
patternUnit :: Lens' c_aq6G CoordinateUnits Source #
patternViewBox :: Lens' c_aq6G (Maybe (Double, Double, Double, Double)) Source #
patternWidth :: Lens' c_aq6G Number Source #
Instances
Mask definition
Define a SVG `<mask>` tag.
Constructors
Mask | |
Fields
|
Instances
Eq Mask Source # | |
Show Mask Source # | |
HasMask Mask Source # | |
Defined in Graphics.SvgTree.Types Methods mask :: Lens' Mask Mask Source # maskContent :: Lens' Mask [Tree] Source # maskContentUnits :: Lens' Mask CoordinateUnits Source # maskDrawAttributes :: Lens' Mask DrawAttributes Source # maskHeight :: Lens' Mask Number Source # maskPosition :: Lens' Mask Point Source # | |
WithDefaultSvg Mask Source # | |
Defined in Graphics.SvgTree.Types Methods defaultSvg :: Mask Source # | |
WithDrawAttributes Mask Source # | |
Defined in Graphics.SvgTree.Types |
class HasMask c_apHI where Source #
Lenses for the Mask type.
Minimal complete definition
Methods
mask :: Lens' c_apHI Mask Source #
maskContent :: Lens' c_apHI [Tree] Source #
maskContentUnits :: Lens' c_apHI CoordinateUnits Source #
maskDrawAttributes :: Lens' c_apHI DrawAttributes Source #
maskHeight :: Lens' c_apHI Number Source #
maskPosition :: Lens' c_apHI Point Source #
maskUnits :: Lens' c_apHI CoordinateUnits Source #
Instances
HasMask Mask Source # | |
Defined in Graphics.SvgTree.Types Methods mask :: Lens' Mask Mask Source # maskContent :: Lens' Mask [Tree] Source # maskContentUnits :: Lens' Mask CoordinateUnits Source # maskDrawAttributes :: Lens' Mask DrawAttributes Source # maskHeight :: Lens' Mask Number Source # maskPosition :: Lens' Mask Point Source # |
Clip path definition
Define a `<clipPath>` tag.
Constructors
ClipPath | |
Fields
|
Instances
Eq ClipPath Source # | |
Show ClipPath Source # | |
HasClipPath ClipPath Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg ClipPath Source # | |
Defined in Graphics.SvgTree.Types Methods | |
WithDrawAttributes ClipPath Source # | |
Defined in Graphics.SvgTree.Types |
class HasClipPath c_apZq where Source #
Lenses for the ClipPath type.
Minimal complete definition
Methods
clipPath :: Lens' c_apZq ClipPath Source #
clipPathContent :: Lens' c_apZq [Tree] Source #
clipPathDrawAttributes :: Lens' c_apZq DrawAttributes Source #
clipPathUnits :: Lens' c_apZq CoordinateUnits Source #
Instances
HasClipPath ClipPath Source # | |
Defined in Graphics.SvgTree.Types |
Aspect Ratio description
data PreserveAspectRatio Source #
Describe the content of the preserveAspectRatio attribute.
Constructors
PreserveAspectRatio | |
Fields |
Instances
Eq PreserveAspectRatio Source # | |
Defined in Graphics.SvgTree.Types Methods (==) :: PreserveAspectRatio -> PreserveAspectRatio -> Bool # (/=) :: PreserveAspectRatio -> PreserveAspectRatio -> Bool # | |
Show PreserveAspectRatio Source # | |
Defined in Graphics.SvgTree.Types Methods showsPrec :: Int -> PreserveAspectRatio -> ShowS # show :: PreserveAspectRatio -> String # showList :: [PreserveAspectRatio] -> ShowS # | |
HasPreserveAspectRatio PreserveAspectRatio Source # | |
Defined in Graphics.SvgTree.Types | |
WithDefaultSvg PreserveAspectRatio Source # | |
Defined in Graphics.SvgTree.Types Methods |
This type represent the align information of the preserveAspectRatio SVGattribute
Constructors
AlignNone | "none" value |
AlignxMinYMin | |
AlignxMidYMin | "xMidYMin" value |
AlignxMaxYMin | "xMaxYMin" value |
AlignxMinYMid | "xMinYMid" value |
AlignxMidYMid | "xMidYMid" value |
AlignxMaxYMid | "xMaxYMid" value |
AlignxMinYMax | "xMinYMax" value |
AlignxMidYMax | "xMidYMax" value |
AlignxMaxYMax | "xMaxYMax" value |
This type represent the "meet or slice" information of the preserveAspectRatio SVGattribute
class HasPreserveAspectRatio a where Source #
Lenses for the PreserveAspectRatio type
Minimal complete definition
Methods
preserveAspectRatio :: Lens' a PreserveAspectRatio Source #
aspectRatioAlign :: Lens' a Alignment Source #
aspectRatioDefer :: Lens' a Bool Source #
Instances
HasPreserveAspectRatio PreserveAspectRatio Source # | |
Defined in Graphics.SvgTree.Types |
MISC functions
isPathArc :: PathCommand -> Bool Source #
Tell if the path command is an EllipticalArc.
isPathWithArc :: Foldable f => f PathCommand -> Bool Source #
Tell if a full path contain an EllipticalArc.
nameOfTree :: Tree -> Text Source #
For every element of a svg tree, associate it's SVG tag name.
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.