| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Text.Blaze.Svg.Internal
- type Svg = Markup
 - toSvg :: ToMarkup a => a -> Svg
 - type Path = State AttributeValue ()
 - mkPath :: Path -> AttributeValue
 - appendToPath :: [String] -> Path
 - m :: Show a => a -> a -> Path
 - mr :: Show a => a -> a -> Path
 - z :: Path
 - l :: Show a => a -> a -> Path
 - lr :: Show a => a -> a -> Path
 - h :: Show a => a -> Path
 - hr :: Show a => a -> Path
 - v :: Show a => a -> Path
 - vr :: Show a => a -> Path
 - c :: Show a => a -> a -> a -> a -> a -> a -> Path
 - cr :: Show a => a -> a -> a -> a -> a -> a -> Path
 - s :: Show a => a -> a -> a -> a -> Path
 - sr :: Show a => a -> a -> a -> a -> Path
 - q :: Show a => a -> a -> a -> a -> Path
 - qr :: Show a => a -> a -> a -> a -> Path
 - t :: Show a => a -> a -> Path
 - tr :: Show a => a -> a -> Path
 - aa :: Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
 - a :: Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
 - ar :: Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
 - translate :: Show a => a -> a -> AttributeValue
 - scale :: Show a => a -> a -> AttributeValue
 - rotate :: Show a => a -> AttributeValue
 - rotateAround :: Show a => a -> a -> a -> AttributeValue
 - skewX :: Show a => a -> AttributeValue
 - skewY :: Show a => a -> AttributeValue
 - matrix :: Show a => a -> a -> a -> a -> a -> a -> AttributeValue
 
Documentation
type Path = State AttributeValue () Source #
Type to accumulate an SVG path.
mkPath :: Path -> AttributeValue Source #
Construct SVG path values using path instruction combinators.
 See simple example below of how you can use mkPath to
 specify a path using the path instruction combinators
 that are included as part of the same module.
More information available at: http://www.w3.org/TR/SVG/paths.html
import Text.Blaze.Svg11 ((!), mkPath, l, m) import qualified Text.Blaze.Svg11 as S import qualified Text.Blaze.Svg11.Attributes as A svgDoc :: S.Svg svgDoc = S.docTypeSvg ! A.version "1.1" ! A.width "150" ! A.height "100" $ do S.path ! A.d makeSimplePath makeSimplePath :: S.AttributeValue makeSimplePath = mkPath do l 2 3 m 4 5
appendToPath :: [String] -> Path Source #
Arguments
| :: Show a | |
| => a | Radius in the x-direction  | 
| -> a | Radius in the y-direction  | 
| -> a | The rotation of the arc's x-axis compared to the normal x-axis  | 
| -> Bool | Draw the smaller or bigger arc satisfying the start point  | 
| -> Bool | To mirror or not  | 
| -> a | The x-coordinate of the end point  | 
| -> a | The y-coordinate of the end point  | 
| -> Path | 
Elliptical Arc (absolute).
Note that this function is an alias for the function
   a, defined in
   Text.Blaze.Svg.Internal. aa is exported from Text.Blaze.Svg
   instead of a due to naming conflicts with a
   from Text.Blaze.SVG11.
Arguments
| :: Show a | |
| => a | Radius in the x-direction  | 
| -> a | Radius in the y-direction  | 
| -> a | The rotation of the arc's x-axis compared to the normal x-axis  | 
| -> Bool | True to draw the larger of the two arcs satisfying constraints.  | 
| -> Bool | To mirror or not  | 
| -> a | The x-coordinate of the end point  | 
| -> a | The y-coordinate of the end point  | 
| -> Path | 
Arguments
| :: Show a | |
| => a | Radius in the x-direction  | 
| -> a | Radius in the y-direction  | 
| -> a | The rotation of the arc's x-axis compared to the normal x-axis  | 
| -> Bool | True to draw the larger of the two arcs satisfying constraints.  | 
| -> Bool | To mirror or not  | 
| -> a | The x-coordinate of the end point  | 
| -> a | The y-coordinate of the end point  | 
| -> Path | 
Elliptical Arc (relative)
translate :: Show a => a -> a -> AttributeValue Source #
Specifies a translation by x and y
scale :: Show a => a -> a -> AttributeValue Source #
Specifies a scale operation by x and y
rotate :: Show a => a -> AttributeValue Source #
Specifies a rotation by rotate-angle degrees
rotateAround :: Show a => a -> a -> a -> AttributeValue Source #
Specifies a rotation by rotate-angle degrees about the given time rx,ry
skewX :: Show a => a -> AttributeValue Source #
Skew tansformation along x-axis
skewY :: Show a => a -> AttributeValue Source #
Skew tansformation along y-axis
matrix :: Show a => a -> a -> a -> a -> a -> a -> AttributeValue Source #
Specifies a transform in the form of a transformation matrix