Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.Svg.Types
Contents
Description
This module define all the types used in the definition of a svg scene.
Most of the types are lensified.
- type Coord = Float
- 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]
- | ElipticalArc Origin [(Coord, Coord, Coord, Coord, Coord, 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)
- | PathTree !Path
- | CircleTree !Circle
- | PolyLineTree !PolyLine
- | PolygonTree !Polygon
- | EllipseTree !Ellipse
- | LineTree !Line
- | RectangleTree !Rectangle
- | TextTree !(Maybe TextPath) !Text
- | ImageTree !Image
- 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 Element)
- description :: Lens' c String
- documentLocation :: Lens' c FilePath
- elements :: Lens' c [Tree]
- height :: Lens' c (Maybe Number)
- styleRules :: Lens' c [CssRule]
- viewBox :: Lens' c (Maybe (Int, Int, Int, Int))
- 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 Float)
- _fillColor :: !(Last Texture)
- _fillOpacity :: !(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 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)
- fontFamily :: Lens' c (Last [String])
- fontSize :: Lens' c (Last Number)
- fontStyle :: Lens' c (Last FontStyle)
- markerEnd :: Lens' c (Last ElementRef)
- markerMid :: Lens' c (Last ElementRef)
- markerStart :: Lens' c (Last ElementRef)
- maskRef :: Lens' c (Last ElementRef)
- strokeColor :: Lens' c (Last Texture)
- strokeDashArray :: Lens' c (Last [Number])
- strokeLineCap :: Lens' c (Last Cap)
- strokeLineJoin :: Lens' c (Last LineJoin)
- strokeMiterLimit :: Lens' c (Last Float)
- 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])
- class WithDrawAttributes a where
- drawAttr :: Lens' a DrawAttributes
- data Rectangle = Rectangle {}
- class HasRectangle c where
- rectangle :: Lens' c Rectangle
- rectCornerRadius :: Lens' c (Number, Number)
- rectDrawAttributes :: Lens' c DrawAttributes
- rectHeight :: Lens' c Number
- rectUpperLeftCorner :: Lens' c Point
- rectWidth :: Lens' c Number
- data Line = Line {}
- class HasLine c where
- line :: Lens' c Line
- lineDrawAttributes :: Lens' c DrawAttributes
- linePoint1 :: Lens' c Point
- linePoint2 :: Lens' c Point
- data Polygon = Polygon {}
- class HasPolygon c where
- polygon :: Lens' c Polygon
- polygonDrawAttributes :: Lens' c DrawAttributes
- polygonPoints :: Lens' c [RPoint]
- data PolyLine = PolyLine {}
- class HasPolyLine c where
- polyLine :: Lens' c PolyLine
- polyLineDrawAttributes :: Lens' c DrawAttributes
- polyLinePoints :: Lens' c [RPoint]
- data Path = Path {}
- class HasPath c where
- path :: Lens' c Path
- pathDefinition :: Lens' c [PathCommand]
- pathDrawAttributes :: Lens' c DrawAttributes
- data Circle = Circle {}
- class HasCircle c where
- circle :: Lens' c Circle
- circleCenter :: Lens' c Point
- circleDrawAttributes :: Lens' c DrawAttributes
- circleRadius :: Lens' c Number
- data Ellipse = Ellipse {}
- class HasEllipse c where
- ellipse :: Lens' c Ellipse
- ellipseCenter :: Lens' c Point
- ellipseDrawAttributes :: Lens' c DrawAttributes
- ellipseXRadius :: Lens' c Number
- ellipseYRadius :: Lens' c Number
- data Image = Image {}
- class HasImage c where
- image :: Lens' c Image
- imageCornerUpperLeft :: Lens' c Point
- imageDrawAttributes :: Lens' c DrawAttributes
- imageHeight :: Lens' c Number
- imageHref :: Lens' c String
- imageWidth :: Lens' c Number
- data Use = Use {}
- class HasUse c where
- data Group a = Group {
- _groupDrawAttributes :: !DrawAttributes
- _groupChildren :: ![a]
- _groupViewBox :: !(Maybe (Int, Int, Int, Int))
- class HasGroup c a | c -> a where
- group :: Lens' c (Group a)
- groupChildren :: Lens' c [a]
- groupDrawAttributes :: Lens' c DrawAttributes
- groupViewBox :: Lens' c (Maybe (Int, Int, Int, Int))
- newtype Symbol a = Symbol {
- _groupOfSymbol :: Group a
- groupOfSymbol :: forall a a. Iso (Symbol a) (Symbol a) (Group a) (Group a)
- data Text = Text {
- _textAdjust :: !TextAdjust
- _textRoot :: !TextSpan
- class HasText c where
- text :: Lens' c Text
- textAdjust :: Lens' c TextAdjust
- textRoot :: Lens' c TextSpan
- data TextAnchor
- textAt :: Point -> Text -> Text
- data TextPath = TextPath {}
- class HasTextPath c where
- textPath :: Lens' c TextPath
- textPathData :: Lens' c [PathCommand]
- textPathMethod :: Lens' c TextPathMethod
- textPathName :: Lens' c String
- textPathSpacing :: Lens' c TextPathSpacing
- textPathStartOffset :: Lens' c Number
- data TextPathSpacing
- data TextPathMethod
- data TextSpanContent
- data TextSpan = TextSpan {}
- class HasTextSpan c where
- textSpan :: Lens' c TextSpan
- spanContent :: Lens' c [TextSpanContent]
- spanDrawAttributes :: Lens' c DrawAttributes
- spanInfo :: Lens' c TextInfo
- data TextInfo = TextInfo {
- _textInfoX :: ![Number]
- _textInfoY :: ![Number]
- _textInfoDX :: ![Number]
- _textInfoDY :: ![Number]
- _textInfoRotate :: ![Float]
- _textInfoLength :: !(Maybe Number)
- class HasTextInfo c where
- data TextAdjust
- data Marker = Marker {}
- data MarkerOrientation
- data MarkerUnit
- class HasMarker c where
- marker :: Lens' c Marker
- markerDrawAttributes :: Lens' c DrawAttributes
- markerElements :: Lens' c [Tree]
- markerHeight :: Lens' c (Maybe Number)
- markerOrient :: Lens' c (Maybe MarkerOrientation)
- markerRefPoint :: Lens' c (Number, Number)
- markerUnits :: Lens' c (Maybe MarkerUnit)
- markerViewBox :: Lens' c (Maybe (Int, Int, Int, Int))
- markerWidth :: Lens' c (Maybe Number)
- data GradientStop = GradientStop {}
- class HasGradientStop c where
- gradientStop :: Lens' c GradientStop
- gradientColor :: Lens' c PixelRGBA8
- gradientOffset :: Lens' c Float
- data LinearGradient = LinearGradient {}
- class HasLinearGradient c where
- data RadialGradient = RadialGradient {}
- class HasRadialGradient c where
- radialGradient :: Lens' c RadialGradient
- radialGradientCenter :: Lens' c Point
- radialGradientFocusX :: Lens' c (Maybe Number)
- radialGradientFocusY :: Lens' c (Maybe Number)
- radialGradientRadius :: Lens' c Number
- radialGradientSpread :: Lens' c Spread
- radialGradientStops :: Lens' c [GradientStop]
- radialGradientTransform :: Lens' c [Transformation]
- radialGradientUnits :: Lens' c CoordinateUnits
- data Pattern = Pattern {}
- class HasPattern c where
- pattern :: Lens' c Pattern
- patternDrawAttributes :: Lens' c DrawAttributes
- patternElements :: Lens' c [Tree]
- patternHeight :: Lens' c Number
- patternPos :: Lens' c Point
- patternUnit :: Lens' c CoordinateUnits
- patternViewBox :: Lens' c (Maybe (Int, Int, Int, Int))
- patternWidth :: Lens' c Number
- data Mask = Mask {}
- class HasMask c where
- mask :: Lens' c Mask
- maskContent :: Lens' c [Tree]
- maskContentUnits :: Lens' c CoordinateUnits
- maskDrawAttributes :: Lens' c DrawAttributes
- maskHeight :: Lens' c Number
- maskPosition :: Lens' c Point
- maskUnits :: Lens' c CoordinateUnits
- maskWidth :: Lens' c Number
- data ClipPath = ClipPath {}
- class HasClipPath c where
- clipPath :: Lens' c ClipPath
- clipPathContent :: Lens' c [Tree]
- clipPathDrawAttributes :: Lens' c DrawAttributes
- clipPathUnits :: Lens' c CoordinateUnits
- 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 :: (Float -> Float) -> 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 |
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, |
ElipticalArc Origin [(Coord, Coord, Coord, Coord, Coord, RPoint)] | Eliptical 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 Float Float | Translation along a vector |
Scale Float (Maybe Float) | Scaling on both axis or on X axis and Y axis. |
Rotate Float (Maybe (Float, Float)) | Rotation around `(0, 0)` or around an optional point. |
SkewX Float | Skew transformation along the X axis. |
SkewY Float | Skew transformation along the Y axis. |
TransformUnknown | Unkown transformation, like identity. |
Instances
data ElementRef Source
Correspond to the possible values of the
the attributes which are either none
or
`url(#elem)`
Instances
data CoordinateUnits Source
Define the possible values of various *units attributes used in the definition of the gradients and masks.
Constructors
CoordUserSpace |
|
CoordBoundingBox |
|
Instances
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
None | |
UseTree | |
Fields
| |
GroupTree !(Group Tree) | |
SymbolTree !(Symbol Tree) | |
PathTree !Path | |
CircleTree !Circle | |
PolyLineTree !PolyLine | |
PolygonTree !Polygon | |
EllipseTree !Ellipse | |
LineTree !Line | |
RectangleTree !Rectangle | |
TextTree !(Maybe TextPath) !Text | |
ImageTree !Image |
Instances
Encode complex number possibly dependant to the current render size.
Constructors
Num Float | Simple coordinate in current user coordinate. |
Px Float | With suffix "px" |
Em Float | Number relative to the current font size. |
Percent Float | Number relative to the current viewport size. |
Pc Float | |
Mm Float | Number in millimeters, relative to DPI. |
Cm Float | Number in centimeters, relative to DPI. |
Point Float | Number in points, relative to DPI. |
Inches Float | 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.
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
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 Element) Source
description :: Lens' c String Source
documentLocation :: Lens' c FilePath Source
elements :: Lens' c [Tree] Source
height :: Lens' c (Maybe Number) Source
styleRules :: Lens' c [CssRule] Source
Instances
documentSize :: Dpi -> Document -> (Int, Int) Source
Calculate the document size in function of the different available attributes in the document.
Drawing attributes
data DrawAttributes Source
This type define how to draw any primitives, which color to use, how to stroke the primitives and the potential transformations to use.
All these attributes are propagated to the children.
Constructors
DrawAttributes | |
Fields
|
class HasDrawAttributes c where Source
Lenses for the DrawAttributes type.
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
fontFamily :: Lens' c (Last [String]) Source
fontSize :: Lens' c (Last Number) Source
fontStyle :: Lens' c (Last FontStyle) Source
markerEnd :: Lens' c (Last ElementRef) Source
markerMid :: Lens' c (Last ElementRef) Source
markerStart :: Lens' c (Last ElementRef) Source
maskRef :: Lens' c (Last ElementRef) Source
strokeColor :: Lens' c (Last Texture) Source
strokeDashArray :: Lens' c (Last [Number]) Source
strokeLineCap :: Lens' c (Last Cap) Source
strokeLineJoin :: Lens' c (Last LineJoin) Source
strokeMiterLimit :: Lens' c (Last Float) 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
transform :: Lens' c (Maybe [Transformation]) 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
|
class HasRectangle c where Source
Lenses for the Rectangle type.
Minimal complete definition
Methods
rectangle :: Lens' c Rectangle Source
rectCornerRadius :: Lens' c (Number, Number) Source
rectDrawAttributes :: Lens' c DrawAttributes Source
rectHeight :: Lens' c Number Source
Instances
Line
Define a simple line. Correspond to the `<line>` tag.
Constructors
Line | |
Fields
|
Instances
Lenses for the Line type.
Minimal complete definition
Methods
lineDrawAttributes :: Lens' c DrawAttributes Source
linePoint1 :: Lens' c Point Source
linePoint2 :: Lens' c Point Source
Polygon
Primitive decriving polygon composed of segements. Correspond to the `<polygon>` tag
Constructors
Polygon | |
Fields
|
class HasPolygon c where Source
Lenses for the Polygon type
Minimal complete definition
Methods
polygon :: Lens' c Polygon Source
polygonDrawAttributes :: Lens' c DrawAttributes Source
polygonPoints :: Lens' c [RPoint] Source
Instances
Polyline
This primitive describe an unclosed suite of segments. Correspond to the `<polyline>` tag.
Constructors
PolyLine | |
Fields
|
class HasPolyLine c where Source
Lenses for the PolyLine type.
Minimal complete definition
Methods
polyLine :: Lens' c PolyLine Source
polyLineDrawAttributes :: Lens' c DrawAttributes Source
polyLinePoints :: Lens' c [RPoint] Source
Instances
Path
Type mapping the `<path>` svg tag.
Constructors
Path | |
Fields
|
Instances
Lenses for the Path type
Minimal complete definition
Methods
pathDefinition :: Lens' c [PathCommand] Source
Circle
Define a `<circle>`.
Constructors
Circle | |
Fields
|
class HasCircle c where Source
Lenses for the Circle type.
Minimal complete definition
Methods
circle :: Lens' c Circle Source
circleCenter :: Lens' c Point Source
circleDrawAttributes :: Lens' c DrawAttributes Source
circleRadius :: Lens' c Number Source
Ellipse
Define an `<ellipse>`
Constructors
Ellipse | |
Fields
|
class HasEllipse c where Source
Lenses for the ellipse type.
Minimal complete definition
Methods
ellipse :: Lens' c Ellipse Source
ellipseCenter :: Lens' c Point Source
ellipseDrawAttributes :: Lens' c DrawAttributes Source
ellipseXRadius :: Lens' c Number Source
ellipseYRadius :: Lens' c Number Source
Instances
Image
Define an `<image>` tag.
Constructors
Image | |
Fields
|
Instances
Lenses for the Image type.
Minimal complete definition
Methods
imageCornerUpperLeft :: Lens' c Point Source
imageDrawAttributes :: Lens' c DrawAttributes Source
imageHeight :: Lens' c Number Source
imageHref :: Lens' c String Source
imageWidth :: Lens' c Number Source
Use
Define an `<use>` for a named content. Every named content can be reused in the document using this element.
Constructors
Use | |
Fields
|
Instances
Lenses for the Use type.
Minimal complete definition
Grouping primitives
Group
Define a SVG group, corresponding `<g>` tag.
Constructors
Group | |
Fields
|
class HasGroup c a | c -> a where Source
Lenses associated to the Group type.
Minimal complete definition
Methods
group :: Lens' c (Group a) Source
groupChildren :: Lens' c [a] Source
Symbol
Define the `<symbol>` tag, equivalent to a named group.
Constructors
Symbol | |
Fields
|
Instances
Eq a => Eq (Symbol a) | |
Show a => Show (Symbol a) | |
WithDefaultSvg (Symbol a) | |
WithDrawAttributes (Symbol a) |
groupOfSymbol :: forall a a. Iso (Symbol a) (Symbol a) (Group a) (Group a) Source
Lenses associated with the Symbol type.
Text related types
Text
Define the global `<tag>` 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
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
class HasTextPath c where Source
Lenses for the TextPath type.
Minimal complete definition
Methods
textPath :: Lens' c TextPath Source
textPathData :: Lens' c [PathCommand] Source
textPathMethod :: Lens' c TextPathMethod Source
textPathName :: Lens' c String Source
Instances
data TextPathSpacing Source
Describe the content of the spacing
text path
attribute.
Constructors
TextPathSpacingExact | Map to the |
TextPathSpacingAuto | Map to the |
Instances
data TextPathMethod Source
Describe the content of the method
attribute on
text path.
Constructors
TextPathAlign | Map to the |
TextPathStretch | Map to the |
Instances
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
Define a `<tspan>` tag.
Constructors
TextSpan | |
Fields
|
Instances
class HasTextSpan c where Source
Lenses for the TextSpan type.
Minimal complete definition
Methods
textSpan :: Lens' c TextSpan Source
spanContent :: Lens' c [TextSpanContent] Source
Instances
Define position information associated to `<text>` or `<tspan>` svg tag.
Constructors
TextInfo | |
Fields
|
class HasTextInfo c where Source
Lenses for the TextInfo type.
Minimal complete definition
Methods
textInfo :: Lens' c TextInfo Source
textInfoDX :: Lens' c [Number] Source
textInfoDY :: Lens' c [Number] Source
textInfoLength :: Lens' c (Maybe Number) Source
textInfoRotate :: Lens' c [Float] Source
Instances
data TextAdjust Source
Define the possible values of the lengthAdjust
attribute.
Constructors
TextAdjustSpacing | Value |
TextAdjustSpacingAndGlyphs | Value |
Instances
Marker definition
Define the `<marker>` tag.
Constructors
Marker | |
Fields
|
data MarkerOrientation Source
Define 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
class HasMarker c where Source
Lenses for the Marker type.
Minimal complete definition
Methods
marker :: Lens' c Marker Source
markerDrawAttributes :: Lens' c DrawAttributes Source
markerElements :: Lens' c [Tree] Source
markerHeight :: Lens' c (Maybe Number) Source
markerOrient :: Lens' c (Maybe MarkerOrientation) Source
markerRefPoint :: Lens' c (Number, Number) Source
markerUnits :: Lens' c (Maybe MarkerUnit) Source
markerViewBox :: Lens' c (Maybe (Int, Int, Int, Int)) Source
markerWidth :: Lens' c (Maybe Number) Source
Gradient definition
data GradientStop Source
Define a color stop for the gradients. Represent the `<stop>` SVG tag.
Constructors
GradientStop | |
Fields
|
class HasGradientStop c where Source
Lenses for the GradientStop type.
Minimal complete definition
Methods
gradientStop :: Lens' c GradientStop Source
gradientColor :: Lens' c PixelRGBA8 Source
gradientOffset :: Lens' c Float Source
Instances
Linear Gradient
data LinearGradient Source
Define a `<linearGradient>` tag.
Constructors
LinearGradient | |
Fields
|
class HasLinearGradient c where Source
Lenses for the LinearGradient type.
Minimal complete definition
Methods
linearGradient :: Lens' c LinearGradient Source
linearGradientSpread :: Lens' c Spread Source
linearGradientStart :: Lens' c Point Source
linearGradientStop :: Lens' c Point Source
linearGradientStops :: Lens' c [GradientStop] Source
Instances
Radial Gradient
data RadialGradient Source
Define a `<radialGradient>` tag.
Constructors
RadialGradient | |
Fields
|
class HasRadialGradient c where Source
Lenses for the RadialGradient type.
Minimal complete definition
Methods
radialGradient :: Lens' c RadialGradient Source
radialGradientCenter :: Lens' c Point Source
radialGradientFocusX :: Lens' c (Maybe Number) Source
radialGradientFocusY :: Lens' c (Maybe Number) Source
radialGradientRadius :: Lens' c Number Source
radialGradientSpread :: Lens' c Spread Source
radialGradientStops :: Lens' c [GradientStop] Source
Instances
Pattern definition
Define a `<pattern>` tag.
Constructors
Pattern | |
Fields
|
class HasPattern c where Source
Lenses for the Patter type.
Minimal complete definition
Methods
pattern :: Lens' c Pattern Source
patternDrawAttributes :: Lens' c DrawAttributes Source
patternElements :: Lens' c [Tree] Source
patternHeight :: Lens' c Number Source
patternPos :: Lens' c Point Source
patternUnit :: Lens' c CoordinateUnits Source
patternViewBox :: Lens' c (Maybe (Int, Int, Int, Int)) Source
patternWidth :: Lens' c Number Source
Instances
Mask definition
Define a SVG `<mask>` tag.
Constructors
Mask | |
Fields
|
Instances
Lenses for the Mask type.
Minimal complete definition
Methods
maskContent :: Lens' c [Tree] Source
maskContentUnits :: Lens' c CoordinateUnits Source
maskDrawAttributes :: Lens' c DrawAttributes Source
maskHeight :: Lens' c Number Source
maskPosition :: Lens' c Point Source
Clip path definition
Define a `<clipPath>` tag.
Constructors
ClipPath | |
Fields
|
class HasClipPath c where Source
Lenses for the ClipPath type.
Minimal complete definition
Methods
clipPath :: Lens' c ClipPath Source
clipPathContent :: Lens' c [Tree] Source
Instances
MISC functions
isPathArc :: PathCommand -> Bool Source
Tell if the path command is an ElipticalArc.
isPathWithArc :: Foldable f => f PathCommand -> Bool Source
Tell if a full path contain an ElipticalArc.
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.
toUserUnit :: Dpi -> Number -> Number Source
This function replace all device dependant units to user units given it's DPI configuration. Preserve percentage and "em" notation.