-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:69
--
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
-- | This module exports SVG combinators used to create documents.
--
module Text.Blaze.Svg11
    ( module Text.Blaze
    , module Text.Blaze.Svg
    , docType
    , docTypeSvg
    , a
    , altglyph
    , altglyphdef
    , altglyphitem
    , animate
    , animatecolor
    , animatemotion
    , animatetransform
    , circle
    , clippath
    , colorProfile
    , cursor
    , defs
    , desc
    , ellipse
    , feblend
    , fecolormatrix
    , fecomponenttransfer
    , fecomposite
    , feconvolvematrix
    , fediffuselighting
    , fedisplacementmap
    , fedistantlight
    , feflood
    , fefunca
    , fefuncb
    , fefuncg
    , fefuncr
    , fegaussianblur
    , feimage
    , femerge
    , femergenode
    , femorphology
    , feoffset
    , fepointlight
    , fespecularlighting
    , fespotlight
    , fetile
    , feturbulence
    , filter_
    , font
    , fontFace
    , fontFaceFormat
    , fontFaceName
    , fontFaceSrc
    , fontFaceUri
    , foreignobject
    , g
    , glyph
    , glyphref
    , hkern
    , image
    , line
    , lineargradient
    , marker
    , mask
    , metadata
    , missingGlyph
    , mpath
    , path
    , pattern
    , polygon
    , polyline
    , radialgradient
    , rect
    , script
    , set
    , stop
    , style
    , svg
    , switch
    , symbol
    , text_
    , textpath
    , title
    , tref
    , tspan
    , use
    , view
    , vkern
    ) where

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:79
--
import Prelude ((>>), (.), ($))

import Text.Blaze
import Text.Blaze.Svg
import Text.Blaze.Internal

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:168
--
-- | Combinator for the document type. This should be placed at the top
-- of every SVG page.
--
-- > <?xml version="1.0" encoding="UTF-8"?>
-- > <!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
-- >     "http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd">
--
docType :: Svg  -- ^ The document type SVG.
docType :: Svg
docType = Text -> Svg
preEscapedText Text
"<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n<!DOCTYPE svg PUBLIC \"-//W3C//DTD SVG 1.1//EN\"\n    \"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd\">\n"
{-# INLINE docType #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:183
--
-- | Combinator for the @\<svg>@ element. This combinator will also
-- insert the correct doctype.
--
docTypeSvg :: Svg  -- ^ Inner SVG.
            -> Svg  -- ^ Resulting SVG.
docTypeSvg :: Svg -> Svg
docTypeSvg Svg
inner = Svg
docType forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Svg -> Svg
svg forall h. Attributable h => h -> Attribute -> h
! Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"xmlns" Tag
" xmlns=\"" AttributeValue
"http://www.w3.org/2000/svg" forall h. Attributable h => h -> Attribute -> h
! Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"xmlns:xlink" Tag
" xmlns:xlink=\"" AttributeValue
"http://www.w3.org/1999/xlink"  forall a b. (a -> b) -> a -> b
$ Svg
inner)
{-# INLINE docTypeSvg #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<a>@ element.
--
a :: Svg  -- ^ Inner SVG.
  -> Svg  -- ^ Resulting SVG.
a :: Svg -> Svg
a = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"a" StaticString
"<a" StaticString
"</a>"
{-# INLINE a #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<altGlyph>@ element.
--
altglyph :: Svg  -- ^ Inner SVG.
         -> Svg  -- ^ Resulting SVG.
altglyph :: Svg -> Svg
altglyph = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"altGlyph" StaticString
"<altGlyph" StaticString
"</altGlyph>"
{-# INLINE altglyph #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<altGlyphDef />@ element.
--
altglyphdef :: Svg  -- ^ Resulting SVG.
altglyphdef :: Svg
altglyphdef = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"altGlyphDef" StaticString
"<altGlyphDef" StaticString
" />"
{-# INLINE altglyphdef #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<altGlyphItem />@ element.
--
altglyphitem :: Svg  -- ^ Resulting SVG.
altglyphitem :: Svg
altglyphitem = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"altGlyphItem" StaticString
"<altGlyphItem" StaticString
" />"
{-# INLINE altglyphitem #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<animate />@ element.
--
animate :: Svg  -- ^ Resulting SVG.
animate :: Svg
animate = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"animate" StaticString
"<animate" StaticString
" />"
{-# INLINE animate #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<animateColor />@ element.
--
animatecolor :: Svg  -- ^ Resulting SVG.
animatecolor :: Svg
animatecolor = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"animateColor" StaticString
"<animateColor" StaticString
" />"
{-# INLINE animatecolor #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<animateMotion />@ element.
--
animatemotion :: Svg  -- ^ Resulting SVG.
animatemotion :: Svg
animatemotion = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"animateMotion" StaticString
"<animateMotion" StaticString
" />"
{-# INLINE animatemotion #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<animateTransform />@ element.
--
animatetransform :: Svg  -- ^ Resulting SVG.
animatetransform :: Svg
animatetransform = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"animateTransform" StaticString
"<animateTransform" StaticString
" />"
{-# INLINE animatetransform #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<circle />@ element.
--
circle :: Svg  -- ^ Resulting SVG.
circle :: Svg
circle = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"circle" StaticString
"<circle" StaticString
" />"
{-# INLINE circle #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<clipPath>@ element.
--
clippath :: Svg  -- ^ Inner SVG.
         -> Svg  -- ^ Resulting SVG.
clippath :: Svg -> Svg
clippath = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"clipPath" StaticString
"<clipPath" StaticString
"</clipPath>"
{-# INLINE clippath #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<color-profile />@ element.
--
colorProfile :: Svg  -- ^ Resulting SVG.
colorProfile :: Svg
colorProfile = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"color-profile" StaticString
"<color-profile" StaticString
" />"
{-# INLINE colorProfile #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<cursor />@ element.
--
cursor :: Svg  -- ^ Resulting SVG.
cursor :: Svg
cursor = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"cursor" StaticString
"<cursor" StaticString
" />"
{-# INLINE cursor #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<defs>@ element.
--
defs :: Svg  -- ^ Inner SVG.
     -> Svg  -- ^ Resulting SVG.
defs :: Svg -> Svg
defs = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"defs" StaticString
"<defs" StaticString
"</defs>"
{-# INLINE defs #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<desc>@ element.
--
desc :: Svg  -- ^ Inner SVG.
     -> Svg  -- ^ Resulting SVG.
desc :: Svg -> Svg
desc = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"desc" StaticString
"<desc" StaticString
"</desc>"
{-# INLINE desc #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<ellipse />@ element.
--
ellipse :: Svg  -- ^ Resulting SVG.
ellipse :: Svg
ellipse = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"ellipse" StaticString
"<ellipse" StaticString
" />"
{-# INLINE ellipse #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feBlend />@ element.
--
feblend :: Svg  -- ^ Resulting SVG.
feblend :: Svg
feblend = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feBlend" StaticString
"<feBlend" StaticString
" />"
{-# INLINE feblend #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feColorMatrix />@ element.
--
fecolormatrix :: Svg  -- ^ Resulting SVG.
fecolormatrix :: Svg
fecolormatrix = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feColorMatrix" StaticString
"<feColorMatrix" StaticString
" />"
{-# INLINE fecolormatrix #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feComponentTransfer />@ element.
--
fecomponenttransfer :: Svg  -- ^ Resulting SVG.
fecomponenttransfer :: Svg
fecomponenttransfer = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feComponentTransfer" StaticString
"<feComponentTransfer" StaticString
" />"
{-# INLINE fecomponenttransfer #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feComposite />@ element.
--
fecomposite :: Svg  -- ^ Resulting SVG.
fecomposite :: Svg
fecomposite = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feComposite" StaticString
"<feComposite" StaticString
" />"
{-# INLINE fecomposite #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feConvolveMatrix />@ element.
--
feconvolvematrix :: Svg  -- ^ Resulting SVG.
feconvolvematrix :: Svg
feconvolvematrix = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feConvolveMatrix" StaticString
"<feConvolveMatrix" StaticString
" />"
{-# INLINE feconvolvematrix #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feDiffuseLighting />@ element.
--
fediffuselighting :: Svg  -- ^ Resulting SVG.
fediffuselighting :: Svg
fediffuselighting = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feDiffuseLighting" StaticString
"<feDiffuseLighting" StaticString
" />"
{-# INLINE fediffuselighting #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feDisplacementMap />@ element.
--
fedisplacementmap :: Svg  -- ^ Resulting SVG.
fedisplacementmap :: Svg
fedisplacementmap = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feDisplacementMap" StaticString
"<feDisplacementMap" StaticString
" />"
{-# INLINE fedisplacementmap #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feDistantLight />@ element.
--
fedistantlight :: Svg  -- ^ Resulting SVG.
fedistantlight :: Svg
fedistantlight = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feDistantLight" StaticString
"<feDistantLight" StaticString
" />"
{-# INLINE fedistantlight #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feFlood />@ element.
--
feflood :: Svg  -- ^ Resulting SVG.
feflood :: Svg
feflood = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feFlood" StaticString
"<feFlood" StaticString
" />"
{-# INLINE feflood #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feFuncA />@ element.
--
fefunca :: Svg  -- ^ Resulting SVG.
fefunca :: Svg
fefunca = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feFuncA" StaticString
"<feFuncA" StaticString
" />"
{-# INLINE fefunca #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feFuncB />@ element.
--
fefuncb :: Svg  -- ^ Resulting SVG.
fefuncb :: Svg
fefuncb = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feFuncB" StaticString
"<feFuncB" StaticString
" />"
{-# INLINE fefuncb #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feFuncG />@ element.
--
fefuncg :: Svg  -- ^ Resulting SVG.
fefuncg :: Svg
fefuncg = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feFuncG" StaticString
"<feFuncG" StaticString
" />"
{-# INLINE fefuncg #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feFuncR />@ element.
--
fefuncr :: Svg  -- ^ Resulting SVG.
fefuncr :: Svg
fefuncr = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feFuncR" StaticString
"<feFuncR" StaticString
" />"
{-# INLINE fefuncr #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feGaussianBlur />@ element.
--
fegaussianblur :: Svg  -- ^ Resulting SVG.
fegaussianblur :: Svg
fegaussianblur = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feGaussianBlur" StaticString
"<feGaussianBlur" StaticString
" />"
{-# INLINE fegaussianblur #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feImage />@ element.
--
feimage :: Svg  -- ^ Resulting SVG.
feimage :: Svg
feimage = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feImage" StaticString
"<feImage" StaticString
" />"
{-# INLINE feimage #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feMerge />@ element.
--
femerge :: Svg  -- ^ Resulting SVG.
femerge :: Svg
femerge = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feMerge" StaticString
"<feMerge" StaticString
" />"
{-# INLINE femerge #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feMergeNode />@ element.
--
femergenode :: Svg  -- ^ Resulting SVG.
femergenode :: Svg
femergenode = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feMergeNode" StaticString
"<feMergeNode" StaticString
" />"
{-# INLINE femergenode #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feMorphology />@ element.
--
femorphology :: Svg  -- ^ Resulting SVG.
femorphology :: Svg
femorphology = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feMorphology" StaticString
"<feMorphology" StaticString
" />"
{-# INLINE femorphology #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feOffset />@ element.
--
feoffset :: Svg  -- ^ Resulting SVG.
feoffset :: Svg
feoffset = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feOffset" StaticString
"<feOffset" StaticString
" />"
{-# INLINE feoffset #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<fePointLight />@ element.
--
fepointlight :: Svg  -- ^ Resulting SVG.
fepointlight :: Svg
fepointlight = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"fePointLight" StaticString
"<fePointLight" StaticString
" />"
{-# INLINE fepointlight #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feSpecularLighting />@ element.
--
fespecularlighting :: Svg  -- ^ Resulting SVG.
fespecularlighting :: Svg
fespecularlighting = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feSpecularLighting" StaticString
"<feSpecularLighting" StaticString
" />"
{-# INLINE fespecularlighting #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feSpotLight />@ element.
--
fespotlight :: Svg  -- ^ Resulting SVG.
fespotlight :: Svg
fespotlight = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feSpotLight" StaticString
"<feSpotLight" StaticString
" />"
{-# INLINE fespotlight #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feTile />@ element.
--
fetile :: Svg  -- ^ Resulting SVG.
fetile :: Svg
fetile = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feTile" StaticString
"<feTile" StaticString
" />"
{-# INLINE fetile #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<feTurbulence />@ element.
--
feturbulence :: Svg  -- ^ Resulting SVG.
feturbulence :: Svg
feturbulence = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"feTurbulence" StaticString
"<feTurbulence" StaticString
" />"
{-# INLINE feturbulence #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<filter>@ element.
--
filter_ :: Svg  -- ^ Inner SVG.
        -> Svg  -- ^ Resulting SVG.
filter_ :: Svg -> Svg
filter_ = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"filter" StaticString
"<filter" StaticString
"</filter>"
{-# INLINE filter_ #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<font />@ element.
--
font :: Svg  -- ^ Resulting SVG.
font :: Svg
font = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"font" StaticString
"<font" StaticString
" />"
{-# INLINE font #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<font-face />@ element.
--
fontFace :: Svg  -- ^ Resulting SVG.
fontFace :: Svg
fontFace = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"font-face" StaticString
"<font-face" StaticString
" />"
{-# INLINE fontFace #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<font-face-format />@ element.
--
fontFaceFormat :: Svg  -- ^ Resulting SVG.
fontFaceFormat :: Svg
fontFaceFormat = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"font-face-format" StaticString
"<font-face-format" StaticString
" />"
{-# INLINE fontFaceFormat #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<font-face-name />@ element.
--
fontFaceName :: Svg  -- ^ Resulting SVG.
fontFaceName :: Svg
fontFaceName = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"font-face-name" StaticString
"<font-face-name" StaticString
" />"
{-# INLINE fontFaceName #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<font-face-src />@ element.
--
fontFaceSrc :: Svg  -- ^ Resulting SVG.
fontFaceSrc :: Svg
fontFaceSrc = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"font-face-src" StaticString
"<font-face-src" StaticString
" />"
{-# INLINE fontFaceSrc #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<font-face-uri />@ element.
--
fontFaceUri :: Svg  -- ^ Resulting SVG.
fontFaceUri :: Svg
fontFaceUri = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"font-face-uri" StaticString
"<font-face-uri" StaticString
" />"
{-# INLINE fontFaceUri #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<foreignObject>@ element.
--
foreignobject :: Svg  -- ^ Inner SVG.
              -> Svg  -- ^ Resulting SVG.
foreignobject :: Svg -> Svg
foreignobject = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"foreignObject" StaticString
"<foreignObject" StaticString
"</foreignObject>"
{-# INLINE foreignobject #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<g>@ element.
--
g :: Svg  -- ^ Inner SVG.
  -> Svg  -- ^ Resulting SVG.
g :: Svg -> Svg
g = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"g" StaticString
"<g" StaticString
"</g>"
{-# INLINE g #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<glyph>@ element.
--
glyph :: Svg  -- ^ Inner SVG.
      -> Svg  -- ^ Resulting SVG.
glyph :: Svg -> Svg
glyph = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"glyph" StaticString
"<glyph" StaticString
"</glyph>"
{-# INLINE glyph #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<glyphRef />@ element.
--
glyphref :: Svg  -- ^ Resulting SVG.
glyphref :: Svg
glyphref = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"glyphRef" StaticString
"<glyphRef" StaticString
" />"
{-# INLINE glyphref #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<hkern />@ element.
--
hkern :: Svg  -- ^ Resulting SVG.
hkern :: Svg
hkern = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"hkern" StaticString
"<hkern" StaticString
" />"
{-# INLINE hkern #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<image />@ element.
--
image :: Svg  -- ^ Resulting SVG.
image :: Svg
image = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"image" StaticString
"<image" StaticString
" />"
{-# INLINE image #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<line />@ element.
--
line :: Svg  -- ^ Resulting SVG.
line :: Svg
line = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"line" StaticString
"<line" StaticString
" />"
{-# INLINE line #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<linearGradient>@ element.
--
lineargradient :: Svg  -- ^ Inner SVG.
               -> Svg  -- ^ Resulting SVG.
lineargradient :: Svg -> Svg
lineargradient = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"linearGradient" StaticString
"<linearGradient" StaticString
"</linearGradient>"
{-# INLINE lineargradient #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<marker>@ element.
--
marker :: Svg  -- ^ Inner SVG.
       -> Svg  -- ^ Resulting SVG.
marker :: Svg -> Svg
marker = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"marker" StaticString
"<marker" StaticString
"</marker>"
{-# INLINE marker #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<mask>@ element.
--
mask :: Svg  -- ^ Inner SVG.
     -> Svg  -- ^ Resulting SVG.
mask :: Svg -> Svg
mask = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"mask" StaticString
"<mask" StaticString
"</mask>"
{-# INLINE mask #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<metadata>@ element.
--
metadata :: Svg  -- ^ Inner SVG.
         -> Svg  -- ^ Resulting SVG.
metadata :: Svg -> Svg
metadata = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"metadata" StaticString
"<metadata" StaticString
"</metadata>"
{-# INLINE metadata #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<missing-glyph>@ element.
--
missingGlyph :: Svg  -- ^ Inner SVG.
             -> Svg  -- ^ Resulting SVG.
missingGlyph :: Svg -> Svg
missingGlyph = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"missing-glyph" StaticString
"<missing-glyph" StaticString
"</missing-glyph>"
{-# INLINE missingGlyph #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<mpath />@ element.
--
mpath :: Svg  -- ^ Resulting SVG.
mpath :: Svg
mpath = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"mpath" StaticString
"<mpath" StaticString
" />"
{-# INLINE mpath #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<path />@ element.
--
path :: Svg  -- ^ Resulting SVG.
path :: Svg
path = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"path" StaticString
"<path" StaticString
" />"
{-# INLINE path #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<pattern>@ element.
--
pattern :: Svg  -- ^ Inner SVG.
        -> Svg  -- ^ Resulting SVG.
pattern :: Svg -> Svg
pattern = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"pattern" StaticString
"<pattern" StaticString
"</pattern>"
{-# INLINE pattern #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<polygon />@ element.
--
polygon :: Svg  -- ^ Resulting SVG.
polygon :: Svg
polygon = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"polygon" StaticString
"<polygon" StaticString
" />"
{-# INLINE polygon #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<polyline />@ element.
--
polyline :: Svg  -- ^ Resulting SVG.
polyline :: Svg
polyline = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"polyline" StaticString
"<polyline" StaticString
" />"
{-# INLINE polyline #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<radialGradient>@ element.
--
radialgradient :: Svg  -- ^ Inner SVG.
               -> Svg  -- ^ Resulting SVG.
radialgradient :: Svg -> Svg
radialgradient = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"radialGradient" StaticString
"<radialGradient" StaticString
"</radialGradient>"
{-# INLINE radialgradient #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<rect />@ element.
--
rect :: Svg  -- ^ Resulting SVG.
rect :: Svg
rect = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"rect" StaticString
"<rect" StaticString
" />"
{-# INLINE rect #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<script>@ element.
--
script :: Svg  -- ^ Inner SVG.
       -> Svg  -- ^ Resulting SVG.
script :: Svg -> Svg
script = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"script" StaticString
"<script" StaticString
"</script>" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. MarkupM a -> MarkupM a
external
{-# INLINE script #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<set />@ element.
--
set :: Svg  -- ^ Resulting SVG.
set :: Svg
set = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"set" StaticString
"<set" StaticString
" />"
{-# INLINE set #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<stop />@ element.
--
stop :: Svg  -- ^ Resulting SVG.
stop :: Svg
stop = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"stop" StaticString
"<stop" StaticString
" />"
{-# INLINE stop #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<style>@ element.
--
style :: Svg  -- ^ Inner SVG.
      -> Svg  -- ^ Resulting SVG.
style :: Svg -> Svg
style = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"style" StaticString
"<style" StaticString
"</style>" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. MarkupM a -> MarkupM a
external
{-# INLINE style #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<svg>@ element.
--
svg :: Svg  -- ^ Inner SVG.
    -> Svg  -- ^ Resulting SVG.
svg :: Svg -> Svg
svg = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"svg" StaticString
"<svg" StaticString
"</svg>"
{-# INLINE svg #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<switch>@ element.
--
switch :: Svg  -- ^ Inner SVG.
       -> Svg  -- ^ Resulting SVG.
switch :: Svg -> Svg
switch = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"switch" StaticString
"<switch" StaticString
"</switch>"
{-# INLINE switch #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<symbol>@ element.
--
symbol :: Svg  -- ^ Inner SVG.
       -> Svg  -- ^ Resulting SVG.
symbol :: Svg -> Svg
symbol = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"symbol" StaticString
"<symbol" StaticString
"</symbol>"
{-# INLINE symbol #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<text>@ element.
--
text_ :: Svg  -- ^ Inner SVG.
      -> Svg  -- ^ Resulting SVG.
text_ :: Svg -> Svg
text_ = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"text" StaticString
"<text" StaticString
"</text>"
{-# INLINE text_ #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<textPath>@ element.
--
textpath :: Svg  -- ^ Inner SVG.
         -> Svg  -- ^ Resulting SVG.
textpath :: Svg -> Svg
textpath = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"textPath" StaticString
"<textPath" StaticString
"</textPath>"
{-# INLINE textpath #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<title>@ element.
--
title :: Svg  -- ^ Inner SVG.
      -> Svg  -- ^ Resulting SVG.
title :: Svg -> Svg
title = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"title" StaticString
"<title" StaticString
"</title>"
{-# INLINE title #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<tref />@ element.
--
tref :: Svg  -- ^ Resulting SVG.
tref :: Svg
tref = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"tref" StaticString
"<tref" StaticString
" />"
{-# INLINE tref #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:197
--
-- | Combinator for the @\<tspan>@ element.
--
tspan :: Svg  -- ^ Inner SVG.
      -> Svg  -- ^ Resulting SVG.
tspan :: Svg -> Svg
tspan = forall a.
StaticString
-> StaticString -> StaticString -> MarkupM a -> MarkupM a
Parent StaticString
"tspan" StaticString
"<tspan" StaticString
"</tspan>"
{-# INLINE tspan #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<use />@ element.
--
use :: Svg  -- ^ Resulting SVG.
use :: Svg
use = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"use" StaticString
"<use" StaticString
" />"
{-# INLINE use #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<view />@ element.
--
view :: Svg  -- ^ Resulting SVG.
view :: Svg
view = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"view" StaticString
"<view" StaticString
" />"
{-# INLINE view #-}

-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:216
--
-- | Combinator for the @\<vkern />@ element.
--
vkern :: Svg  -- ^ Resulting SVG.
vkern :: Svg
vkern = StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
"vkern" StaticString
"<vkern" StaticString
" />"
{-# INLINE vkern #-}


-- WARNING: The next block of code was automatically generated by
-- src/Util/GenerateSvgCombinators.hs:89
--
leaf :: StaticString -> StaticString -> StaticString -> Svg
#if MIN_VERSION_blaze_markup(0,8,0)
leaf :: StaticString -> StaticString -> StaticString -> Svg
leaf StaticString
tag StaticString
open StaticString
close = forall a.
StaticString -> StaticString -> StaticString -> a -> MarkupM a
Leaf StaticString
tag StaticString
open StaticString
close ()
#else
leaf = Leaf
#endif
{-# INLINE leaf #-}