blaze-svg-0.3.5/0000755000000000000000000000000012642557533011613 5ustar0000000000000000blaze-svg-0.3.5/CHANGES.md0000644000000000000000000000050012642557533013200 0ustar00000000000000000.3.5 (4 January 2016) ---------------------- * Added support for elliptical arcs (aa, ar) 0.3.4.1 (24 February 2015) -------------------------- * Allow `blaze-markup-0.7` 0.3.4 (21 May 2014) ------------------- * export `rotateAround` 0.3.3.1 (3 February 2014) ------------------------- * Allow blaze-markup-0.6 blaze-svg-0.3.5/blaze-svg.cabal0000644000000000000000000000316012642557533014471 0ustar0000000000000000name: blaze-svg version: 0.3.5 synopsis: SVG combinator library homepage: https://github.com/deepakjois/blaze-svg license: BSD3 license-file: LICENSE author: Deepak Jois maintainer: deepak.jois@gmail.com category: Graphics build-type: Simple cabal-version: >=1.8 description: A blazingly fast SVG combinator library for the Haskell programming language. The "Text.Blaze.SVG" module is a good starting point. . Other documentation: . * Programs in the /examples/ folder of this project: . * Jasper Van Der Jeugt has written a tutorial for /blaze-html/, which is a sister library of /blaze-svg/. It may not be directly relevant, but still it gives a good overview on how to use the combinators in "Text.Blaze.Svg11" and "Text.Blaze.Svg11.Attributes": . Extra-source-files: src/Util/Sanitize.hs src/Util/GenerateSvgCombinators.hs examples/*.hs CHANGES.md Library Hs-Source-Dirs: src Ghc-Options: -Wall Exposed-modules: Text.Blaze.Svg Text.Blaze.Svg.Internal Text.Blaze.Svg11 Text.Blaze.Svg11.Attributes Text.Blaze.Svg.Renderer.Pretty Text.Blaze.Svg.Renderer.String Text.Blaze.Svg.Renderer.Text Text.Blaze.Svg.Renderer.Utf8 Build-depends: base >= 4 && < 5, mtl >= 2 && < 3, blaze-markup >= 0.5 && < 0.8 Source-repository head Type: git Location: http://github.com/deepakjois/blaze-svg.git blaze-svg-0.3.5/Setup.hs0000644000000000000000000000005612642557533013250 0ustar0000000000000000import Distribution.Simple main = defaultMain blaze-svg-0.3.5/LICENSE0000644000000000000000000000276012642557533012625 0ustar0000000000000000Copyright (c) 2012, Deepak Jois All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of Deepak Jois nor the names of other contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. blaze-svg-0.3.5/src/0000755000000000000000000000000012642557533012402 5ustar0000000000000000blaze-svg-0.3.5/src/Util/0000755000000000000000000000000012642557533013317 5ustar0000000000000000blaze-svg-0.3.5/src/Util/GenerateSvgCombinators.hs0000644000000000000000000003253212642557533020273 0ustar0000000000000000{-# LANGUAGE CPP #-} #define DO_NOT_EDIT (doNotEdit __FILE__ __LINE__) -- | Generates code for SVG tags. -- module Util.GenerateSvgCombinators where import Control.Arrow ((&&&)) import Data.List (sort, sortBy, intersperse, intercalate) import Data.Ord (comparing) import System.Directory (createDirectoryIfMissing) import System.FilePath ((), (<.>)) import Data.Map (Map) import qualified Data.Map as M import Data.Char (toLower) import qualified Data.Set as S import Util.Sanitize (sanitize, prelude) -- | Datatype for an SVG variant. -- data SvgVariant = SvgVariant { version :: [String] , docType :: [String] , parents :: [String] , leafs :: [String] , attributes :: [String] , selfClosing :: Bool } deriving (Eq) instance Show SvgVariant where show = map toLower . intercalate "-" . version -- | Get the full module name for an SVG variant. -- getModuleName :: SvgVariant -> String getModuleName = ("Text.Blaze." ++) . intercalate "." . version -- | Get the attribute module name for an SVG variant. -- getAttributeModuleName :: SvgVariant -> String getAttributeModuleName = (++ ".Attributes") . getModuleName -- | Check if a given name causes a name clash. -- isNameClash :: SvgVariant -> String -> Bool isNameClash v t -- Both an element and an attribute | (t `elem` parents v || t `elem` leafs v) && t `elem` attributes v = True -- Already a prelude function | sanitize t `S.member` prelude = True | otherwise = False -- | Write an SVG variant. -- writeSvgVariant :: SvgVariant -> IO () writeSvgVariant svgVariant = do -- Make a directory. createDirectoryIfMissing True basePath let tags = zip parents' (repeat makeParent) ++ zip leafs' (repeat (makeLeaf $ selfClosing svgVariant)) sortedTags = sortBy (comparing fst) tags appliedTags = map (\(x, f) -> f x) sortedTags -- Write the main module. writeFile' (basePath <.> "hs") $ removeTrailingNewlines $ unlines [ DO_NOT_EDIT , "{-# LANGUAGE OverloadedStrings #-}" , "-- | This module exports SVG combinators used to create documents." , "--" , exportList modulName $ "module Text.Blaze" : "module Text.Blaze.Svg" : "docType" : "docTypeSvg" : map (sanitize . fst) sortedTags , DO_NOT_EDIT , "import Prelude ((>>), (.), ($))" , "" , "import Text.Blaze" , "import Text.Blaze.Svg" , "import Text.Blaze.Internal" , "" , makeDocType $ docType svgVariant , makeDocTypeSvg $ docType svgVariant , unlines appliedTags ] let sortedAttributes = sort attributes' -- Write the attribute module. writeFile' (basePath "Attributes.hs") $ removeTrailingNewlines $ unlines [ DO_NOT_EDIT , "-- | This module exports combinators that provide you with the" , "-- ability to set attributes on SVG elements." , "--" , "{-# LANGUAGE OverloadedStrings #-}" , exportList attributeModuleName $ map sanitize sortedAttributes , DO_NOT_EDIT , "import Prelude ()" , "" , "import Text.Blaze.Internal (Attribute, AttributeValue, attribute)" , "" , unlines (map makeAttribute sortedAttributes) ] where basePath = "src" "Text" "Blaze" foldl1 () version' modulName = getModuleName svgVariant attributeModuleName = getAttributeModuleName svgVariant attributes' = attributes svgVariant parents' = parents svgVariant leafs' = leafs svgVariant version' = version svgVariant removeTrailingNewlines = reverse . drop 2 . reverse writeFile' file content = do putStrLn ("Generating " ++ file) writeFile file content -- | Create a string, consisting of @x@ spaces, where @x@ is the length of the -- argument. -- spaces :: String -> String spaces = flip replicate ' ' . length -- | Join blocks of code with a newline in between. -- unblocks :: [String] -> String unblocks = unlines . intersperse "\n" -- | A warning to not edit the generated code. -- doNotEdit :: FilePath -> Int -> String doNotEdit fileName lineNumber = init $ unlines [ "-- WARNING: The next block of code was automatically generated by" , "-- " ++ fileName ++ ":" ++ show lineNumber , "--" ] -- | Generate an export list for a Haskell module. -- exportList :: String -- ^ Module name. -> [String] -- ^ List of functions. -> String -- ^ Resulting string. exportList _ [] = error "exportList without functions." exportList name (f:functions) = unlines $ [ "module " ++ name , " ( " ++ f ] ++ map (" , " ++) functions ++ [ " ) where"] -- | Generate a function for a doctype. -- makeDocType :: [String] -> String makeDocType lines' = unlines [ DO_NOT_EDIT , "-- | Combinator for the document type. This should be placed at the top" , "-- of every SVG page." , "--" , unlines (map ("-- > " ++) lines') ++ "--" , "docType :: Svg -- ^ The document type SVG." , "docType = preEscapedText " ++ show (unlines lines') , "{-# INLINE docType #-}" ] -- | Generate a function for the SVG tag (including the doctype). -- makeDocTypeSvg :: [String] -- ^ The doctype. -> String -- ^ Resulting combinator function. makeDocTypeSvg lines' = unlines [ DO_NOT_EDIT , "-- | Combinator for the @\\@ element. This combinator will also" , "-- insert the correct doctype." , "--" , "docTypeSvg :: Svg -- ^ Inner SVG." , " -> Svg -- ^ Resulting SVG." , "docTypeSvg inner = docType >> (svg ! attribute \"xmlns\" \" xmlns=\\\"\" \"http://www.w3.org/2000/svg\" ! attribute \"xmlns:xlink\" \" xmlns:xlink=\\\"\" \"http://www.w3.org/1999/xlink\" $ inner)" , "{-# INLINE docTypeSvg #-}" ] -- | Generate a function for an SVG tag that can be a parent. -- makeParent :: String -> String makeParent tag = unlines [ DO_NOT_EDIT , "-- | Combinator for the @\\<" ++ tag ++ ">@ element." , "--" , function ++ " :: Svg -- ^ Inner SVG." , spaces function ++ " -> Svg -- ^ Resulting SVG." , function ++ " = Parent \"" ++ tag ++ "\" \"<" ++ tag ++ "\" \"\"" ++ modifier , "{-# INLINE " ++ function ++ " #-}" ] where function = sanitize tag modifier = if tag `elem` ["style", "script"] then " . external" else "" -- | Generate a function for an SVG tag that must be a leaf. -- makeLeaf :: Bool -- ^ Make leaf tags self-closing -> String -- ^ Tag for the combinator -> String -- ^ Combinator code makeLeaf closing tag = unlines [ DO_NOT_EDIT , "-- | Combinator for the @\\<" ++ tag ++ " />@ element." , "--" , function ++ " :: Svg -- ^ Resulting SVG." , function ++ " = Leaf \"" ++ tag ++ "\" \"<" ++ tag ++ "\" " ++ "\"" ++ (if closing then " /" else "") ++ ">\"" , "{-# INLINE " ++ function ++ " #-}" ] where function = sanitize tag -- | Generate a function for an SVG attribute. -- makeAttribute :: String -> String makeAttribute name = unlines [ DO_NOT_EDIT , "-- | Combinator for the @" ++ name ++ "@ attribute." , "--" , function ++ " :: AttributeValue -- ^ Attribute value." , spaces function ++ " -> Attribute -- ^ Resulting attribute." , function ++ " = attribute \"" ++ name ++ "\" \" " ++ name ++ "=\\\"\"" , "{-# INLINE " ++ function ++ " #-}" ] where function = sanitize name -- | SVG 1.1 -- Reference: https://developer.mozilla.org/en/SVG -- svg11 :: SvgVariant svg11 = SvgVariant { version = ["Svg11"] , docType = [ "" , "" ] , parents = [ "a","defs","glyph","g","marker","mask","missing-glyph","pattern", "svg" , "switch", "symbol", "linearGradient", "radialGradient", "clipPath", "text" ] , leafs = [ "altGlyph", "altGlyphDef", "altGlyphItem", "animate", "animateColor" , "animateMotion", "animateTransform", "circle", "color-profile" , "cursor", "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" , "font-face", "font-face-format" , "font-face-name", "font-face-src" , "font-face-uri", "foreignObject" , "glyphRef", "hkern", "image" , "line", "metadata", "mpath", "path" , "polygon" , "polyline", "rect", "script", "set" , "stop", "style" , "textPath", "title", "tref", "tspan", "use" , "view", "vkern" ] , attributes = [ "accent-height", "accumulate", "additive", "alphabetic", "amplitude" , "arabic-form", "ascent", "attributeName", "attributeType", "azimuth" , "baseFrequency", "baseProfile", "bbox", "begin", "bias", "by", "calcMode" , "cap-height", "class", "clipPathUnits", "contentScriptType" , "contentStyleType", "cx", "cy", "d", "descent", "diffuseConstant", "divisor" , "dur", "dx", "dy", "edgeMode", "elevation", "end", "exponent" , "externalResourcesRequired", "fill", "filterRes", "filterUnits", "font-family" , "font-size", "font-stretch", "font-style", "font-variant", "font-weight" , "format", "from", "fx", "fy", "g1", "g2", "glyph-name", "glyphRef" , "gradientTransform", "gradientUnits", "hanging", "height", "horiz-adv-x" , "horiz-origin-x", "horiz-origin-y", "id", "ideographic", "in", "in2" , "intercept", "k", "k1", "k2", "k3", "k4", "kernelMatrix", "kernelUnitLength" , "keyPoints", "keySplines", "keyTimes", "lang", "lengthAdjust" , "limitingConeAngle", "local", "markerHeight", "markerUnits", "markerWidth" , "maskContentUnits", "maskUnits", "mathematical", "max", "media", "method" , "min", "mode", "name", "numOctaves", "offset", "onabort", "onactivate" , "onbegin", "onclick", "onend", "onerror", "onfocusin", "onfocusout", "onload" , "onmousedown", "onmousemove", "onmouseout", "onmouseover", "onmouseup" , "onrepeat", "onresize", "onscroll", "onunload", "onzoom", "operator", "order" , "orient", "orientation", "origin", "overline-position", "overline-thickness" , "panose-1", "path", "pathLength", "patternContentUnits", "patternTransform" , "patternUnits", "points", "pointsAtX", "pointsAtY", "pointsAtZ" , "preserveAlpha", "preserveAspectRatio", "primitiveUnits", "r", "radius" , "refX", "refY", "rendering-intent", "repeatCount", "repeatDur" , "requiredExtensions", "requiredFeatures", "restart", "result", "rotate", "rx" , "ry", "scale", "seed", "slope", "spacing", "specularConstant" , "specularExponent", "spreadMethod", "startOffset", "stdDeviation", "stemh" , "stemv", "stitchTiles", "strikethrough-position", "strikethrough-thickness" , "string", "style", "surfaceScale", "systemLanguage", "tableValues", "target" , "targetX", "targetY", "textLength", "title", "to", "transform", "type", "u1" , "u2", "underline-position", "underline-thickness", "unicode", "unicode-range" , "units-per-em", "v-alphabetic", "v-hanging", "v-ideographic", "v-mathematical" , "values", "version", "vert-adv-y", "vert-origin-x", "vert-origin-y", "viewBox" , "viewTarget", "width", "widths", "x", "x-height", "x1", "x2" , "xChannelSelector", "xlink:actuate", "xlink:arcrole", "xlink:href" , "xlink:role", "xlink:show", "xlink:title", "xlink:type", "xml:base" , "xml:lang", "xml:space", "y", "y1", "y2", "yChannelSelector", "z", "zoomAndPan" -- Presentation Attributes , "alignment-baseline", "baseline-shift", "clip-path", "clip-rule" , "clip", "color-interpolation-filters", "color-interpolation" , "color-profile", "color-rendering", "color", "cursor", "direction" , "display", "dominant-baseline", "enable-background", "fill-opacity" , "fill-rule", "filter", "flood-color", "flood-opacity" , "font-size-adjust", "glyph-orientation-horizontal" , "glyph-orientation-vertical", "image-rendering", "kerning", "letter-spacing" , "lighting-color", "marker-end", "marker-mid", "marker-start", "mask" , "opacity", "overflow", "pointer-events", "shape-rendering", "stop-color" , "stop-opacity", "stroke-dasharray", "stroke-dashoffset", "stroke-linecap" , "stroke-linejoin", "stroke-miterlimit", "stroke-opacity", "stroke-width" , "stroke", "text-anchor", "text-decoration", "text-rendering", "unicode-bidi" , "visibility", "word-spacing", "writing-mode" ] , selfClosing = True } -- | A map of SVG variants, per version, lowercase. -- svgVariants :: Map String SvgVariant svgVariants = M.fromList $ map (show &&& id) [ svg11 ] main :: IO () main = mapM_ (writeSvgVariant . snd) $ M.toList svgVariants ����������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Util/Sanitize.hs����������������������������������������������������������������0000644�0000000�0000000�00000006574�12642557533�015455� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������-- | A program to sanitize an HTML tag to a Haskell function. -- module Util.Sanitize ( sanitize , keywords , prelude ) where import Data.Char (toLower, toUpper) import Data.Set (Set) import qualified Data.Set as S -- | Sanitize a tag. This function returns a name that can be used as -- combinator in haskell source code. -- -- Examples: -- -- > sanitize "class" == "class_" -- > sanitize "http-equiv" == "httpEquiv" -- sanitize :: String -> String sanitize = appendUnderscore . removeDashOrColon . map toLower where -- Remove a dash, replacing it by camelcase notation -- -- Example: -- -- > removeDashOrColon "foo-bar" == "fooBar" -- removeDashOrColon ('-' : x : xs) = toUpper x : removeDashOrColon xs removeDashOrColon (':' : x : xs) = toUpper x : removeDashOrColon xs removeDashOrColon (x : xs) = x : removeDashOrColon xs removeDashOrColon [] = [] appendUnderscore t | t `S.member` keywords = t ++ "_" | t `S.member` prelude = t ++ "_" | otherwise = t -- | A set of standard Haskell keywords, which cannot be used as combinators. -- keywords :: Set String keywords = S.fromList [ "case", "class", "data", "default", "deriving", "do", "else", "if" , "import", "in", "infix", "infixl", "infixr", "instance" , "let", "module" , "newtype", "of", "then", "type", "where" ] -- | Set of functions from the Prelude, which we do not use as combinators. -- prelude :: Set String prelude = S.fromList [ "abs", "acos", "acosh", "all", "and", "any", "appendFile", "asTypeOf" , "asin", "asinh", "atan", "atan2", "atanh", "break", "catch", "ceiling" , "compare", "concat", "concatMap", "const", "cos", "cosh", "curry", "cycle" , "decodeFloat", "div", "divMod", "drop", "dropWhile", "either", "elem" , "encodeFloat", "enumFrom", "enumFromThen", "enumFromThenTo", "enumFromTo" , "error", "even", "exp", "exponent", "fail", "filter", "flip" , "floatDigits", "floatRadix", "floatRange", "floor", "fmap", "foldl" , "foldl1", "foldr", "foldr1", "fromEnum", "fromInteger", "fromIntegral" , "fromRational", "fst", "gcd", "getChar", "getContents", "getLine", "head" , "id", "init", "interact", "ioError", "isDenormalized", "isIEEE" , "isInfinite", "isNaN", "isNegativeZero", "iterate", "last", "lcm" , "length", "lex", "lines", "log", "logBase", "lookup", "map", "mapM" , "mapM_", "max", "maxBound", "maximum", "maybe", "min", "minBound" , "minimum", "mod", "negate", "not", "notElem", "null", "odd", "or" , "otherwise", "pi", "pred", "print", "product", "properFraction", "putChar" , "putStr", "putStrLn", "quot", "quotRem", "read", "readFile", "readIO" , "readList", "readLn", "readParen", "reads", "readsPrec", "realToFrac" , "recip", "rem", "repeat", "replicate", "return", "reverse", "round" , "scaleFloat", "scanl", "scanl1", "scanr", "scanr1", "seq", "sequence" , "sequence_", "show", "showChar", "showList", "showParen", "showString" , "shows", "showsPrec", "significand", "signum", "sin", "sinh", "snd" , "span", "splitAt", "sqrt", "subtract", "succ", "sum", "tail", "take" , "takeWhile", "tan", "tanh", "toEnum", "toInteger", "toRational" , "truncate", "text", "uncurry", "undefined", "unlines", "until", "unwords", "unzip" , "unzip3", "userError", "words", "writeFile", "zip", "zip3", "zipWith" , "zipWith3" ] ������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/���������������������������������������������������������������������������0000755�0000000�0000000�00000000000�12642557533�013326� 5����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/���������������������������������������������������������������������0000755�0000000�0000000�00000000000�12642557533�014363� 5����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg.hs���������������������������������������������������������������0000644�0000000�0000000�00000001117�12642557533�015456� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������{-# LANGUAGE OverloadedStrings #-} module Text.Blaze.Svg ( Svg , Path -- * SVG Path combinators , mkPath -- ** \"moveto\" commands , m, mr -- ** \"closepath\" command , z -- ** \"lineto\" commands , l, lr, h, hr, v, vr -- ** The cubic Bézier curve commands , c, cr, s, sr -- ** The quadratic Bézier curve commands , q, qr, t, tr -- ** Elliptical arc , aa , ar -- * SVG Transform combinators , translate, rotate, rotateAround, scale , skewX, skewY , matrix ) where import Text.Blaze.Svg.Internal �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg11.hs�������������������������������������������������������������0000644�0000000�0000000�00000061231�12642557533�015623� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������-- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:69 -- {-# 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:78 -- 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:157 -- -- | Combinator for the document type. This should be placed at the top -- of every SVG page. -- -- > -- > "http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd"> -- docType :: Svg -- ^ The document type SVG. docType = preEscapedText "\n\n" {-# INLINE docType #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:172 -- -- | Combinator for the @\@ element. This combinator will also -- insert the correct doctype. -- docTypeSvg :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. docTypeSvg inner = docType >> (svg ! attribute "xmlns" " xmlns=\"" "http://www.w3.org/2000/svg" ! attribute "xmlns:xlink" " xmlns:xlink=\"" "http://www.w3.org/1999/xlink" $ inner) {-# INLINE docTypeSvg #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- a :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. a = Parent "a" "" {-# INLINE a #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- altglyph :: Svg -- ^ Resulting SVG. altglyph = Leaf "altGlyph" "" {-# INLINE altglyph #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- altglyphdef :: Svg -- ^ Resulting SVG. altglyphdef = Leaf "altGlyphDef" "" {-# INLINE altglyphdef #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- altglyphitem :: Svg -- ^ Resulting SVG. altglyphitem = Leaf "altGlyphItem" "" {-# INLINE altglyphitem #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- animate :: Svg -- ^ Resulting SVG. animate = Leaf "animate" "" {-# INLINE animate #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- animatecolor :: Svg -- ^ Resulting SVG. animatecolor = Leaf "animateColor" "" {-# INLINE animatecolor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- animatemotion :: Svg -- ^ Resulting SVG. animatemotion = Leaf "animateMotion" "" {-# INLINE animatemotion #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- animatetransform :: Svg -- ^ Resulting SVG. animatetransform = Leaf "animateTransform" "" {-# INLINE animatetransform #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- circle :: Svg -- ^ Resulting SVG. circle = Leaf "circle" "" {-# INLINE circle #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- clippath :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. clippath = Parent "clipPath" "" {-# INLINE clippath #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- colorProfile :: Svg -- ^ Resulting SVG. colorProfile = Leaf "color-profile" "" {-# INLINE colorProfile #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- cursor :: Svg -- ^ Resulting SVG. cursor = Leaf "cursor" "" {-# INLINE cursor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- defs :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. defs = Parent "defs" "" {-# INLINE defs #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- desc :: Svg -- ^ Resulting SVG. desc = Leaf "desc" "" {-# INLINE desc #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- ellipse :: Svg -- ^ Resulting SVG. ellipse = Leaf "ellipse" "" {-# INLINE ellipse #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- feblend :: Svg -- ^ Resulting SVG. feblend = Leaf "feBlend" "" {-# INLINE feblend #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fecolormatrix :: Svg -- ^ Resulting SVG. fecolormatrix = Leaf "feColorMatrix" "" {-# INLINE fecolormatrix #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fecomponenttransfer :: Svg -- ^ Resulting SVG. fecomponenttransfer = Leaf "feComponentTransfer" "" {-# INLINE fecomponenttransfer #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fecomposite :: Svg -- ^ Resulting SVG. fecomposite = Leaf "feComposite" "" {-# INLINE fecomposite #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- feconvolvematrix :: Svg -- ^ Resulting SVG. feconvolvematrix = Leaf "feConvolveMatrix" "" {-# INLINE feconvolvematrix #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fediffuselighting :: Svg -- ^ Resulting SVG. fediffuselighting = Leaf "feDiffuseLighting" "" {-# INLINE fediffuselighting #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fedisplacementmap :: Svg -- ^ Resulting SVG. fedisplacementmap = Leaf "feDisplacementMap" "" {-# INLINE fedisplacementmap #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fedistantlight :: Svg -- ^ Resulting SVG. fedistantlight = Leaf "feDistantLight" "" {-# INLINE fedistantlight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- feflood :: Svg -- ^ Resulting SVG. feflood = Leaf "feFlood" "" {-# INLINE feflood #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fefunca :: Svg -- ^ Resulting SVG. fefunca = Leaf "feFuncA" "" {-# INLINE fefunca #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fefuncb :: Svg -- ^ Resulting SVG. fefuncb = Leaf "feFuncB" "" {-# INLINE fefuncb #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fefuncg :: Svg -- ^ Resulting SVG. fefuncg = Leaf "feFuncG" "" {-# INLINE fefuncg #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fefuncr :: Svg -- ^ Resulting SVG. fefuncr = Leaf "feFuncR" "" {-# INLINE fefuncr #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fegaussianblur :: Svg -- ^ Resulting SVG. fegaussianblur = Leaf "feGaussianBlur" "" {-# INLINE fegaussianblur #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- feimage :: Svg -- ^ Resulting SVG. feimage = Leaf "feImage" "" {-# INLINE feimage #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- femerge :: Svg -- ^ Resulting SVG. femerge = Leaf "feMerge" "" {-# INLINE femerge #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- femergenode :: Svg -- ^ Resulting SVG. femergenode = Leaf "feMergeNode" "" {-# INLINE femergenode #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- femorphology :: Svg -- ^ Resulting SVG. femorphology = Leaf "feMorphology" "" {-# INLINE femorphology #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- feoffset :: Svg -- ^ Resulting SVG. feoffset = Leaf "feOffset" "" {-# INLINE feoffset #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fepointlight :: Svg -- ^ Resulting SVG. fepointlight = Leaf "fePointLight" "" {-# INLINE fepointlight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fespecularlighting :: Svg -- ^ Resulting SVG. fespecularlighting = Leaf "feSpecularLighting" "" {-# INLINE fespecularlighting #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fespotlight :: Svg -- ^ Resulting SVG. fespotlight = Leaf "feSpotLight" "" {-# INLINE fespotlight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fetile :: Svg -- ^ Resulting SVG. fetile = Leaf "feTile" "" {-# INLINE fetile #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- feturbulence :: Svg -- ^ Resulting SVG. feturbulence = Leaf "feTurbulence" "" {-# INLINE feturbulence #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- filter_ :: Svg -- ^ Resulting SVG. filter_ = Leaf "filter" "" {-# INLINE filter_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- font :: Svg -- ^ Resulting SVG. font = Leaf "font" "" {-# INLINE font #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fontFace :: Svg -- ^ Resulting SVG. fontFace = Leaf "font-face" "" {-# INLINE fontFace #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fontFaceFormat :: Svg -- ^ Resulting SVG. fontFaceFormat = Leaf "font-face-format" "" {-# INLINE fontFaceFormat #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fontFaceName :: Svg -- ^ Resulting SVG. fontFaceName = Leaf "font-face-name" "" {-# INLINE fontFaceName #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fontFaceSrc :: Svg -- ^ Resulting SVG. fontFaceSrc = Leaf "font-face-src" "" {-# INLINE fontFaceSrc #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- fontFaceUri :: Svg -- ^ Resulting SVG. fontFaceUri = Leaf "font-face-uri" "" {-# INLINE fontFaceUri #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- foreignobject :: Svg -- ^ Resulting SVG. foreignobject = Leaf "foreignObject" "" {-# INLINE foreignobject #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- g :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. g = Parent "g" "" {-# INLINE g #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- glyph :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. glyph = Parent "glyph" "" {-# INLINE glyph #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- glyphref :: Svg -- ^ Resulting SVG. glyphref = Leaf "glyphRef" "" {-# INLINE glyphref #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- hkern :: Svg -- ^ Resulting SVG. hkern = Leaf "hkern" "" {-# INLINE hkern #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- image :: Svg -- ^ Resulting SVG. image = Leaf "image" "" {-# INLINE image #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- line :: Svg -- ^ Resulting SVG. line = Leaf "line" "" {-# INLINE line #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- lineargradient :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. lineargradient = Parent "linearGradient" "" {-# INLINE lineargradient #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- marker :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. marker = Parent "marker" "" {-# INLINE marker #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- mask :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. mask = Parent "mask" "" {-# INLINE mask #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- metadata :: Svg -- ^ Resulting SVG. metadata = Leaf "metadata" "" {-# INLINE metadata #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- missingGlyph :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. missingGlyph = Parent "missing-glyph" "" {-# INLINE missingGlyph #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- mpath :: Svg -- ^ Resulting SVG. mpath = Leaf "mpath" "" {-# INLINE mpath #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- path :: Svg -- ^ Resulting SVG. path = Leaf "path" "" {-# INLINE path #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- pattern :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. pattern = Parent "pattern" "" {-# INLINE pattern #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- polygon :: Svg -- ^ Resulting SVG. polygon = Leaf "polygon" "" {-# INLINE polygon #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- polyline :: Svg -- ^ Resulting SVG. polyline = Leaf "polyline" "" {-# INLINE polyline #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- radialgradient :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. radialgradient = Parent "radialGradient" "" {-# INLINE radialgradient #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- rect :: Svg -- ^ Resulting SVG. rect = Leaf "rect" "" {-# INLINE rect #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- script :: Svg -- ^ Resulting SVG. script = Leaf "script" "" {-# INLINE script #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- set :: Svg -- ^ Resulting SVG. set = Leaf "set" "" {-# INLINE set #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- stop :: Svg -- ^ Resulting SVG. stop = Leaf "stop" "" {-# INLINE stop #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- style :: Svg -- ^ Resulting SVG. style = Leaf "style" "" {-# INLINE style #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- svg :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. svg = Parent "svg" "" {-# INLINE svg #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- switch :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. switch = Parent "switch" "" {-# INLINE switch #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- symbol :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. symbol = Parent "symbol" "" {-# INLINE symbol #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:186 -- -- | Combinator for the @\@ element. -- text_ :: Svg -- ^ Inner SVG. -> Svg -- ^ Resulting SVG. text_ = Parent "text" "" {-# INLINE text_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- textpath :: Svg -- ^ Resulting SVG. textpath = Leaf "textPath" "" {-# INLINE textpath #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- title :: Svg -- ^ Resulting SVG. title = Leaf "title" "" {-# INLINE title #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- tref :: Svg -- ^ Resulting SVG. tref = Leaf "tref" "" {-# INLINE tref #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- tspan :: Svg -- ^ Resulting SVG. tspan = Leaf "tspan" "" {-# INLINE tspan #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- use :: Svg -- ^ Resulting SVG. use = Leaf "use" "" {-# INLINE use #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- view :: Svg -- ^ Resulting SVG. view = Leaf "view" "" {-# INLINE view #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:205 -- -- | Combinator for the @\@ element. -- vkern :: Svg -- ^ Resulting SVG. vkern = Leaf "vkern" "" {-# INLINE vkern #-} �����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg/�����������������������������������������������������������������0000755�0000000�0000000�00000000000�12642557533�015122� 5����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg/Internal.hs������������������������������������������������������0000644�0000000�0000000�00000015545�12642557533�017244� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������{-# OPTIONS_HADDOCK hide #-} module Text.Blaze.Svg.Internal where import Control.Monad.State import Data.Monoid (mappend, mempty) import Text.Blaze -- | Type to represent an SVG document fragment. type Svg = Markup -- | Type to accumulate an SVG path. type Path = State AttributeValue () -- | 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: -- -- > 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 mkPath :: Path -> AttributeValue mkPath path = snd $ runState path mempty appendToPath :: [String] -> Path appendToPath = modify . flip mappend . toValue . join -- | Moveto m :: Show a => a -> a -> Path m x y = appendToPath [ "M " , show x, ",", show y , " " ] -- | Moveto (relative) mr :: Show a => a -> a -> Path mr dx dy = appendToPath [ "m " , show dx, ",", show dy , " " ] -- | ClosePath z :: Path z = modify (`mappend` toValue "Z") -- | Lineto l :: Show a => a -> a -> Path l x y = appendToPath [ "L " , show x, ",", show y , " " ] -- | Lineto (relative) lr :: Show a => a -> a -> Path lr dx dy = appendToPath [ "l " , show dx, ",", show dy , " " ] -- | Horizontal lineto h :: Show a => a -> Path h x = appendToPath [ "H " , show x , " " ] -- | Horizontal lineto (relative) hr :: Show a => a -> Path hr dx = appendToPath [ "h " , show dx , " " ] -- | Vertical lineto v :: Show a => a -> Path v y = appendToPath [ "V " , show y , " " ] -- | Vertical lineto (relative) vr :: Show a => a -> Path vr dy = appendToPath [ "v " , show dy , " " ] -- | Cubic Bezier curve c :: Show a => a -> a -> a -> a -> a -> a -> Path c c1x c1y c2x c2y x y = appendToPath [ "C " , show c1x, ",", show c1y , " " , show c2x, ",", show c2y , " " , show x, " ", show y ] -- | Cubic Bezier curve (relative) cr :: Show a => a -> a -> a -> a -> a -> a -> Path cr dc1x dc1y dc2x dc2y dx dy = appendToPath [ "c " , show dc1x, ",", show dc1y , " " , show dc2x, ",", show dc2y , " " , show dx, " ", show dy ] -- | Smooth Cubic Bezier curve s :: Show a => a -> a -> a -> a -> Path s c2x c2y x y = appendToPath [ "S " , show c2x, ",", show c2y , " " , show x, ",", show y , " " ] -- | Smooth Cubic Bezier curve (relative) sr :: Show a => a -> a -> a -> a -> Path sr dc2x dc2y dx dy = appendToPath [ "s " , show dc2x, ",", show dc2y , " " , show dx, ",", show dy , " " ] -- | Quadratic Bezier curve q :: Show a => a -> a -> a -> a -> Path q cx cy x y = appendToPath [ "Q " , show cx, ",", show cy , " " , show x, ",", show y , " " ] -- | Quadratic Bezier curve (relative) qr :: Show a => a -> a -> a -> a -> Path qr dcx dcy dx dy = appendToPath [ "q " , show dcx, ",", show dcy , " " , show dx, ",", show dy , " " ] -- | Smooth Quadratic Bezier curve t :: Show a => a -> a -> Path t x y = appendToPath [ "T " , " " , show x, ",", show y , " " ] -- | Smooth Quadratic Bezier curve (relative) tr :: Show a => a -> a -> Path tr x y = appendToPath [ "t " , " " , show x, ",", show y , " " ] -- | Elliptical Arc (absolute). This function is an alias for 'a' defined in -- this module. It is defined so that it can be exported instead of the a -- function due to naming conflicts with 'Text.Blaze.SVG11.a'. aa :: 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 -> a -- ^ Draw the smaller or bigger arc satisfying the start point -> a -- ^ To mirror or not -> a -- ^ The x-coordinate of the end point -> a -- ^ The y-coordinate of the end point -> Path aa = a -- | Elliptical Arc (absolute). This is the internal definition for absolute -- arcs. It is not exported but instead exported as 'aa' due to naming -- conflicts with 'Text.Blaze.SVG11.a'. a :: 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 -> a -- ^ Draw the smaller or bigger arc satisfying the start point -> a -- ^ To mirror or not -> a -- ^ The x-coordinate of the end point -> a -- ^ The y-coordinate of the end point -> Path a rx ry xAxisRotation largeArcFlag sweepFlag x y = appendToPath [ "A " , show rx, ",", show ry, " " , show xAxisRotation, " " , show largeArcFlag, ",", show sweepFlag, " " , show x, ",", show y, " " ] -- | Elliptical Arc (relative) ar :: 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 -> a -- ^ Draw the smaller or bigger arc satisfying the start point -> a -- ^ To mirror or not -> a -- ^ The x-coordinate of the end point -> a -- ^ The y-coordinate of the end point -> Path ar rx ry xAxisRotation largeArcFlag sweepFlag x y = appendToPath [ "a " , show rx, ",", show ry, " " , show xAxisRotation, " " , show largeArcFlag, ",", show sweepFlag, " " , show x, ",", show y, " " ] -- | Specifies a translation by @x@ and @y@ translate :: Show a => a -> a -> AttributeValue translate x y = toValue . join $ [ "translate(" , show x, " ", show y , ")" ] -- | Specifies a scale operation by @x@ and @y@ scale :: Show a => a -> a -> AttributeValue scale x y = toValue . join $ [ "scale(" , show x, " ", show y , ")" ] -- | Specifies a rotation by @rotate-angle@ degrees rotate :: Show a => a -> AttributeValue rotate rotateAngle = toValue . join $ [ "rotate(" , show rotateAngle , ")" ] -- | Specifies a rotation by @rotate-angle@ degrees about the given time @rx,ry@ rotateAround :: Show a => a -> a -> a -> AttributeValue rotateAround rotateAngle rx ry = toValue . join $ [ "rotate(" , show rotateAngle, "," , show rx, ",", show ry , ")" ] -- | Skew tansformation along x-axis skewX :: Show a => a -> AttributeValue skewX skewAngle = toValue . join $ [ "skewX(" , show skewAngle , ")" ] -- | Skew tansformation along y-axis skewY :: Show a => a -> AttributeValue skewY skewAngle = toValue . join $ [ "skewY(" , show skewAngle , ")" ] -- | Specifies a transform in the form of a transformation matrix matrix :: Show a => a -> a -> a -> a -> a -> a -> AttributeValue matrix a_ b c_ d e f = toValue . join $ [ "matrix(" , show a_, "," , show b, "," , show c_, "," , show d, "," , show e, "," , show f , ")" ] �����������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg/Renderer/��������������������������������������������������������0000755�0000000�0000000�00000000000�12642557533�016670� 5����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg/Renderer/Utf8.hs�������������������������������������������������0000644�0000000�0000000�00000000272�12642557533�020053� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������{-# OPTIONS_GHC -fno-warn-missing-signatures #-} module Text.Blaze.Svg.Renderer.Utf8 ( renderSvg ) where import Text.Blaze.Renderer.Utf8 (renderMarkup) renderSvg = renderMarkup��������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg/Renderer/Pretty.hs�����������������������������������������������0000644�0000000�0000000�00000000420�12642557533�020507� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������{-# OPTIONS_GHC -fno-warn-missing-signatures #-} -- | A renderer that produces pretty SVG, mostly meant for debugging purposes. -- module Text.Blaze.Svg.Renderer.Pretty ( renderSvg ) where import Text.Blaze.Renderer.Pretty (renderMarkup) renderSvg = renderMarkup������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg/Renderer/String.hs�����������������������������������������������0000644�0000000�0000000�00000000442�12642557533�020472� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������{-# OPTIONS_GHC -fno-warn-missing-signatures #-} -- | A renderer that produces a native Haskell 'String', mostly meant for -- debugging purposes. -- module Text.Blaze.Svg.Renderer.String ( renderSvg ) where import Text.Blaze.Renderer.String (renderMarkup) renderSvg = renderMarkup������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg/Renderer/Text.hs�������������������������������������������������0000644�0000000�0000000�00000000411�12642557533�020144� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������{-# OPTIONS_GHC -fno-warn-missing-signatures #-} -- | A renderer that produces a lazy 'Text' value, using the Text Builder. -- module Text.Blaze.Svg.Renderer.Text ( renderSvg ) where import Text.Blaze.Renderer.Text (renderMarkup) renderSvg = renderMarkup �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg11/���������������������������������������������������������������0000755�0000000�0000000�00000000000�12642557533�015264� 5����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/src/Text/Blaze/Svg11/Attributes.hs��������������������������������������������������0000644�0000000�0000000�00000274337�12642557533�017766� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������-- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:94 -- -- | This module exports combinators that provide you with the -- ability to set attributes on SVG elements. -- {-# LANGUAGE OverloadedStrings #-} module Text.Blaze.Svg11.Attributes ( accentHeight , accumulate , additive , alignmentBaseline , alphabetic , amplitude , arabicForm , ascent , attributename , attributetype , azimuth , basefrequency , baseprofile , baselineShift , bbox , begin , bias , by , calcmode , capHeight , class_ , clip , clipPath , clipRule , clippathunits , color , colorInterpolation , colorInterpolationFilters , colorProfile , colorRendering , contentscripttype , contentstyletype , cursor , cx , cy , d , descent , diffuseconstant , direction , display , divisor , dominantBaseline , dur , dx , dy , edgemode , elevation , enableBackground , end , exponent_ , externalresourcesrequired , fill , fillOpacity , fillRule , filter_ , filterres , filterunits , floodColor , floodOpacity , fontFamily , fontSize , fontSizeAdjust , fontStretch , fontStyle , fontVariant , fontWeight , format , from , fx , fy , g1 , g2 , glyphName , glyphOrientationHorizontal , glyphOrientationVertical , glyphref , gradienttransform , gradientunits , hanging , height , horizAdvX , horizOriginX , horizOriginY , id_ , ideographic , imageRendering , in_ , in2 , intercept , k , k1 , k2 , k3 , k4 , kernelmatrix , kernelunitlength , kerning , keypoints , keysplines , keytimes , lang , lengthadjust , letterSpacing , lightingColor , limitingconeangle , local , markerEnd , markerMid , markerStart , markerheight , markerunits , markerwidth , mask , maskcontentunits , maskunits , mathematical , max_ , media , method , min_ , mode , name , numoctaves , offset , onabort , onactivate , onbegin , onclick , onend , onerror , onfocusin , onfocusout , onload , onmousedown , onmousemove , onmouseout , onmouseover , onmouseup , onrepeat , onresize , onscroll , onunload , onzoom , opacity , operator , order , orient , orientation , origin , overflow , overlinePosition , overlineThickness , panose1 , path , pathlength , patterncontentunits , patterntransform , patternunits , pointerEvents , points , pointsatx , pointsaty , pointsatz , preservealpha , preserveaspectratio , primitiveunits , r , radius , refx , refy , renderingIntent , repeatcount , repeatdur , requiredextensions , requiredfeatures , restart , result , rotate , rx , ry , scale , seed , shapeRendering , slope , spacing , specularconstant , specularexponent , spreadmethod , startoffset , stddeviation , stemh , stemv , stitchtiles , stopColor , stopOpacity , strikethroughPosition , strikethroughThickness , string , stroke , strokeDasharray , strokeDashoffset , strokeLinecap , strokeLinejoin , strokeMiterlimit , strokeOpacity , strokeWidth , style , surfacescale , systemlanguage , tablevalues , target , targetx , targety , textAnchor , textDecoration , textRendering , textlength , title , to , transform , type_ , u1 , u2 , underlinePosition , underlineThickness , unicode , unicodeBidi , unicodeRange , unitsPerEm , vAlphabetic , vHanging , vIdeographic , vMathematical , values , version , vertAdvY , vertOriginX , vertOriginY , viewbox , viewtarget , visibility , width , widths , wordSpacing , writingMode , x , xHeight , x1 , x2 , xchannelselector , xlinkActuate , xlinkArcrole , xlinkHref , xlinkRole , xlinkShow , xlinkTitle , xlinkType , xmlBase , xmlLang , xmlSpace , y , y1 , y2 , ychannelselector , z , zoomandpan ) where -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:100 -- import Prelude () import Text.Blaze.Internal (Attribute, AttributeValue, attribute) -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @accent-height@ attribute. -- accentHeight :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. accentHeight = attribute "accent-height" " accent-height=\"" {-# INLINE accentHeight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @accumulate@ attribute. -- accumulate :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. accumulate = attribute "accumulate" " accumulate=\"" {-# INLINE accumulate #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @additive@ attribute. -- additive :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. additive = attribute "additive" " additive=\"" {-# INLINE additive #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @alignment-baseline@ attribute. -- alignmentBaseline :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. alignmentBaseline = attribute "alignment-baseline" " alignment-baseline=\"" {-# INLINE alignmentBaseline #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @alphabetic@ attribute. -- alphabetic :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. alphabetic = attribute "alphabetic" " alphabetic=\"" {-# INLINE alphabetic #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @amplitude@ attribute. -- amplitude :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. amplitude = attribute "amplitude" " amplitude=\"" {-# INLINE amplitude #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @arabic-form@ attribute. -- arabicForm :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. arabicForm = attribute "arabic-form" " arabic-form=\"" {-# INLINE arabicForm #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @ascent@ attribute. -- ascent :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. ascent = attribute "ascent" " ascent=\"" {-# INLINE ascent #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @attributeName@ attribute. -- attributename :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. attributename = attribute "attributeName" " attributeName=\"" {-# INLINE attributename #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @attributeType@ attribute. -- attributetype :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. attributetype = attribute "attributeType" " attributeType=\"" {-# INLINE attributetype #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @azimuth@ attribute. -- azimuth :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. azimuth = attribute "azimuth" " azimuth=\"" {-# INLINE azimuth #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @baseFrequency@ attribute. -- basefrequency :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. basefrequency = attribute "baseFrequency" " baseFrequency=\"" {-# INLINE basefrequency #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @baseProfile@ attribute. -- baseprofile :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. baseprofile = attribute "baseProfile" " baseProfile=\"" {-# INLINE baseprofile #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @baseline-shift@ attribute. -- baselineShift :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. baselineShift = attribute "baseline-shift" " baseline-shift=\"" {-# INLINE baselineShift #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @bbox@ attribute. -- bbox :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. bbox = attribute "bbox" " bbox=\"" {-# INLINE bbox #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @begin@ attribute. -- begin :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. begin = attribute "begin" " begin=\"" {-# INLINE begin #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @bias@ attribute. -- bias :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. bias = attribute "bias" " bias=\"" {-# INLINE bias #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @by@ attribute. -- by :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. by = attribute "by" " by=\"" {-# INLINE by #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @calcMode@ attribute. -- calcmode :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. calcmode = attribute "calcMode" " calcMode=\"" {-# INLINE calcmode #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @cap-height@ attribute. -- capHeight :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. capHeight = attribute "cap-height" " cap-height=\"" {-# INLINE capHeight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @class@ attribute. -- class_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. class_ = attribute "class" " class=\"" {-# INLINE class_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @clip@ attribute. -- clip :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. clip = attribute "clip" " clip=\"" {-# INLINE clip #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @clip-path@ attribute. -- clipPath :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. clipPath = attribute "clip-path" " clip-path=\"" {-# INLINE clipPath #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @clip-rule@ attribute. -- clipRule :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. clipRule = attribute "clip-rule" " clip-rule=\"" {-# INLINE clipRule #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @clipPathUnits@ attribute. -- clippathunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. clippathunits = attribute "clipPathUnits" " clipPathUnits=\"" {-# INLINE clippathunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @color@ attribute. -- color :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. color = attribute "color" " color=\"" {-# INLINE color #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @color-interpolation@ attribute. -- colorInterpolation :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. colorInterpolation = attribute "color-interpolation" " color-interpolation=\"" {-# INLINE colorInterpolation #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @color-interpolation-filters@ attribute. -- colorInterpolationFilters :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. colorInterpolationFilters = attribute "color-interpolation-filters" " color-interpolation-filters=\"" {-# INLINE colorInterpolationFilters #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @color-profile@ attribute. -- colorProfile :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. colorProfile = attribute "color-profile" " color-profile=\"" {-# INLINE colorProfile #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @color-rendering@ attribute. -- colorRendering :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. colorRendering = attribute "color-rendering" " color-rendering=\"" {-# INLINE colorRendering #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @contentScriptType@ attribute. -- contentscripttype :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. contentscripttype = attribute "contentScriptType" " contentScriptType=\"" {-# INLINE contentscripttype #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @contentStyleType@ attribute. -- contentstyletype :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. contentstyletype = attribute "contentStyleType" " contentStyleType=\"" {-# INLINE contentstyletype #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @cursor@ attribute. -- cursor :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. cursor = attribute "cursor" " cursor=\"" {-# INLINE cursor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @cx@ attribute. -- cx :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. cx = attribute "cx" " cx=\"" {-# INLINE cx #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @cy@ attribute. -- cy :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. cy = attribute "cy" " cy=\"" {-# INLINE cy #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @d@ attribute. -- d :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. d = attribute "d" " d=\"" {-# INLINE d #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @descent@ attribute. -- descent :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. descent = attribute "descent" " descent=\"" {-# INLINE descent #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @diffuseConstant@ attribute. -- diffuseconstant :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. diffuseconstant = attribute "diffuseConstant" " diffuseConstant=\"" {-# INLINE diffuseconstant #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @direction@ attribute. -- direction :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. direction = attribute "direction" " direction=\"" {-# INLINE direction #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @display@ attribute. -- display :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. display = attribute "display" " display=\"" {-# INLINE display #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @divisor@ attribute. -- divisor :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. divisor = attribute "divisor" " divisor=\"" {-# INLINE divisor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @dominant-baseline@ attribute. -- dominantBaseline :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. dominantBaseline = attribute "dominant-baseline" " dominant-baseline=\"" {-# INLINE dominantBaseline #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @dur@ attribute. -- dur :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. dur = attribute "dur" " dur=\"" {-# INLINE dur #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @dx@ attribute. -- dx :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. dx = attribute "dx" " dx=\"" {-# INLINE dx #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @dy@ attribute. -- dy :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. dy = attribute "dy" " dy=\"" {-# INLINE dy #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @edgeMode@ attribute. -- edgemode :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. edgemode = attribute "edgeMode" " edgeMode=\"" {-# INLINE edgemode #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @elevation@ attribute. -- elevation :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. elevation = attribute "elevation" " elevation=\"" {-# INLINE elevation #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @enable-background@ attribute. -- enableBackground :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. enableBackground = attribute "enable-background" " enable-background=\"" {-# INLINE enableBackground #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @end@ attribute. -- end :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. end = attribute "end" " end=\"" {-# INLINE end #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @exponent@ attribute. -- exponent_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. exponent_ = attribute "exponent" " exponent=\"" {-# INLINE exponent_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @externalResourcesRequired@ attribute. -- externalresourcesrequired :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. externalresourcesrequired = attribute "externalResourcesRequired" " externalResourcesRequired=\"" {-# INLINE externalresourcesrequired #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @fill@ attribute. -- fill :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fill = attribute "fill" " fill=\"" {-# INLINE fill #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @fill-opacity@ attribute. -- fillOpacity :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fillOpacity = attribute "fill-opacity" " fill-opacity=\"" {-# INLINE fillOpacity #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @fill-rule@ attribute. -- fillRule :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fillRule = attribute "fill-rule" " fill-rule=\"" {-# INLINE fillRule #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @filter@ attribute. -- filter_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. filter_ = attribute "filter" " filter=\"" {-# INLINE filter_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @filterRes@ attribute. -- filterres :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. filterres = attribute "filterRes" " filterRes=\"" {-# INLINE filterres #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @filterUnits@ attribute. -- filterunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. filterunits = attribute "filterUnits" " filterUnits=\"" {-# INLINE filterunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @flood-color@ attribute. -- floodColor :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. floodColor = attribute "flood-color" " flood-color=\"" {-# INLINE floodColor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @flood-opacity@ attribute. -- floodOpacity :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. floodOpacity = attribute "flood-opacity" " flood-opacity=\"" {-# INLINE floodOpacity #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @font-family@ attribute. -- fontFamily :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fontFamily = attribute "font-family" " font-family=\"" {-# INLINE fontFamily #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @font-size@ attribute. -- fontSize :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fontSize = attribute "font-size" " font-size=\"" {-# INLINE fontSize #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @font-size-adjust@ attribute. -- fontSizeAdjust :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fontSizeAdjust = attribute "font-size-adjust" " font-size-adjust=\"" {-# INLINE fontSizeAdjust #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @font-stretch@ attribute. -- fontStretch :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fontStretch = attribute "font-stretch" " font-stretch=\"" {-# INLINE fontStretch #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @font-style@ attribute. -- fontStyle :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fontStyle = attribute "font-style" " font-style=\"" {-# INLINE fontStyle #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @font-variant@ attribute. -- fontVariant :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fontVariant = attribute "font-variant" " font-variant=\"" {-# INLINE fontVariant #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @font-weight@ attribute. -- fontWeight :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fontWeight = attribute "font-weight" " font-weight=\"" {-# INLINE fontWeight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @format@ attribute. -- format :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. format = attribute "format" " format=\"" {-# INLINE format #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @from@ attribute. -- from :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. from = attribute "from" " from=\"" {-# INLINE from #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @fx@ attribute. -- fx :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fx = attribute "fx" " fx=\"" {-# INLINE fx #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @fy@ attribute. -- fy :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. fy = attribute "fy" " fy=\"" {-# INLINE fy #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @g1@ attribute. -- g1 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. g1 = attribute "g1" " g1=\"" {-# INLINE g1 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @g2@ attribute. -- g2 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. g2 = attribute "g2" " g2=\"" {-# INLINE g2 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @glyph-name@ attribute. -- glyphName :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. glyphName = attribute "glyph-name" " glyph-name=\"" {-# INLINE glyphName #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @glyph-orientation-horizontal@ attribute. -- glyphOrientationHorizontal :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. glyphOrientationHorizontal = attribute "glyph-orientation-horizontal" " glyph-orientation-horizontal=\"" {-# INLINE glyphOrientationHorizontal #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @glyph-orientation-vertical@ attribute. -- glyphOrientationVertical :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. glyphOrientationVertical = attribute "glyph-orientation-vertical" " glyph-orientation-vertical=\"" {-# INLINE glyphOrientationVertical #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @glyphRef@ attribute. -- glyphref :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. glyphref = attribute "glyphRef" " glyphRef=\"" {-# INLINE glyphref #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @gradientTransform@ attribute. -- gradienttransform :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. gradienttransform = attribute "gradientTransform" " gradientTransform=\"" {-# INLINE gradienttransform #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @gradientUnits@ attribute. -- gradientunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. gradientunits = attribute "gradientUnits" " gradientUnits=\"" {-# INLINE gradientunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @hanging@ attribute. -- hanging :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. hanging = attribute "hanging" " hanging=\"" {-# INLINE hanging #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @height@ attribute. -- height :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. height = attribute "height" " height=\"" {-# INLINE height #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @horiz-adv-x@ attribute. -- horizAdvX :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. horizAdvX = attribute "horiz-adv-x" " horiz-adv-x=\"" {-# INLINE horizAdvX #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @horiz-origin-x@ attribute. -- horizOriginX :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. horizOriginX = attribute "horiz-origin-x" " horiz-origin-x=\"" {-# INLINE horizOriginX #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @horiz-origin-y@ attribute. -- horizOriginY :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. horizOriginY = attribute "horiz-origin-y" " horiz-origin-y=\"" {-# INLINE horizOriginY #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @id@ attribute. -- id_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. id_ = attribute "id" " id=\"" {-# INLINE id_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @ideographic@ attribute. -- ideographic :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. ideographic = attribute "ideographic" " ideographic=\"" {-# INLINE ideographic #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @image-rendering@ attribute. -- imageRendering :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. imageRendering = attribute "image-rendering" " image-rendering=\"" {-# INLINE imageRendering #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @in@ attribute. -- in_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. in_ = attribute "in" " in=\"" {-# INLINE in_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @in2@ attribute. -- in2 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. in2 = attribute "in2" " in2=\"" {-# INLINE in2 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @intercept@ attribute. -- intercept :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. intercept = attribute "intercept" " intercept=\"" {-# INLINE intercept #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @k@ attribute. -- k :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. k = attribute "k" " k=\"" {-# INLINE k #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @k1@ attribute. -- k1 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. k1 = attribute "k1" " k1=\"" {-# INLINE k1 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @k2@ attribute. -- k2 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. k2 = attribute "k2" " k2=\"" {-# INLINE k2 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @k3@ attribute. -- k3 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. k3 = attribute "k3" " k3=\"" {-# INLINE k3 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @k4@ attribute. -- k4 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. k4 = attribute "k4" " k4=\"" {-# INLINE k4 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @kernelMatrix@ attribute. -- kernelmatrix :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. kernelmatrix = attribute "kernelMatrix" " kernelMatrix=\"" {-# INLINE kernelmatrix #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @kernelUnitLength@ attribute. -- kernelunitlength :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. kernelunitlength = attribute "kernelUnitLength" " kernelUnitLength=\"" {-# INLINE kernelunitlength #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @kerning@ attribute. -- kerning :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. kerning = attribute "kerning" " kerning=\"" {-# INLINE kerning #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @keyPoints@ attribute. -- keypoints :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. keypoints = attribute "keyPoints" " keyPoints=\"" {-# INLINE keypoints #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @keySplines@ attribute. -- keysplines :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. keysplines = attribute "keySplines" " keySplines=\"" {-# INLINE keysplines #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @keyTimes@ attribute. -- keytimes :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. keytimes = attribute "keyTimes" " keyTimes=\"" {-# INLINE keytimes #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @lang@ attribute. -- lang :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. lang = attribute "lang" " lang=\"" {-# INLINE lang #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @lengthAdjust@ attribute. -- lengthadjust :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. lengthadjust = attribute "lengthAdjust" " lengthAdjust=\"" {-# INLINE lengthadjust #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @letter-spacing@ attribute. -- letterSpacing :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. letterSpacing = attribute "letter-spacing" " letter-spacing=\"" {-# INLINE letterSpacing #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @lighting-color@ attribute. -- lightingColor :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. lightingColor = attribute "lighting-color" " lighting-color=\"" {-# INLINE lightingColor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @limitingConeAngle@ attribute. -- limitingconeangle :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. limitingconeangle = attribute "limitingConeAngle" " limitingConeAngle=\"" {-# INLINE limitingconeangle #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @local@ attribute. -- local :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. local = attribute "local" " local=\"" {-# INLINE local #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @marker-end@ attribute. -- markerEnd :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. markerEnd = attribute "marker-end" " marker-end=\"" {-# INLINE markerEnd #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @marker-mid@ attribute. -- markerMid :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. markerMid = attribute "marker-mid" " marker-mid=\"" {-# INLINE markerMid #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @marker-start@ attribute. -- markerStart :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. markerStart = attribute "marker-start" " marker-start=\"" {-# INLINE markerStart #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @markerHeight@ attribute. -- markerheight :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. markerheight = attribute "markerHeight" " markerHeight=\"" {-# INLINE markerheight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @markerUnits@ attribute. -- markerunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. markerunits = attribute "markerUnits" " markerUnits=\"" {-# INLINE markerunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @markerWidth@ attribute. -- markerwidth :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. markerwidth = attribute "markerWidth" " markerWidth=\"" {-# INLINE markerwidth #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @mask@ attribute. -- mask :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. mask = attribute "mask" " mask=\"" {-# INLINE mask #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @maskContentUnits@ attribute. -- maskcontentunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. maskcontentunits = attribute "maskContentUnits" " maskContentUnits=\"" {-# INLINE maskcontentunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @maskUnits@ attribute. -- maskunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. maskunits = attribute "maskUnits" " maskUnits=\"" {-# INLINE maskunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @mathematical@ attribute. -- mathematical :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. mathematical = attribute "mathematical" " mathematical=\"" {-# INLINE mathematical #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @max@ attribute. -- max_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. max_ = attribute "max" " max=\"" {-# INLINE max_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @media@ attribute. -- media :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. media = attribute "media" " media=\"" {-# INLINE media #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @method@ attribute. -- method :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. method = attribute "method" " method=\"" {-# INLINE method #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @min@ attribute. -- min_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. min_ = attribute "min" " min=\"" {-# INLINE min_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @mode@ attribute. -- mode :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. mode = attribute "mode" " mode=\"" {-# INLINE mode #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @name@ attribute. -- name :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. name = attribute "name" " name=\"" {-# INLINE name #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @numOctaves@ attribute. -- numoctaves :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. numoctaves = attribute "numOctaves" " numOctaves=\"" {-# INLINE numoctaves #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @offset@ attribute. -- offset :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. offset = attribute "offset" " offset=\"" {-# INLINE offset #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onabort@ attribute. -- onabort :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onabort = attribute "onabort" " onabort=\"" {-# INLINE onabort #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onactivate@ attribute. -- onactivate :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onactivate = attribute "onactivate" " onactivate=\"" {-# INLINE onactivate #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onbegin@ attribute. -- onbegin :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onbegin = attribute "onbegin" " onbegin=\"" {-# INLINE onbegin #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onclick@ attribute. -- onclick :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onclick = attribute "onclick" " onclick=\"" {-# INLINE onclick #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onend@ attribute. -- onend :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onend = attribute "onend" " onend=\"" {-# INLINE onend #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onerror@ attribute. -- onerror :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onerror = attribute "onerror" " onerror=\"" {-# INLINE onerror #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onfocusin@ attribute. -- onfocusin :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onfocusin = attribute "onfocusin" " onfocusin=\"" {-# INLINE onfocusin #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onfocusout@ attribute. -- onfocusout :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onfocusout = attribute "onfocusout" " onfocusout=\"" {-# INLINE onfocusout #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onload@ attribute. -- onload :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onload = attribute "onload" " onload=\"" {-# INLINE onload #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onmousedown@ attribute. -- onmousedown :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onmousedown = attribute "onmousedown" " onmousedown=\"" {-# INLINE onmousedown #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onmousemove@ attribute. -- onmousemove :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onmousemove = attribute "onmousemove" " onmousemove=\"" {-# INLINE onmousemove #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onmouseout@ attribute. -- onmouseout :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onmouseout = attribute "onmouseout" " onmouseout=\"" {-# INLINE onmouseout #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onmouseover@ attribute. -- onmouseover :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onmouseover = attribute "onmouseover" " onmouseover=\"" {-# INLINE onmouseover #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onmouseup@ attribute. -- onmouseup :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onmouseup = attribute "onmouseup" " onmouseup=\"" {-# INLINE onmouseup #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onrepeat@ attribute. -- onrepeat :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onrepeat = attribute "onrepeat" " onrepeat=\"" {-# INLINE onrepeat #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onresize@ attribute. -- onresize :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onresize = attribute "onresize" " onresize=\"" {-# INLINE onresize #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onscroll@ attribute. -- onscroll :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onscroll = attribute "onscroll" " onscroll=\"" {-# INLINE onscroll #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onunload@ attribute. -- onunload :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onunload = attribute "onunload" " onunload=\"" {-# INLINE onunload #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @onzoom@ attribute. -- onzoom :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. onzoom = attribute "onzoom" " onzoom=\"" {-# INLINE onzoom #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @opacity@ attribute. -- opacity :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. opacity = attribute "opacity" " opacity=\"" {-# INLINE opacity #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @operator@ attribute. -- operator :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. operator = attribute "operator" " operator=\"" {-# INLINE operator #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @order@ attribute. -- order :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. order = attribute "order" " order=\"" {-# INLINE order #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @orient@ attribute. -- orient :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. orient = attribute "orient" " orient=\"" {-# INLINE orient #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @orientation@ attribute. -- orientation :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. orientation = attribute "orientation" " orientation=\"" {-# INLINE orientation #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @origin@ attribute. -- origin :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. origin = attribute "origin" " origin=\"" {-# INLINE origin #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @overflow@ attribute. -- overflow :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. overflow = attribute "overflow" " overflow=\"" {-# INLINE overflow #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @overline-position@ attribute. -- overlinePosition :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. overlinePosition = attribute "overline-position" " overline-position=\"" {-# INLINE overlinePosition #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @overline-thickness@ attribute. -- overlineThickness :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. overlineThickness = attribute "overline-thickness" " overline-thickness=\"" {-# INLINE overlineThickness #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @panose-1@ attribute. -- panose1 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. panose1 = attribute "panose-1" " panose-1=\"" {-# INLINE panose1 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @path@ attribute. -- path :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. path = attribute "path" " path=\"" {-# INLINE path #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @pathLength@ attribute. -- pathlength :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. pathlength = attribute "pathLength" " pathLength=\"" {-# INLINE pathlength #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @patternContentUnits@ attribute. -- patterncontentunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. patterncontentunits = attribute "patternContentUnits" " patternContentUnits=\"" {-# INLINE patterncontentunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @patternTransform@ attribute. -- patterntransform :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. patterntransform = attribute "patternTransform" " patternTransform=\"" {-# INLINE patterntransform #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @patternUnits@ attribute. -- patternunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. patternunits = attribute "patternUnits" " patternUnits=\"" {-# INLINE patternunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @pointer-events@ attribute. -- pointerEvents :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. pointerEvents = attribute "pointer-events" " pointer-events=\"" {-# INLINE pointerEvents #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @points@ attribute. -- points :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. points = attribute "points" " points=\"" {-# INLINE points #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @pointsAtX@ attribute. -- pointsatx :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. pointsatx = attribute "pointsAtX" " pointsAtX=\"" {-# INLINE pointsatx #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @pointsAtY@ attribute. -- pointsaty :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. pointsaty = attribute "pointsAtY" " pointsAtY=\"" {-# INLINE pointsaty #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @pointsAtZ@ attribute. -- pointsatz :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. pointsatz = attribute "pointsAtZ" " pointsAtZ=\"" {-# INLINE pointsatz #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @preserveAlpha@ attribute. -- preservealpha :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. preservealpha = attribute "preserveAlpha" " preserveAlpha=\"" {-# INLINE preservealpha #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @preserveAspectRatio@ attribute. -- preserveaspectratio :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. preserveaspectratio = attribute "preserveAspectRatio" " preserveAspectRatio=\"" {-# INLINE preserveaspectratio #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @primitiveUnits@ attribute. -- primitiveunits :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. primitiveunits = attribute "primitiveUnits" " primitiveUnits=\"" {-# INLINE primitiveunits #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @r@ attribute. -- r :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. r = attribute "r" " r=\"" {-# INLINE r #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @radius@ attribute. -- radius :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. radius = attribute "radius" " radius=\"" {-# INLINE radius #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @refX@ attribute. -- refx :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. refx = attribute "refX" " refX=\"" {-# INLINE refx #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @refY@ attribute. -- refy :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. refy = attribute "refY" " refY=\"" {-# INLINE refy #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @rendering-intent@ attribute. -- renderingIntent :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. renderingIntent = attribute "rendering-intent" " rendering-intent=\"" {-# INLINE renderingIntent #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @repeatCount@ attribute. -- repeatcount :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. repeatcount = attribute "repeatCount" " repeatCount=\"" {-# INLINE repeatcount #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @repeatDur@ attribute. -- repeatdur :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. repeatdur = attribute "repeatDur" " repeatDur=\"" {-# INLINE repeatdur #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @requiredExtensions@ attribute. -- requiredextensions :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. requiredextensions = attribute "requiredExtensions" " requiredExtensions=\"" {-# INLINE requiredextensions #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @requiredFeatures@ attribute. -- requiredfeatures :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. requiredfeatures = attribute "requiredFeatures" " requiredFeatures=\"" {-# INLINE requiredfeatures #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @restart@ attribute. -- restart :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. restart = attribute "restart" " restart=\"" {-# INLINE restart #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @result@ attribute. -- result :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. result = attribute "result" " result=\"" {-# INLINE result #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @rotate@ attribute. -- rotate :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. rotate = attribute "rotate" " rotate=\"" {-# INLINE rotate #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @rx@ attribute. -- rx :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. rx = attribute "rx" " rx=\"" {-# INLINE rx #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @ry@ attribute. -- ry :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. ry = attribute "ry" " ry=\"" {-# INLINE ry #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @scale@ attribute. -- scale :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. scale = attribute "scale" " scale=\"" {-# INLINE scale #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @seed@ attribute. -- seed :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. seed = attribute "seed" " seed=\"" {-# INLINE seed #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @shape-rendering@ attribute. -- shapeRendering :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. shapeRendering = attribute "shape-rendering" " shape-rendering=\"" {-# INLINE shapeRendering #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @slope@ attribute. -- slope :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. slope = attribute "slope" " slope=\"" {-# INLINE slope #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @spacing@ attribute. -- spacing :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. spacing = attribute "spacing" " spacing=\"" {-# INLINE spacing #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @specularConstant@ attribute. -- specularconstant :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. specularconstant = attribute "specularConstant" " specularConstant=\"" {-# INLINE specularconstant #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @specularExponent@ attribute. -- specularexponent :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. specularexponent = attribute "specularExponent" " specularExponent=\"" {-# INLINE specularexponent #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @spreadMethod@ attribute. -- spreadmethod :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. spreadmethod = attribute "spreadMethod" " spreadMethod=\"" {-# INLINE spreadmethod #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @startOffset@ attribute. -- startoffset :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. startoffset = attribute "startOffset" " startOffset=\"" {-# INLINE startoffset #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stdDeviation@ attribute. -- stddeviation :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. stddeviation = attribute "stdDeviation" " stdDeviation=\"" {-# INLINE stddeviation #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stemh@ attribute. -- stemh :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. stemh = attribute "stemh" " stemh=\"" {-# INLINE stemh #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stemv@ attribute. -- stemv :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. stemv = attribute "stemv" " stemv=\"" {-# INLINE stemv #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stitchTiles@ attribute. -- stitchtiles :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. stitchtiles = attribute "stitchTiles" " stitchTiles=\"" {-# INLINE stitchtiles #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stop-color@ attribute. -- stopColor :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. stopColor = attribute "stop-color" " stop-color=\"" {-# INLINE stopColor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stop-opacity@ attribute. -- stopOpacity :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. stopOpacity = attribute "stop-opacity" " stop-opacity=\"" {-# INLINE stopOpacity #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @strikethrough-position@ attribute. -- strikethroughPosition :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strikethroughPosition = attribute "strikethrough-position" " strikethrough-position=\"" {-# INLINE strikethroughPosition #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @strikethrough-thickness@ attribute. -- strikethroughThickness :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strikethroughThickness = attribute "strikethrough-thickness" " strikethrough-thickness=\"" {-# INLINE strikethroughThickness #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @string@ attribute. -- string :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. string = attribute "string" " string=\"" {-# INLINE string #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke@ attribute. -- stroke :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. stroke = attribute "stroke" " stroke=\"" {-# INLINE stroke #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke-dasharray@ attribute. -- strokeDasharray :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strokeDasharray = attribute "stroke-dasharray" " stroke-dasharray=\"" {-# INLINE strokeDasharray #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke-dashoffset@ attribute. -- strokeDashoffset :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strokeDashoffset = attribute "stroke-dashoffset" " stroke-dashoffset=\"" {-# INLINE strokeDashoffset #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke-linecap@ attribute. -- strokeLinecap :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strokeLinecap = attribute "stroke-linecap" " stroke-linecap=\"" {-# INLINE strokeLinecap #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke-linejoin@ attribute. -- strokeLinejoin :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strokeLinejoin = attribute "stroke-linejoin" " stroke-linejoin=\"" {-# INLINE strokeLinejoin #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke-miterlimit@ attribute. -- strokeMiterlimit :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strokeMiterlimit = attribute "stroke-miterlimit" " stroke-miterlimit=\"" {-# INLINE strokeMiterlimit #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke-opacity@ attribute. -- strokeOpacity :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strokeOpacity = attribute "stroke-opacity" " stroke-opacity=\"" {-# INLINE strokeOpacity #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @stroke-width@ attribute. -- strokeWidth :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. strokeWidth = attribute "stroke-width" " stroke-width=\"" {-# INLINE strokeWidth #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @style@ attribute. -- style :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. style = attribute "style" " style=\"" {-# INLINE style #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @surfaceScale@ attribute. -- surfacescale :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. surfacescale = attribute "surfaceScale" " surfaceScale=\"" {-# INLINE surfacescale #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @systemLanguage@ attribute. -- systemlanguage :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. systemlanguage = attribute "systemLanguage" " systemLanguage=\"" {-# INLINE systemlanguage #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @tableValues@ attribute. -- tablevalues :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. tablevalues = attribute "tableValues" " tableValues=\"" {-# INLINE tablevalues #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @target@ attribute. -- target :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. target = attribute "target" " target=\"" {-# INLINE target #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @targetX@ attribute. -- targetx :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. targetx = attribute "targetX" " targetX=\"" {-# INLINE targetx #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @targetY@ attribute. -- targety :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. targety = attribute "targetY" " targetY=\"" {-# INLINE targety #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @text-anchor@ attribute. -- textAnchor :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. textAnchor = attribute "text-anchor" " text-anchor=\"" {-# INLINE textAnchor #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @text-decoration@ attribute. -- textDecoration :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. textDecoration = attribute "text-decoration" " text-decoration=\"" {-# INLINE textDecoration #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @text-rendering@ attribute. -- textRendering :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. textRendering = attribute "text-rendering" " text-rendering=\"" {-# INLINE textRendering #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @textLength@ attribute. -- textlength :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. textlength = attribute "textLength" " textLength=\"" {-# INLINE textlength #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @title@ attribute. -- title :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. title = attribute "title" " title=\"" {-# INLINE title #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @to@ attribute. -- to :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. to = attribute "to" " to=\"" {-# INLINE to #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @transform@ attribute. -- transform :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. transform = attribute "transform" " transform=\"" {-# INLINE transform #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @type@ attribute. -- type_ :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. type_ = attribute "type" " type=\"" {-# INLINE type_ #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @u1@ attribute. -- u1 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. u1 = attribute "u1" " u1=\"" {-# INLINE u1 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @u2@ attribute. -- u2 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. u2 = attribute "u2" " u2=\"" {-# INLINE u2 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @underline-position@ attribute. -- underlinePosition :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. underlinePosition = attribute "underline-position" " underline-position=\"" {-# INLINE underlinePosition #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @underline-thickness@ attribute. -- underlineThickness :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. underlineThickness = attribute "underline-thickness" " underline-thickness=\"" {-# INLINE underlineThickness #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @unicode@ attribute. -- unicode :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. unicode = attribute "unicode" " unicode=\"" {-# INLINE unicode #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @unicode-bidi@ attribute. -- unicodeBidi :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. unicodeBidi = attribute "unicode-bidi" " unicode-bidi=\"" {-# INLINE unicodeBidi #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @unicode-range@ attribute. -- unicodeRange :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. unicodeRange = attribute "unicode-range" " unicode-range=\"" {-# INLINE unicodeRange #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @units-per-em@ attribute. -- unitsPerEm :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. unitsPerEm = attribute "units-per-em" " units-per-em=\"" {-# INLINE unitsPerEm #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @v-alphabetic@ attribute. -- vAlphabetic :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. vAlphabetic = attribute "v-alphabetic" " v-alphabetic=\"" {-# INLINE vAlphabetic #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @v-hanging@ attribute. -- vHanging :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. vHanging = attribute "v-hanging" " v-hanging=\"" {-# INLINE vHanging #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @v-ideographic@ attribute. -- vIdeographic :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. vIdeographic = attribute "v-ideographic" " v-ideographic=\"" {-# INLINE vIdeographic #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @v-mathematical@ attribute. -- vMathematical :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. vMathematical = attribute "v-mathematical" " v-mathematical=\"" {-# INLINE vMathematical #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @values@ attribute. -- values :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. values = attribute "values" " values=\"" {-# INLINE values #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @version@ attribute. -- version :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. version = attribute "version" " version=\"" {-# INLINE version #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @vert-adv-y@ attribute. -- vertAdvY :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. vertAdvY = attribute "vert-adv-y" " vert-adv-y=\"" {-# INLINE vertAdvY #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @vert-origin-x@ attribute. -- vertOriginX :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. vertOriginX = attribute "vert-origin-x" " vert-origin-x=\"" {-# INLINE vertOriginX #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @vert-origin-y@ attribute. -- vertOriginY :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. vertOriginY = attribute "vert-origin-y" " vert-origin-y=\"" {-# INLINE vertOriginY #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @viewBox@ attribute. -- viewbox :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. viewbox = attribute "viewBox" " viewBox=\"" {-# INLINE viewbox #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @viewTarget@ attribute. -- viewtarget :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. viewtarget = attribute "viewTarget" " viewTarget=\"" {-# INLINE viewtarget #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @visibility@ attribute. -- visibility :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. visibility = attribute "visibility" " visibility=\"" {-# INLINE visibility #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @width@ attribute. -- width :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. width = attribute "width" " width=\"" {-# INLINE width #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @widths@ attribute. -- widths :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. widths = attribute "widths" " widths=\"" {-# INLINE widths #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @word-spacing@ attribute. -- wordSpacing :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. wordSpacing = attribute "word-spacing" " word-spacing=\"" {-# INLINE wordSpacing #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @writing-mode@ attribute. -- writingMode :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. writingMode = attribute "writing-mode" " writing-mode=\"" {-# INLINE writingMode #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @x@ attribute. -- x :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. x = attribute "x" " x=\"" {-# INLINE x #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @x-height@ attribute. -- xHeight :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xHeight = attribute "x-height" " x-height=\"" {-# INLINE xHeight #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @x1@ attribute. -- x1 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. x1 = attribute "x1" " x1=\"" {-# INLINE x1 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @x2@ attribute. -- x2 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. x2 = attribute "x2" " x2=\"" {-# INLINE x2 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xChannelSelector@ attribute. -- xchannelselector :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xchannelselector = attribute "xChannelSelector" " xChannelSelector=\"" {-# INLINE xchannelselector #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xlink:actuate@ attribute. -- xlinkActuate :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xlinkActuate = attribute "xlink:actuate" " xlink:actuate=\"" {-# INLINE xlinkActuate #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xlink:arcrole@ attribute. -- xlinkArcrole :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xlinkArcrole = attribute "xlink:arcrole" " xlink:arcrole=\"" {-# INLINE xlinkArcrole #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xlink:href@ attribute. -- xlinkHref :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xlinkHref = attribute "xlink:href" " xlink:href=\"" {-# INLINE xlinkHref #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xlink:role@ attribute. -- xlinkRole :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xlinkRole = attribute "xlink:role" " xlink:role=\"" {-# INLINE xlinkRole #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xlink:show@ attribute. -- xlinkShow :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xlinkShow = attribute "xlink:show" " xlink:show=\"" {-# INLINE xlinkShow #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xlink:title@ attribute. -- xlinkTitle :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xlinkTitle = attribute "xlink:title" " xlink:title=\"" {-# INLINE xlinkTitle #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xlink:type@ attribute. -- xlinkType :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xlinkType = attribute "xlink:type" " xlink:type=\"" {-# INLINE xlinkType #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xml:base@ attribute. -- xmlBase :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xmlBase = attribute "xml:base" " xml:base=\"" {-# INLINE xmlBase #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xml:lang@ attribute. -- xmlLang :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xmlLang = attribute "xml:lang" " xml:lang=\"" {-# INLINE xmlLang #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @xml:space@ attribute. -- xmlSpace :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. xmlSpace = attribute "xml:space" " xml:space=\"" {-# INLINE xmlSpace #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @y@ attribute. -- y :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. y = attribute "y" " y=\"" {-# INLINE y #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @y1@ attribute. -- y1 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. y1 = attribute "y1" " y1=\"" {-# INLINE y1 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @y2@ attribute. -- y2 :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. y2 = attribute "y2" " y2=\"" {-# INLINE y2 #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @yChannelSelector@ attribute. -- ychannelselector :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. ychannelselector = attribute "yChannelSelector" " yChannelSelector=\"" {-# INLINE ychannelselector #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @z@ attribute. -- z :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. z = attribute "z" " z=\"" {-# INLINE z #-} -- WARNING: The next block of code was automatically generated by -- src/Util/GenerateSvgCombinators.hs:220 -- -- | Combinator for the @zoomAndPan@ attribute. -- zoomandpan :: AttributeValue -- ^ Attribute value. -> Attribute -- ^ Resulting attribute. zoomandpan = attribute "zoomAndPan" " zoomAndPan=\"" {-# INLINE zoomandpan #-} �������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/examples/���������������������������������������������������������������������������0000755�0000000�0000000�00000000000�12642557533�013431� 5����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������blaze-svg-0.3.5/examples/Example.hs�����������������������������������������������������������������0000644�0000000�0000000�00000001425�12642557533�015362� 0����������������������������������������������������������������������������������������������������ustar�00����������������������������������������������������������������0000000�0000000������������������������������������������������������������������������������������������������������������������������������������������������������������������������{-# LANGUAGE OverloadedStrings #-} import Text.Blaze.Svg11 ((!), mkPath, rotate, l, m) import qualified Text.Blaze.Svg11 as S import qualified Text.Blaze.Svg11.Attributes as A import Text.Blaze.Svg.Renderer.String (renderSvg) main :: IO () main = do let a = renderSvg svgDoc putStrLn a svgDoc :: S.Svg svgDoc = S.docTypeSvg ! A.version "1.1" ! A.width "150" ! A.height "100" ! A.viewbox "0 0 3 2" $ do S.g ! A.transform makeTransform $ do S.rect ! A.width "1" ! A.height "2" ! A.fill "#008d46" S.rect ! A.width "1" ! A.height "2" ! A.fill "#ffffff" S.rect ! A.width "1" ! A.height "2" ! A.fill "#d2232c" S.path ! A.d makePath makePath :: S.AttributeValue makePath = mkPath $ do l 2 3 m 4 5 makeTransform :: S.AttributeValue makeTransform = rotate 50�����������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������������