Safe Haskell | None |
---|---|
Language | Haskell2010 |
Main functions for creating SVG dom elements via Reflex
Synopsis
- class AsSVGTag s where
- data BasicSVG
- data BasicInner = Animate
- data SVG_Root = SVG_Root
- type family CanBeNested a :: *
- data SVGEl t m a = SVGEl {
- _svgEl_el :: Element EventResult (DomBuilderSpace m) t
- _svgEl_children :: Dynamic t (Map (CanBeNested a) (Element EventResult (DomBuilderSpace m) t))
- svg_ :: (DomBuilder t m, PostBuild t m, Reflex t, AsSVGTag a) => Dynamic t SVG_El -> m (SVGEl t m a) -> m (Element EventResult (DomBuilderSpace m) t, SVGEl t m a)
- svgBasicDyn :: (DomBuilder t m, PostBuild t m, MonadFix m, MonadHold t m, AsSVGTag s, AsSVGTag (CanBeNested s), Ord (CanBeNested s)) => s -> (p -> Map Text Text) -> Dynamic t p -> Dynamic t (Map (CanBeNested s) (Map Text Text)) -> m (SVGEl t m s)
- svgBasicDyn_ :: (DomBuilder t m, PostBuild t m, MonadFix m, MonadHold t m, AsSVGTag s, AsSVGTag (CanBeNested s), Ord (CanBeNested s)) => s -> (p -> Map Text Text) -> Dynamic t p -> m (SVGEl t m s)
- svgElDynAttr' :: forall t m a e. (DomBuilder t m, PostBuild t m, AsSVGTag e) => e -> Dynamic t (Map Text Text) -> m a -> m (Element EventResult (DomBuilderSpace m) t, a)
- svgElDynAttr_ :: forall t m e. (DomBuilder t m, PostBuild t m, AsSVGTag e) => e -> Dynamic t (Map Text Text) -> m (Element EventResult (DomBuilderSpace m) t)
Documentation
class AsSVGTag s where Source #
Lawless class to provide a constraint indicating that a given type is capable of being represented by a SVG XML Tag. rect, circle, svg, etc.
svgTagName :: s -> Text Source #
Instances
AsSVGTag BasicInner Source # | |
Defined in Reflex.Dom.Widget.SVG svgTagName :: BasicInner -> Text Source # | |
AsSVGTag BasicSVG Source # | |
Defined in Reflex.Dom.Widget.SVG svgTagName :: BasicSVG -> Text Source # | |
AsSVGTag SVG_Root Source # | |
Defined in Reflex.Dom.Widget.SVG svgTagName :: SVG_Root -> Text Source # |
The basic SVG shapes.
data BasicInner Source #
The simplest inner element for a basic shape, the "animate" tag.
Instances
Eq BasicInner Source # | |
Defined in Reflex.Dom.Widget.SVG (==) :: BasicInner -> BasicInner -> Bool # (/=) :: BasicInner -> BasicInner -> Bool # | |
Ord BasicInner Source # | |
Defined in Reflex.Dom.Widget.SVG compare :: BasicInner -> BasicInner -> Ordering # (<) :: BasicInner -> BasicInner -> Bool # (<=) :: BasicInner -> BasicInner -> Bool # (>) :: BasicInner -> BasicInner -> Bool # (>=) :: BasicInner -> BasicInner -> Bool # max :: BasicInner -> BasicInner -> BasicInner # min :: BasicInner -> BasicInner -> BasicInner # | |
AsSVGTag BasicInner Source # | |
Defined in Reflex.Dom.Widget.SVG svgTagName :: BasicInner -> Text Source # |
The SVG Root element: "svg"
Instances
AsSVGTag SVG_Root Source # | |
Defined in Reflex.Dom.Widget.SVG svgTagName :: SVG_Root -> Text Source # |
type family CanBeNested a :: * Source #
Create a relationship between a set of SVG tags that can be nested inside a different set of SVG tags. Currently this just creates the relationship between the "animate" tag and the basic shapes ("rect", "circle", etc).
Instances
type CanBeNested BasicSVG Source # | |
Defined in Reflex.Dom.Widget.SVG |
This represents an SVG element, containing both the raw Reflex.Dom El
type
and a Dynamic
of all of the children that are nested in this element.
SVGEl | |
|
svg_ :: (DomBuilder t m, PostBuild t m, Reflex t, AsSVGTag a) => Dynamic t SVG_El -> m (SVGEl t m a) -> m (Element EventResult (DomBuilderSpace m) t, SVGEl t m a) Source #
Create the Root SVG element.
Note that there are no restrictions on the inner element, apart from the
return type being of m (SVGEl t a)
. So you are free to place whatever you
like in there, but bear in mind that the browser rules for SVG are still in
play. So text inputs etc, won't work.
svgBasicDyn :: (DomBuilder t m, PostBuild t m, MonadFix m, MonadHold t m, AsSVGTag s, AsSVGTag (CanBeNested s), Ord (CanBeNested s)) => s -> (p -> Map Text Text) -> Dynamic t p -> Dynamic t (Map (CanBeNested s) (Map Text Text)) -> m (SVGEl t m s) Source #
Create a SVG element that has dynamic attributes and contains children that are acceptable children for this element. "rect" as a Basic Shape can only contain "animate" elements, for example.
The SVG element will have some Dynamic
properties and a function that
allows these properties to be converted into a Map Text Text
, inline with
other Reflex.Dom widgets.
svgBasicDyn_ :: (DomBuilder t m, PostBuild t m, MonadFix m, MonadHold t m, AsSVGTag s, AsSVGTag (CanBeNested s), Ord (CanBeNested s)) => s -> (p -> Map Text Text) -> Dynamic t p -> m (SVGEl t m s) Source #
As per the svgBasicDyn
function, except with no inner elements.
svgElDynAttr' :: forall t m a e. (DomBuilder t m, PostBuild t m, AsSVGTag e) => e -> Dynamic t (Map Text Text) -> m a -> m (Element EventResult (DomBuilderSpace m) t, a) Source #
This is for creating a SVG element with Dynamic
attributes, and ensuring we
use the right namespace so the browser actually picks up on it. The name
space in use is "http://www.w3.org/2000/svg".
svgElDynAttr_ :: forall t m e. (DomBuilder t m, PostBuild t m, AsSVGTag e) => e -> Dynamic t (Map Text Text) -> m (Element EventResult (DomBuilderSpace m) t) Source #
As per svgElDynAttr'
, but does not have any children.