module Graphics.Svg.Elements where
import Graphics.Svg.Core
doctype :: Element
doctype = makeElementDoctype "?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\""
svg11_:: Element -> Element
svg11_ = svg_ [ makeAttribute "xmlns" "http://www.w3.org/2000/svg"
              , makeAttribute "xmlns:xlink" "http://www.w3.org/1999/xlink"
              , makeAttribute "version" "1.1" ]
a_ :: Term result => [Attribute] -> result
a_ = term "a"
altGlyph_ :: Term result => [Attribute] -> result
altGlyph_ = term "altGlyph"
altGlyphDef_ :: Term result => [Attribute] -> result
altGlyphDef_ = term "altGlyphDef"
altGlyphItem_ :: Term result => [Attribute] -> result
altGlyphItem_ = term "altGlyphItem"
animate_ :: Term result => [Attribute] -> result
animate_ = term "animate"
animateColor_ :: Term result => [Attribute] -> result
animateColor_ = term "animateColor"
animateMotion_ :: Term result => [Attribute] -> result
animateMotion_ = term "animateMotion"
animateTransform_ :: Term result => [Attribute] -> result
animateTransform_ = term "animateTransform"
circle_ :: Term result => [Attribute] -> result
circle_ = term "circle"
clipPath_ :: Term result => [Attribute] -> result
clipPath_ = term "clipPath"
colorProfile_ :: Term result => [Attribute] -> result
colorProfile_ = term "color-profile"
cursor_ :: Term result => [Attribute] -> result
cursor_ = term "cursor"
defs_ :: Term result => [Attribute] -> result
defs_ = term "defs"
desc_ :: Term result => [Attribute] -> result
desc_ = term "desc"
ellipse_ :: Term result => [Attribute] -> result
ellipse_ = term "ellipse"
feBlend_ :: Term result => [Attribute] -> result
feBlend_ = term "feBlend"
feColorMatrix_ :: Term result => [Attribute] -> result
feColorMatrix_ = term "feColorMatrix"
feComponentTransfer_ :: Term result => [Attribute] -> result
feComponentTransfer_ = term "feComponentTransfer"
feComposite_ :: Term result => [Attribute] -> result
feComposite_ = term "feComposite"
feConvolveMatrix_ :: Term result => [Attribute] -> result
feConvolveMatrix_ = term "feConvolveMatrix"
feDiffuseLighting_ :: Term result => [Attribute] -> result
feDiffuseLighting_ = term "feDiffuseLighting"
feDisplacementMap_ :: Term result => [Attribute] -> result
feDisplacementMap_ = term "feDisplacementMap"
feDistantLight_ :: Term result => [Attribute] -> result
feDistantLight_ = term "feDistantLight"
feFlood_ :: Term result => [Attribute] -> result
feFlood_ = term "feFlood"
feFuncA_ :: Term result => [Attribute] -> result
feFuncA_ = term "feFuncA"
feFuncB_ :: Term result => [Attribute] -> result
feFuncB_ = term "feFuncB"
feFuncG_ :: Term result => [Attribute] -> result
feFuncG_ = term "feFuncG"
feFuncR_ :: Term result => [Attribute] -> result
feFuncR_ = term "feFuncR"
feGaussianBlur_ :: Term result => [Attribute] -> result
feGaussianBlur_ = term "feGaussianBlur"
feImage_ :: Term result => [Attribute] -> result
feImage_ = term "feImage"
feMerge_ :: Term result => [Attribute] -> result
feMerge_ = term "feMerge"
feMergeNode_ :: Term result => [Attribute] -> result
feMergeNode_ = term "feMergeNode"
feMorphology_ :: Term result => [Attribute] -> result
feMorphology_ = term "feMorphology"
feOffset_ :: Term result => [Attribute] -> result
feOffset_ = term "feOffset"
fePointLight_ :: Term result => [Attribute] -> result
fePointLight_ = term "fePointLight"
feSpecularLighting_ :: Term result => [Attribute] -> result
feSpecularLighting_ = term "feSpecularLighting"
feSpotLight_ :: Term result => [Attribute] -> result
feSpotLight_ = term "feSpotLight"
feTile_ :: Term result => [Attribute] -> result
feTile_ = term "feTile"
feTurbulence_ :: Term result => [Attribute] -> result
feTurbulence_ = term "feTurbulence"
filter_ :: Term result => [Attribute] -> result
filter_ = term "filter"
font_ :: Term result => [Attribute] -> result
font_ = term "font"
fontFace_ :: Term result => [Attribute] -> result
fontFace_ = term "font-face"
fontFaceFormat_ :: [Attribute] -> Element
fontFaceFormat_ = with $ makeElementNoEnd "font-face-format"
fontFaceName_ :: [Attribute] -> Element
fontFaceName_ = with $ makeElementNoEnd "font-face-name"
fontFaceSrc_ :: Term result => [Attribute] -> result
fontFaceSrc_ = term "font-face-src"
fontFaceUri_ :: Term result => [Attribute] -> result
fontFaceUri_ = term "font-face-uri"
foreignObject_ :: Term result => [Attribute] -> result
foreignObject_ = term "foreignObject"
g_ :: Term result => [Attribute] -> result
g_ = term "g"
glyph_ :: Term result => [Attribute] -> result
glyph_ = term "glyph"
glyphRef_ :: [Attribute] -> Element
glyphRef_ = with $ makeElementNoEnd "glyphRef"
hkern_ :: [Attribute] -> Element
hkern_ = with $ makeElementNoEnd "hkern"
image_ :: Term result => [Attribute] -> result
image_ = term "image"
line_ :: Term result => [Attribute] -> result
line_ = term "line"
linearGradient_ :: Term result => [Attribute] -> result
linearGradient_ = term "linearGradient"
marker_ :: Term result => [Attribute] -> result
marker_ = term "marker"
mask_ :: Term result => [Attribute] -> result
mask_ = term "mask"
metadata_ :: Term result => [Attribute] -> result
metadata_ = term "metadata"
missingGlyph_ :: Term result => [Attribute] -> result
missingGlyph_ = term "missing-glyph"
mpath_ :: Term result => [Attribute] -> result
mpath_ = term "mpath"
path_ :: Term result => [Attribute] -> result
path_ = term "path"
pattern_ :: Term result => [Attribute] -> result
pattern_ = term "pattern"
polygon_ :: Term result => [Attribute] -> result
polygon_ = term "polygon"
polyline_ :: Term result => [Attribute] -> result
polyline_ = term "polyline"
radialGradient_ :: Term result => [Attribute] -> result
radialGradient_ = term "radialGradient"
rect_ :: Term result => [Attribute] -> result
rect_ = term "rect"
script_ :: Term result => [Attribute] -> result
script_ = term "script"
set_ :: Term result => [Attribute] -> result
set_ = term "set"
stop_ :: Term result => [Attribute] -> result
stop_ = term "stop"
style_ :: Term result => [Attribute] -> result
style_ = term "style"
svg_ :: Term result => [Attribute] -> result
svg_ = term "svg"
switch_ :: Term result => [Attribute] -> result
switch_ = term "switch"
symbol_ :: Term result => [Attribute] -> result
symbol_ = term "symbol"
text_ :: Term result => [Attribute] -> result
text_ = term "text"
textPath_ :: Term result => [Attribute] -> result
textPath_ = term "textPath"
title_ :: Term result => [Attribute] -> result
title_ = term "title"
tref_ :: Term result => [Attribute] -> result
tref_ = term "tref"
tspan_ :: Term result => [Attribute] -> result
tspan_ = term "tspan"
use_ :: Term result => [Attribute] -> result
use_ = term "use"
view_ :: Term result => [Attribute] -> result
view_ = term "view"
vkern_ :: [Attribute] -> Element
vkern_ = with $ makeElementNoEnd "vkern"