{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
-- |
-- Module      : Graphics.Color.Standard.SVG
-- Copyright   : (c) Alexey Kuleshevich 2021
-- License     : BSD3
-- Maintainer  : Alexey Kuleshevich <lehins@yandex.ru>
-- Stability   : experimental
-- Portability : non-portable
--
-- Source: https://www.w3.org/TR/SVG11/types.html#ColorKeywords
module Graphics.Color.Standard.SVG where
-- This file is generated with files/mkStdSVGModule

import Prelude hiding (tan)
import Graphics.Color.Space.RGB
import GHC.TypeLits
import Graphics.Color.Adaptation.VonKries
import Graphics.Color.Standard.Internal

-- | Get a color value by specifying its SVG standard name at the type level:
--
-- >>> import Graphics.Color.Standard
-- >>> import Graphics.Color.Space.CIE1976.LAB
-- >>> import Graphics.Color.Illuminant.CIE1931
-- >>> color (SVG :: SVG "aqua") :: Color (LAB 'D65) Float
-- <LAB CIE1931 'D65:(91.11637000,-48.08154700,-14.12457300)>
--
data SVG (n :: Symbol) = SVG

instance KnownSymbol n => Show (SVG (n :: Symbol)) where
  showsPrec :: Int -> SVG n -> ShowS
showsPrec Int
n SVG n
c
    | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = ShowS
p ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SVG n -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal SVG n
c String -> ShowS
forall a. [a] -> [a] -> [a]
++)
    | Bool
otherwise = (Char
'(' Char -> ShowS
forall a. a -> [a] -> [a]
:) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
p ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SVG n -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal SVG n
c String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
')' Char -> ShowS
forall a. a -> [a] -> [a]
:)
    where
      p :: ShowS
p = (String
"SVG " String -> ShowS
forall a. [a] -> [a] -> [a]
++)

-- | Source: https://www.w3.org/TR/SVG11/types.html#ColorKeywords
--
-- @since 0.3.3
allSVGColors :: [(String, Color (SRGB 'NonLinear) Word8)]
allSVGColors :: [(String, Color (SRGB 'NonLinear) Word8)]
allSVGColors =
  [ (String
"aliceblue", Color (SRGB 'NonLinear) Word8
aliceBlue)
  , (String
"antiquewhite", Color (SRGB 'NonLinear) Word8
antiqueWhite)
  , (String
"aqua", Color (SRGB 'NonLinear) Word8
aqua)
  , (String
"aquamarine", Color (SRGB 'NonLinear) Word8
aquaMarine)
  , (String
"azure", Color (SRGB 'NonLinear) Word8
azure)
  , (String
"beige", Color (SRGB 'NonLinear) Word8
beige)
  , (String
"bisque", Color (SRGB 'NonLinear) Word8
bisque)
  , (String
"black", Color (SRGB 'NonLinear) Word8
black)
  , (String
"blanchedalmond", Color (SRGB 'NonLinear) Word8
blanchedAlmond)
  , (String
"blue", Color (SRGB 'NonLinear) Word8
blue)
  , (String
"blueviolet", Color (SRGB 'NonLinear) Word8
blueViolet)
  , (String
"brown", Color (SRGB 'NonLinear) Word8
brown)
  , (String
"burlywood", Color (SRGB 'NonLinear) Word8
burlyWood)
  , (String
"cadetblue", Color (SRGB 'NonLinear) Word8
cadetBlue)
  , (String
"chartreuse", Color (SRGB 'NonLinear) Word8
chartreuse)
  , (String
"chocolate", Color (SRGB 'NonLinear) Word8
chocolate)
  , (String
"coral", Color (SRGB 'NonLinear) Word8
coral)
  , (String
"cornflowerblue", Color (SRGB 'NonLinear) Word8
cornFlowerBlue)
  , (String
"cornsilk", Color (SRGB 'NonLinear) Word8
cornSilk)
  , (String
"crimson", Color (SRGB 'NonLinear) Word8
crimson)
  , (String
"cyan", Color (SRGB 'NonLinear) Word8
cyan)
  , (String
"darkblue", Color (SRGB 'NonLinear) Word8
darkBlue)
  , (String
"darkcyan", Color (SRGB 'NonLinear) Word8
darkCyan)
  , (String
"darkgoldenrod", Color (SRGB 'NonLinear) Word8
darkGoldenRod)
  , (String
"darkgray", Color (SRGB 'NonLinear) Word8
darkGray)
  , (String
"darkgreen", Color (SRGB 'NonLinear) Word8
darkGreen)
  , (String
"darkgrey", Color (SRGB 'NonLinear) Word8
darkGrey)
  , (String
"darkkhaki", Color (SRGB 'NonLinear) Word8
darkKhaki)
  , (String
"darkmagenta", Color (SRGB 'NonLinear) Word8
darkMagenta)
  , (String
"darkolivegreen", Color (SRGB 'NonLinear) Word8
darkOliveGreen)
  , (String
"darkorange", Color (SRGB 'NonLinear) Word8
darkOrange)
  , (String
"darkorchid", Color (SRGB 'NonLinear) Word8
darkOrchid)
  , (String
"darkred", Color (SRGB 'NonLinear) Word8
darkRed)
  , (String
"darksalmon", Color (SRGB 'NonLinear) Word8
darkSalmon)
  , (String
"darkseagreen", Color (SRGB 'NonLinear) Word8
darkSeaGreen)
  , (String
"darkslateblue", Color (SRGB 'NonLinear) Word8
darkSlateBlue)
  , (String
"darkslategray", Color (SRGB 'NonLinear) Word8
darkSlateGray)
  , (String
"darkslategrey", Color (SRGB 'NonLinear) Word8
darkSlateGrey)
  , (String
"darkturquoise", Color (SRGB 'NonLinear) Word8
darkTurquoise)
  , (String
"darkviolet", Color (SRGB 'NonLinear) Word8
darkViolet)
  , (String
"deeppink", Color (SRGB 'NonLinear) Word8
deepPink)
  , (String
"deepskyblue", Color (SRGB 'NonLinear) Word8
deepSkyBlue)
  , (String
"dimgray", Color (SRGB 'NonLinear) Word8
dimGray)
  , (String
"dimgrey", Color (SRGB 'NonLinear) Word8
dimGrey)
  , (String
"dodgerblue", Color (SRGB 'NonLinear) Word8
dodgerBlue)
  , (String
"firebrick", Color (SRGB 'NonLinear) Word8
fireBrick)
  , (String
"floralwhite", Color (SRGB 'NonLinear) Word8
floralWhite)
  , (String
"forestgreen", Color (SRGB 'NonLinear) Word8
forestGreen)
  , (String
"fuchsia", Color (SRGB 'NonLinear) Word8
fuchsia)
  , (String
"gainsboro", Color (SRGB 'NonLinear) Word8
gainsboro)
  , (String
"ghostwhite", Color (SRGB 'NonLinear) Word8
ghostWhite)
  , (String
"gold", Color (SRGB 'NonLinear) Word8
gold)
  , (String
"goldenrod", Color (SRGB 'NonLinear) Word8
goldenRod)
  , (String
"gray", Color (SRGB 'NonLinear) Word8
gray)
  , (String
"grey", Color (SRGB 'NonLinear) Word8
grey)
  , (String
"green", Color (SRGB 'NonLinear) Word8
green)
  , (String
"greenyellow", Color (SRGB 'NonLinear) Word8
greenYellow)
  , (String
"honeydew", Color (SRGB 'NonLinear) Word8
honeydew)
  , (String
"hotpink", Color (SRGB 'NonLinear) Word8
hotPink)
  , (String
"indianred", Color (SRGB 'NonLinear) Word8
indianRed)
  , (String
"indigo", Color (SRGB 'NonLinear) Word8
indigo)
  , (String
"ivory", Color (SRGB 'NonLinear) Word8
ivory)
  , (String
"khaki", Color (SRGB 'NonLinear) Word8
khaki)
  , (String
"lavender", Color (SRGB 'NonLinear) Word8
lavender)
  , (String
"lavenderblush", Color (SRGB 'NonLinear) Word8
lavenderBlush)
  , (String
"lawngreen", Color (SRGB 'NonLinear) Word8
lawnGreen)
  , (String
"lemonchiffon", Color (SRGB 'NonLinear) Word8
lemonChiffon)
  , (String
"lightblue", Color (SRGB 'NonLinear) Word8
lightBlue)
  , (String
"lightcoral", Color (SRGB 'NonLinear) Word8
lightCoral)
  , (String
"lightcyan", Color (SRGB 'NonLinear) Word8
lightCyan)
  , (String
"lightgoldenrodyellow", Color (SRGB 'NonLinear) Word8
lightGoldenRodYellow)
  , (String
"lightgray", Color (SRGB 'NonLinear) Word8
lightGray)
  , (String
"lightgreen", Color (SRGB 'NonLinear) Word8
lightGreen)
  , (String
"lightgrey", Color (SRGB 'NonLinear) Word8
lightGrey)
  , (String
"lightpink", Color (SRGB 'NonLinear) Word8
lightPink)
  , (String
"lightsalmon", Color (SRGB 'NonLinear) Word8
lightSalmon)
  , (String
"lightseagreen", Color (SRGB 'NonLinear) Word8
lightSeaGreen)
  , (String
"lightskyblue", Color (SRGB 'NonLinear) Word8
lightSkyBlue)
  , (String
"lightslategray", Color (SRGB 'NonLinear) Word8
lightSlateGray)
  , (String
"lightslategrey", Color (SRGB 'NonLinear) Word8
lightSlateGrey)
  , (String
"lightsteelblue", Color (SRGB 'NonLinear) Word8
lightSteelBlue)
  , (String
"lightyellow", Color (SRGB 'NonLinear) Word8
lightYellow)
  , (String
"lime", Color (SRGB 'NonLinear) Word8
lime)
  , (String
"limegreen", Color (SRGB 'NonLinear) Word8
limeGreen)
  , (String
"linen", Color (SRGB 'NonLinear) Word8
linen)
  , (String
"magenta", Color (SRGB 'NonLinear) Word8
magenta)
  , (String
"maroon", Color (SRGB 'NonLinear) Word8
maroon)
  , (String
"mediumaquamarine", Color (SRGB 'NonLinear) Word8
mediumAquaMarine)
  , (String
"mediumblue", Color (SRGB 'NonLinear) Word8
mediumBlue)
  , (String
"mediumorchid", Color (SRGB 'NonLinear) Word8
mediumOrchid)
  , (String
"mediumpurple", Color (SRGB 'NonLinear) Word8
mediumPurple)
  , (String
"mediumseagreen", Color (SRGB 'NonLinear) Word8
mediumSeaGreen)
  , (String
"mediumslateblue", Color (SRGB 'NonLinear) Word8
mediumSlateBlue)
  , (String
"mediumspringgreen", Color (SRGB 'NonLinear) Word8
mediumSpringGreen)
  , (String
"mediumturquoise", Color (SRGB 'NonLinear) Word8
mediumTurquoise)
  , (String
"mediumvioletred", Color (SRGB 'NonLinear) Word8
mediumVioletRed)
  , (String
"midnightblue", Color (SRGB 'NonLinear) Word8
midnightBlue)
  , (String
"mintcream", Color (SRGB 'NonLinear) Word8
mintCream)
  , (String
"mistyrose", Color (SRGB 'NonLinear) Word8
mistyRose)
  , (String
"moccasin", Color (SRGB 'NonLinear) Word8
moccasin)
  , (String
"navajowhite", Color (SRGB 'NonLinear) Word8
navajoWhite)
  , (String
"navy", Color (SRGB 'NonLinear) Word8
navy)
  , (String
"oldlace", Color (SRGB 'NonLinear) Word8
oldLace)
  , (String
"olive", Color (SRGB 'NonLinear) Word8
olive)
  , (String
"olivedrab", Color (SRGB 'NonLinear) Word8
oliveDrab)
  , (String
"orange", Color (SRGB 'NonLinear) Word8
orange)
  , (String
"orangered", Color (SRGB 'NonLinear) Word8
orangeRed)
  , (String
"orchid", Color (SRGB 'NonLinear) Word8
orchid)
  , (String
"palegoldenrod", Color (SRGB 'NonLinear) Word8
paleGoldenRod)
  , (String
"palegreen", Color (SRGB 'NonLinear) Word8
paleGreen)
  , (String
"paleturquoise", Color (SRGB 'NonLinear) Word8
paleTurquoise)
  , (String
"palevioletred", Color (SRGB 'NonLinear) Word8
paleVioletRed)
  , (String
"papayawhip", Color (SRGB 'NonLinear) Word8
papayaWhip)
  , (String
"peachpuff", Color (SRGB 'NonLinear) Word8
peachPuff)
  , (String
"peru", Color (SRGB 'NonLinear) Word8
peru)
  , (String
"pink", Color (SRGB 'NonLinear) Word8
pink)
  , (String
"plum", Color (SRGB 'NonLinear) Word8
plum)
  , (String
"powderblue", Color (SRGB 'NonLinear) Word8
powderBlue)
  , (String
"purple", Color (SRGB 'NonLinear) Word8
purple)
  , (String
"red", Color (SRGB 'NonLinear) Word8
red)
  , (String
"rosybrown", Color (SRGB 'NonLinear) Word8
rosyBrown)
  , (String
"royalblue", Color (SRGB 'NonLinear) Word8
royalBlue)
  , (String
"saddlebrown", Color (SRGB 'NonLinear) Word8
saddleBrown)
  , (String
"salmon", Color (SRGB 'NonLinear) Word8
salmon)
  , (String
"sandybrown", Color (SRGB 'NonLinear) Word8
sandyBrown)
  , (String
"seagreen", Color (SRGB 'NonLinear) Word8
seaGreen)
  , (String
"seashell", Color (SRGB 'NonLinear) Word8
seashell)
  , (String
"sienna", Color (SRGB 'NonLinear) Word8
sienna)
  , (String
"silver", Color (SRGB 'NonLinear) Word8
silver)
  , (String
"skyblue", Color (SRGB 'NonLinear) Word8
skyBlue)
  , (String
"slateblue", Color (SRGB 'NonLinear) Word8
slateBlue)
  , (String
"slategray", Color (SRGB 'NonLinear) Word8
slateGray)
  , (String
"slategrey", Color (SRGB 'NonLinear) Word8
slateGrey)
  , (String
"snow", Color (SRGB 'NonLinear) Word8
snow)
  , (String
"springgreen", Color (SRGB 'NonLinear) Word8
springGreen)
  , (String
"steelblue", Color (SRGB 'NonLinear) Word8
steelBlue)
  , (String
"tan", Color (SRGB 'NonLinear) Word8
tan)
  , (String
"teal", Color (SRGB 'NonLinear) Word8
teal)
  , (String
"thistle", Color (SRGB 'NonLinear) Word8
thistle)
  , (String
"tomato", Color (SRGB 'NonLinear) Word8
tomato)
  , (String
"turquoise", Color (SRGB 'NonLinear) Word8
turquoise)
  , (String
"violet", Color (SRGB 'NonLinear) Word8
violet)
  , (String
"wheat", Color (SRGB 'NonLinear) Word8
wheat)
  , (String
"white", Color (SRGB 'NonLinear) Word8
white)
  , (String
"whitesmoke", Color (SRGB 'NonLinear) Word8
whiteSmoke)
  , (String
"yellow", Color (SRGB 'NonLinear) Word8
yellow)
  , (String
"yellowgreen", Color (SRGB 'NonLinear) Word8
yellowGreen)
  ]

-- | <<files/svg/AliceBlue.png>>
instance StandardColor SVG "aliceblue" where color :: SVG "aliceblue" -> Color cs e
color SVG "aliceblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
aliceBlue

-- | <<files/svg/AntiqueWhite.png>>
instance StandardColor SVG "antiquewhite" where color :: SVG "antiquewhite" -> Color cs e
color SVG "antiquewhite"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
antiqueWhite

-- | <<files/svg/Aqua.png>>
instance StandardColor SVG "aqua" where color :: SVG "aqua" -> Color cs e
color SVG "aqua"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
aqua

-- | <<files/svg/AquaMarine.png>>
instance StandardColor SVG "aquamarine" where color :: SVG "aquamarine" -> Color cs e
color SVG "aquamarine"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
aquaMarine

-- | <<files/svg/Azure.png>>
instance StandardColor SVG "azure" where color :: SVG "azure" -> Color cs e
color SVG "azure"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
azure

-- | <<files/svg/Beige.png>>
instance StandardColor SVG "beige" where color :: SVG "beige" -> Color cs e
color SVG "beige"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
beige

-- | <<files/svg/Bisque.png>>
instance StandardColor SVG "bisque" where color :: SVG "bisque" -> Color cs e
color SVG "bisque"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
bisque

-- | <<files/svg/Black.png>>
instance StandardColor SVG "black" where color :: SVG "black" -> Color cs e
color SVG "black"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
black

-- | <<files/svg/BlanchedAlmond.png>>
instance StandardColor SVG "blanchedalmond" where color :: SVG "blanchedalmond" -> Color cs e
color SVG "blanchedalmond"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
blanchedAlmond

-- | <<files/svg/Blue.png>>
instance StandardColor SVG "blue" where color :: SVG "blue" -> Color cs e
color SVG "blue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
blue

-- | <<files/svg/BlueViolet.png>>
instance StandardColor SVG "blueviolet" where color :: SVG "blueviolet" -> Color cs e
color SVG "blueviolet"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
blueViolet

-- | <<files/svg/Brown.png>>
instance StandardColor SVG "brown" where color :: SVG "brown" -> Color cs e
color SVG "brown"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
brown

-- | <<files/svg/BurlyWood.png>>
instance StandardColor SVG "burlywood" where color :: SVG "burlywood" -> Color cs e
color SVG "burlywood"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
burlyWood

-- | <<files/svg/CadetBlue.png>>
instance StandardColor SVG "cadetblue" where color :: SVG "cadetblue" -> Color cs e
color SVG "cadetblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
cadetBlue

-- | <<files/svg/Chartreuse.png>>
instance StandardColor SVG "chartreuse" where color :: SVG "chartreuse" -> Color cs e
color SVG "chartreuse"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
chartreuse

-- | <<files/svg/Chocolate.png>>
instance StandardColor SVG "chocolate" where color :: SVG "chocolate" -> Color cs e
color SVG "chocolate"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
chocolate

-- | <<files/svg/Coral.png>>
instance StandardColor SVG "coral" where color :: SVG "coral" -> Color cs e
color SVG "coral"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
coral

-- | <<files/svg/CornFlowerBlue.png>>
instance StandardColor SVG "cornflowerblue" where color :: SVG "cornflowerblue" -> Color cs e
color SVG "cornflowerblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
cornFlowerBlue

-- | <<files/svg/CornSilk.png>>
instance StandardColor SVG "cornsilk" where color :: SVG "cornsilk" -> Color cs e
color SVG "cornsilk"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
cornSilk

-- | <<files/svg/Crimson.png>>
instance StandardColor SVG "crimson" where color :: SVG "crimson" -> Color cs e
color SVG "crimson"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
crimson

-- | <<files/svg/Cyan.png>>
instance StandardColor SVG "cyan" where color :: SVG "cyan" -> Color cs e
color SVG "cyan"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
cyan

-- | <<files/svg/DarkBlue.png>>
instance StandardColor SVG "darkblue" where color :: SVG "darkblue" -> Color cs e
color SVG "darkblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkBlue

-- | <<files/svg/DarkCyan.png>>
instance StandardColor SVG "darkcyan" where color :: SVG "darkcyan" -> Color cs e
color SVG "darkcyan"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkCyan

-- | <<files/svg/DarkGoldenRod.png>>
instance StandardColor SVG "darkgoldenrod" where color :: SVG "darkgoldenrod" -> Color cs e
color SVG "darkgoldenrod"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkGoldenRod

-- | <<files/svg/DarkGray.png>>
instance StandardColor SVG "darkgray" where color :: SVG "darkgray" -> Color cs e
color SVG "darkgray"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkGray

-- | <<files/svg/DarkGreen.png>>
instance StandardColor SVG "darkgreen" where color :: SVG "darkgreen" -> Color cs e
color SVG "darkgreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkGreen

-- | <<files/svg/DarkGrey.png>>
instance StandardColor SVG "darkgrey" where color :: SVG "darkgrey" -> Color cs e
color SVG "darkgrey"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkGrey

-- | <<files/svg/DarkKhaki.png>>
instance StandardColor SVG "darkkhaki" where color :: SVG "darkkhaki" -> Color cs e
color SVG "darkkhaki"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkKhaki

-- | <<files/svg/DarkMagenta.png>>
instance StandardColor SVG "darkmagenta" where color :: SVG "darkmagenta" -> Color cs e
color SVG "darkmagenta"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkMagenta

-- | <<files/svg/DarkOliveGreen.png>>
instance StandardColor SVG "darkolivegreen" where color :: SVG "darkolivegreen" -> Color cs e
color SVG "darkolivegreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkOliveGreen

-- | <<files/svg/DarkOrange.png>>
instance StandardColor SVG "darkorange" where color :: SVG "darkorange" -> Color cs e
color SVG "darkorange"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkOrange

-- | <<files/svg/DarkOrchid.png>>
instance StandardColor SVG "darkorchid" where color :: SVG "darkorchid" -> Color cs e
color SVG "darkorchid"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkOrchid

-- | <<files/svg/DarkRed.png>>
instance StandardColor SVG "darkred" where color :: SVG "darkred" -> Color cs e
color SVG "darkred"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkRed

-- | <<files/svg/DarkSalmon.png>>
instance StandardColor SVG "darksalmon" where color :: SVG "darksalmon" -> Color cs e
color SVG "darksalmon"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkSalmon

-- | <<files/svg/DarkSeaGreen.png>>
instance StandardColor SVG "darkseagreen" where color :: SVG "darkseagreen" -> Color cs e
color SVG "darkseagreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkSeaGreen

-- | <<files/svg/DarkSlateBlue.png>>
instance StandardColor SVG "darkslateblue" where color :: SVG "darkslateblue" -> Color cs e
color SVG "darkslateblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkSlateBlue

-- | <<files/svg/DarkSlateGray.png>>
instance StandardColor SVG "darkslategray" where color :: SVG "darkslategray" -> Color cs e
color SVG "darkslategray"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkSlateGray

-- | <<files/svg/DarkSlateGrey.png>>
instance StandardColor SVG "darkslategrey" where color :: SVG "darkslategrey" -> Color cs e
color SVG "darkslategrey"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkSlateGrey

-- | <<files/svg/DarkTurquoise.png>>
instance StandardColor SVG "darkturquoise" where color :: SVG "darkturquoise" -> Color cs e
color SVG "darkturquoise"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkTurquoise

-- | <<files/svg/DarkViolet.png>>
instance StandardColor SVG "darkviolet" where color :: SVG "darkviolet" -> Color cs e
color SVG "darkviolet"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
darkViolet

-- | <<files/svg/DeepPink.png>>
instance StandardColor SVG "deeppink" where color :: SVG "deeppink" -> Color cs e
color SVG "deeppink"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
deepPink

-- | <<files/svg/DeepSkyBlue.png>>
instance StandardColor SVG "deepskyblue" where color :: SVG "deepskyblue" -> Color cs e
color SVG "deepskyblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
deepSkyBlue

-- | <<files/svg/DimGray.png>>
instance StandardColor SVG "dimgray" where color :: SVG "dimgray" -> Color cs e
color SVG "dimgray"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
dimGray

-- | <<files/svg/DimGrey.png>>
instance StandardColor SVG "dimgrey" where color :: SVG "dimgrey" -> Color cs e
color SVG "dimgrey"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
dimGrey

-- | <<files/svg/DodgerBlue.png>>
instance StandardColor SVG "dodgerblue" where color :: SVG "dodgerblue" -> Color cs e
color SVG "dodgerblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
dodgerBlue

-- | <<files/svg/FireBrick.png>>
instance StandardColor SVG "firebrick" where color :: SVG "firebrick" -> Color cs e
color SVG "firebrick"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
fireBrick

-- | <<files/svg/FloralWhite.png>>
instance StandardColor SVG "floralwhite" where color :: SVG "floralwhite" -> Color cs e
color SVG "floralwhite"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
floralWhite

-- | <<files/svg/ForestGreen.png>>
instance StandardColor SVG "forestgreen" where color :: SVG "forestgreen" -> Color cs e
color SVG "forestgreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
forestGreen

-- | <<files/svg/Fuchsia.png>>
instance StandardColor SVG "fuchsia" where color :: SVG "fuchsia" -> Color cs e
color SVG "fuchsia"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
fuchsia

-- | <<files/svg/Gainsboro.png>>
instance StandardColor SVG "gainsboro" where color :: SVG "gainsboro" -> Color cs e
color SVG "gainsboro"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
gainsboro

-- | <<files/svg/GhostWhite.png>>
instance StandardColor SVG "ghostwhite" where color :: SVG "ghostwhite" -> Color cs e
color SVG "ghostwhite"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
ghostWhite

-- | <<files/svg/Gold.png>>
instance StandardColor SVG "gold" where color :: SVG "gold" -> Color cs e
color SVG "gold"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
gold

-- | <<files/svg/GoldenRod.png>>
instance StandardColor SVG "goldenrod" where color :: SVG "goldenrod" -> Color cs e
color SVG "goldenrod"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
goldenRod

-- | <<files/svg/Gray.png>>
instance StandardColor SVG "gray" where color :: SVG "gray" -> Color cs e
color SVG "gray"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
gray

-- | <<files/svg/Grey.png>>
instance StandardColor SVG "grey" where color :: SVG "grey" -> Color cs e
color SVG "grey"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
grey

-- | <<files/svg/Green.png>>
instance StandardColor SVG "green" where color :: SVG "green" -> Color cs e
color SVG "green"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
green

-- | <<files/svg/GreenYellow.png>>
instance StandardColor SVG "greenyellow" where color :: SVG "greenyellow" -> Color cs e
color SVG "greenyellow"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
greenYellow

-- | <<files/svg/Honeydew.png>>
instance StandardColor SVG "honeydew" where color :: SVG "honeydew" -> Color cs e
color SVG "honeydew"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
honeydew

-- | <<files/svg/HotPink.png>>
instance StandardColor SVG "hotpink" where color :: SVG "hotpink" -> Color cs e
color SVG "hotpink"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
hotPink

-- | <<files/svg/IndianRed.png>>
instance StandardColor SVG "indianred" where color :: SVG "indianred" -> Color cs e
color SVG "indianred"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
indianRed

-- | <<files/svg/Indigo.png>>
instance StandardColor SVG "indigo" where color :: SVG "indigo" -> Color cs e
color SVG "indigo"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
indigo

-- | <<files/svg/Ivory.png>>
instance StandardColor SVG "ivory" where color :: SVG "ivory" -> Color cs e
color SVG "ivory"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
ivory

-- | <<files/svg/Khaki.png>>
instance StandardColor SVG "khaki" where color :: SVG "khaki" -> Color cs e
color SVG "khaki"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
khaki

-- | <<files/svg/Lavender.png>>
instance StandardColor SVG "lavender" where color :: SVG "lavender" -> Color cs e
color SVG "lavender"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lavender

-- | <<files/svg/LavenderBlush.png>>
instance StandardColor SVG "lavenderblush" where color :: SVG "lavenderblush" -> Color cs e
color SVG "lavenderblush"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lavenderBlush

-- | <<files/svg/LawnGreen.png>>
instance StandardColor SVG "lawngreen" where color :: SVG "lawngreen" -> Color cs e
color SVG "lawngreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lawnGreen

-- | <<files/svg/LemonChiffon.png>>
instance StandardColor SVG "lemonchiffon" where color :: SVG "lemonchiffon" -> Color cs e
color SVG "lemonchiffon"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lemonChiffon

-- | <<files/svg/LightBlue.png>>
instance StandardColor SVG "lightblue" where color :: SVG "lightblue" -> Color cs e
color SVG "lightblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightBlue

-- | <<files/svg/LightCoral.png>>
instance StandardColor SVG "lightcoral" where color :: SVG "lightcoral" -> Color cs e
color SVG "lightcoral"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightCoral

-- | <<files/svg/LightCyan.png>>
instance StandardColor SVG "lightcyan" where color :: SVG "lightcyan" -> Color cs e
color SVG "lightcyan"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightCyan

-- | <<files/svg/LightGoldenRodYellow.png>>
instance StandardColor SVG "lightgoldenrodyellow" where color :: SVG "lightgoldenrodyellow" -> Color cs e
color SVG "lightgoldenrodyellow"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightGoldenRodYellow

-- | <<files/svg/LightGray.png>>
instance StandardColor SVG "lightgray" where color :: SVG "lightgray" -> Color cs e
color SVG "lightgray"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightGray

-- | <<files/svg/LightGreen.png>>
instance StandardColor SVG "lightgreen" where color :: SVG "lightgreen" -> Color cs e
color SVG "lightgreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightGreen

-- | <<files/svg/LightGrey.png>>
instance StandardColor SVG "lightgrey" where color :: SVG "lightgrey" -> Color cs e
color SVG "lightgrey"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightGrey

-- | <<files/svg/LightPink.png>>
instance StandardColor SVG "lightpink" where color :: SVG "lightpink" -> Color cs e
color SVG "lightpink"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightPink

-- | <<files/svg/LightSalmon.png>>
instance StandardColor SVG "lightsalmon" where color :: SVG "lightsalmon" -> Color cs e
color SVG "lightsalmon"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightSalmon

-- | <<files/svg/LightSeaGreen.png>>
instance StandardColor SVG "lightseagreen" where color :: SVG "lightseagreen" -> Color cs e
color SVG "lightseagreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightSeaGreen

-- | <<files/svg/LightSkyBlue.png>>
instance StandardColor SVG "lightskyblue" where color :: SVG "lightskyblue" -> Color cs e
color SVG "lightskyblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightSkyBlue

-- | <<files/svg/LightSlateGray.png>>
instance StandardColor SVG "lightslategray" where color :: SVG "lightslategray" -> Color cs e
color SVG "lightslategray"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightSlateGray

-- | <<files/svg/LightSlateGrey.png>>
instance StandardColor SVG "lightslategrey" where color :: SVG "lightslategrey" -> Color cs e
color SVG "lightslategrey"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightSlateGrey

-- | <<files/svg/LightSteelBlue.png>>
instance StandardColor SVG "lightsteelblue" where color :: SVG "lightsteelblue" -> Color cs e
color SVG "lightsteelblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightSteelBlue

-- | <<files/svg/LightYellow.png>>
instance StandardColor SVG "lightyellow" where color :: SVG "lightyellow" -> Color cs e
color SVG "lightyellow"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lightYellow

-- | <<files/svg/Lime.png>>
instance StandardColor SVG "lime" where color :: SVG "lime" -> Color cs e
color SVG "lime"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
lime

-- | <<files/svg/LimeGreen.png>>
instance StandardColor SVG "limegreen" where color :: SVG "limegreen" -> Color cs e
color SVG "limegreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
limeGreen

-- | <<files/svg/Linen.png>>
instance StandardColor SVG "linen" where color :: SVG "linen" -> Color cs e
color SVG "linen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
linen

-- | <<files/svg/Magenta.png>>
instance StandardColor SVG "magenta" where color :: SVG "magenta" -> Color cs e
color SVG "magenta"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
magenta

-- | <<files/svg/Maroon.png>>
instance StandardColor SVG "maroon" where color :: SVG "maroon" -> Color cs e
color SVG "maroon"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
maroon

-- | <<files/svg/MediumAquaMarine.png>>
instance StandardColor SVG "mediumaquamarine" where color :: SVG "mediumaquamarine" -> Color cs e
color SVG "mediumaquamarine"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumAquaMarine

-- | <<files/svg/MediumBlue.png>>
instance StandardColor SVG "mediumblue" where color :: SVG "mediumblue" -> Color cs e
color SVG "mediumblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumBlue

-- | <<files/svg/MediumOrchid.png>>
instance StandardColor SVG "mediumorchid" where color :: SVG "mediumorchid" -> Color cs e
color SVG "mediumorchid"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumOrchid

-- | <<files/svg/MediumPurple.png>>
instance StandardColor SVG "mediumpurple" where color :: SVG "mediumpurple" -> Color cs e
color SVG "mediumpurple"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumPurple

-- | <<files/svg/MediumSeaGreen.png>>
instance StandardColor SVG "mediumseagreen" where color :: SVG "mediumseagreen" -> Color cs e
color SVG "mediumseagreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumSeaGreen

-- | <<files/svg/MediumSlateBlue.png>>
instance StandardColor SVG "mediumslateblue" where color :: SVG "mediumslateblue" -> Color cs e
color SVG "mediumslateblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumSlateBlue

-- | <<files/svg/MediumSpringGreen.png>>
instance StandardColor SVG "mediumspringgreen" where color :: SVG "mediumspringgreen" -> Color cs e
color SVG "mediumspringgreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumSpringGreen

-- | <<files/svg/MediumTurquoise.png>>
instance StandardColor SVG "mediumturquoise" where color :: SVG "mediumturquoise" -> Color cs e
color SVG "mediumturquoise"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumTurquoise

-- | <<files/svg/MediumVioletRed.png>>
instance StandardColor SVG "mediumvioletred" where color :: SVG "mediumvioletred" -> Color cs e
color SVG "mediumvioletred"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mediumVioletRed

-- | <<files/svg/MidnightBlue.png>>
instance StandardColor SVG "midnightblue" where color :: SVG "midnightblue" -> Color cs e
color SVG "midnightblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
midnightBlue

-- | <<files/svg/MintCream.png>>
instance StandardColor SVG "mintcream" where color :: SVG "mintcream" -> Color cs e
color SVG "mintcream"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mintCream

-- | <<files/svg/MistyRose.png>>
instance StandardColor SVG "mistyrose" where color :: SVG "mistyrose" -> Color cs e
color SVG "mistyrose"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
mistyRose

-- | <<files/svg/Moccasin.png>>
instance StandardColor SVG "moccasin" where color :: SVG "moccasin" -> Color cs e
color SVG "moccasin"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
moccasin

-- | <<files/svg/NavajoWhite.png>>
instance StandardColor SVG "navajowhite" where color :: SVG "navajowhite" -> Color cs e
color SVG "navajowhite"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
navajoWhite

-- | <<files/svg/Navy.png>>
instance StandardColor SVG "navy" where color :: SVG "navy" -> Color cs e
color SVG "navy"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
navy

-- | <<files/svg/OldLace.png>>
instance StandardColor SVG "oldlace" where color :: SVG "oldlace" -> Color cs e
color SVG "oldlace"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
oldLace

-- | <<files/svg/Olive.png>>
instance StandardColor SVG "olive" where color :: SVG "olive" -> Color cs e
color SVG "olive"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
olive

-- | <<files/svg/OliveDrab.png>>
instance StandardColor SVG "olivedrab" where color :: SVG "olivedrab" -> Color cs e
color SVG "olivedrab"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
oliveDrab

-- | <<files/svg/Orange.png>>
instance StandardColor SVG "orange" where color :: SVG "orange" -> Color cs e
color SVG "orange"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
orange

-- | <<files/svg/OrangeRed.png>>
instance StandardColor SVG "orangered" where color :: SVG "orangered" -> Color cs e
color SVG "orangered"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
orangeRed

-- | <<files/svg/Orchid.png>>
instance StandardColor SVG "orchid" where color :: SVG "orchid" -> Color cs e
color SVG "orchid"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
orchid

-- | <<files/svg/PaleGoldenRod.png>>
instance StandardColor SVG "palegoldenrod" where color :: SVG "palegoldenrod" -> Color cs e
color SVG "palegoldenrod"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
paleGoldenRod

-- | <<files/svg/PaleGreen.png>>
instance StandardColor SVG "palegreen" where color :: SVG "palegreen" -> Color cs e
color SVG "palegreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
paleGreen

-- | <<files/svg/PaleTurquoise.png>>
instance StandardColor SVG "paleturquoise" where color :: SVG "paleturquoise" -> Color cs e
color SVG "paleturquoise"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
paleTurquoise

-- | <<files/svg/PaleVioletRed.png>>
instance StandardColor SVG "palevioletred" where color :: SVG "palevioletred" -> Color cs e
color SVG "palevioletred"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
paleVioletRed

-- | <<files/svg/PapayaWhip.png>>
instance StandardColor SVG "papayawhip" where color :: SVG "papayawhip" -> Color cs e
color SVG "papayawhip"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
papayaWhip

-- | <<files/svg/PeachPuff.png>>
instance StandardColor SVG "peachpuff" where color :: SVG "peachpuff" -> Color cs e
color SVG "peachpuff"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
peachPuff

-- | <<files/svg/Peru.png>>
instance StandardColor SVG "peru" where color :: SVG "peru" -> Color cs e
color SVG "peru"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
peru

-- | <<files/svg/Pink.png>>
instance StandardColor SVG "pink" where color :: SVG "pink" -> Color cs e
color SVG "pink"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
pink

-- | <<files/svg/Plum.png>>
instance StandardColor SVG "plum" where color :: SVG "plum" -> Color cs e
color SVG "plum"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
plum

-- | <<files/svg/PowderBlue.png>>
instance StandardColor SVG "powderblue" where color :: SVG "powderblue" -> Color cs e
color SVG "powderblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
powderBlue

-- | <<files/svg/Purple.png>>
instance StandardColor SVG "purple" where color :: SVG "purple" -> Color cs e
color SVG "purple"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
purple

-- | <<files/svg/Red.png>>
instance StandardColor SVG "red" where color :: SVG "red" -> Color cs e
color SVG "red"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
red

-- | <<files/svg/RosyBrown.png>>
instance StandardColor SVG "rosybrown" where color :: SVG "rosybrown" -> Color cs e
color SVG "rosybrown"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
rosyBrown

-- | <<files/svg/RoyalBlue.png>>
instance StandardColor SVG "royalblue" where color :: SVG "royalblue" -> Color cs e
color SVG "royalblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
royalBlue

-- | <<files/svg/SaddleBrown.png>>
instance StandardColor SVG "saddlebrown" where color :: SVG "saddlebrown" -> Color cs e
color SVG "saddlebrown"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
saddleBrown

-- | <<files/svg/Salmon.png>>
instance StandardColor SVG "salmon" where color :: SVG "salmon" -> Color cs e
color SVG "salmon"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
salmon

-- | <<files/svg/SandyBrown.png>>
instance StandardColor SVG "sandybrown" where color :: SVG "sandybrown" -> Color cs e
color SVG "sandybrown"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
sandyBrown

-- | <<files/svg/SeaGreen.png>>
instance StandardColor SVG "seagreen" where color :: SVG "seagreen" -> Color cs e
color SVG "seagreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
seaGreen

-- | <<files/svg/Seashell.png>>
instance StandardColor SVG "seashell" where color :: SVG "seashell" -> Color cs e
color SVG "seashell"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
seashell

-- | <<files/svg/Sienna.png>>
instance StandardColor SVG "sienna" where color :: SVG "sienna" -> Color cs e
color SVG "sienna"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
sienna

-- | <<files/svg/Silver.png>>
instance StandardColor SVG "silver" where color :: SVG "silver" -> Color cs e
color SVG "silver"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
silver

-- | <<files/svg/SkyBlue.png>>
instance StandardColor SVG "skyblue" where color :: SVG "skyblue" -> Color cs e
color SVG "skyblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
skyBlue

-- | <<files/svg/SlateBlue.png>>
instance StandardColor SVG "slateblue" where color :: SVG "slateblue" -> Color cs e
color SVG "slateblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
slateBlue

-- | <<files/svg/SlateGray.png>>
instance StandardColor SVG "slategray" where color :: SVG "slategray" -> Color cs e
color SVG "slategray"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
slateGray

-- | <<files/svg/SlateGrey.png>>
instance StandardColor SVG "slategrey" where color :: SVG "slategrey" -> Color cs e
color SVG "slategrey"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
slateGrey

-- | <<files/svg/Snow.png>>
instance StandardColor SVG "snow" where color :: SVG "snow" -> Color cs e
color SVG "snow"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
snow

-- | <<files/svg/SpringGreen.png>>
instance StandardColor SVG "springgreen" where color :: SVG "springgreen" -> Color cs e
color SVG "springgreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
springGreen

-- | <<files/svg/SteelBlue.png>>
instance StandardColor SVG "steelblue" where color :: SVG "steelblue" -> Color cs e
color SVG "steelblue"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
steelBlue

-- | <<files/svg/Tan.png>>
instance StandardColor SVG "tan" where color :: SVG "tan" -> Color cs e
color SVG "tan"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
tan

-- | <<files/svg/Teal.png>>
instance StandardColor SVG "teal" where color :: SVG "teal" -> Color cs e
color SVG "teal"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
teal

-- | <<files/svg/Thistle.png>>
instance StandardColor SVG "thistle" where color :: SVG "thistle" -> Color cs e
color SVG "thistle"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
thistle

-- | <<files/svg/Tomato.png>>
instance StandardColor SVG "tomato" where color :: SVG "tomato" -> Color cs e
color SVG "tomato"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
tomato

-- | <<files/svg/Turquoise.png>>
instance StandardColor SVG "turquoise" where color :: SVG "turquoise" -> Color cs e
color SVG "turquoise"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
turquoise

-- | <<files/svg/Violet.png>>
instance StandardColor SVG "violet" where color :: SVG "violet" -> Color cs e
color SVG "violet"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
violet

-- | <<files/svg/Wheat.png>>
instance StandardColor SVG "wheat" where color :: SVG "wheat" -> Color cs e
color SVG "wheat"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
wheat

-- | <<files/svg/White.png>>
instance StandardColor SVG "white" where color :: SVG "white" -> Color cs e
color SVG "white"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
white

-- | <<files/svg/WhiteSmoke.png>>
instance StandardColor SVG "whitesmoke" where color :: SVG "whitesmoke" -> Color cs e
color SVG "whitesmoke"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
whiteSmoke

-- | <<files/svg/Yellow.png>>
instance StandardColor SVG "yellow" where color :: SVG "yellow" -> Color cs e
color SVG "yellow"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
yellow

-- | <<files/svg/YellowGreen.png>>
instance StandardColor SVG "yellowgreen" where color :: SVG "yellowgreen" -> Color cs e
color SVG "yellowgreen"
_ = Color (SRGB 'NonLinear) Word8 -> Color cs e
forall k1 k2 cs' (i' :: k1) e' cs (i :: k2) e.
(ColorSpace cs' i' e', ColorSpace cs i e) =>
Color cs' e' -> Color cs e
convert Color (SRGB 'NonLinear) Word8
yellowGreen

-- | Defined in SVG1.1 as
--
-- @
-- aliceblue = rgb(240, 248, 255)
-- @
--
-- <<files/svg/AliceBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = aliceBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/AliceBlue.png" img
--
-- @since 0.3.3
aliceBlue :: Color (SRGB 'NonLinear) Word8
aliceBlue :: Color (SRGB 'NonLinear) Word8
aliceBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
240 Word8
248 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- antiquewhite = rgb(250, 235, 215)
-- @
--
-- <<files/svg/AntiqueWhite.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = antiqueWhite
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/AntiqueWhite.png" img
--
-- @since 0.3.3
antiqueWhite :: Color (SRGB 'NonLinear) Word8
antiqueWhite :: Color (SRGB 'NonLinear) Word8
antiqueWhite = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
250 Word8
235 Word8
215

-- | Defined in SVG1.1 as
--
-- @
-- aqua = rgb(0, 255, 255)
-- @
--
-- <<files/svg/Aqua.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = aqua
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Aqua.png" img
--
-- @since 0.3.3
aqua :: Color (SRGB 'NonLinear) Word8
aqua :: Color (SRGB 'NonLinear) Word8
aqua = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
255 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- aquamarine = rgb(127, 255, 212)
-- @
--
-- <<files/svg/AquaMarine.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = aquaMarine
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/AquaMarine.png" img
--
-- @since 0.3.3
aquaMarine :: Color (SRGB 'NonLinear) Word8
aquaMarine :: Color (SRGB 'NonLinear) Word8
aquaMarine = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
127 Word8
255 Word8
212

-- | Defined in SVG1.1 as
--
-- @
-- azure = rgb(240, 255, 255)
-- @
--
-- <<files/svg/Azure.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = azure
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Azure.png" img
--
-- @since 0.3.3
azure :: Color (SRGB 'NonLinear) Word8
azure :: Color (SRGB 'NonLinear) Word8
azure = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
240 Word8
255 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- beige = rgb(245, 245, 220)
-- @
--
-- <<files/svg/Beige.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = beige
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Beige.png" img
--
-- @since 0.3.3
beige :: Color (SRGB 'NonLinear) Word8
beige :: Color (SRGB 'NonLinear) Word8
beige = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
245 Word8
245 Word8
220

-- | Defined in SVG1.1 as
--
-- @
-- bisque = rgb(255, 228, 196)
-- @
--
-- <<files/svg/Bisque.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = bisque
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Bisque.png" img
--
-- @since 0.3.3
bisque :: Color (SRGB 'NonLinear) Word8
bisque :: Color (SRGB 'NonLinear) Word8
bisque = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
228 Word8
196

-- | Defined in SVG1.1 as
--
-- @
-- black = rgb(0, 0, 0)
-- @
--
-- <<files/svg/Black.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = black
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Black.png" img
--
-- @since 0.3.3
black :: Color (SRGB 'NonLinear) Word8
black :: Color (SRGB 'NonLinear) Word8
black = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
0 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- blanchedalmond = rgb(255, 235, 205)
-- @
--
-- <<files/svg/BlanchedAlmond.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = blanchedAlmond
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/BlanchedAlmond.png" img
--
-- @since 0.3.3
blanchedAlmond :: Color (SRGB 'NonLinear) Word8
blanchedAlmond :: Color (SRGB 'NonLinear) Word8
blanchedAlmond = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
235 Word8
205

-- | Defined in SVG1.1 as
--
-- @
-- blue = rgb(0, 0, 255)
-- @
--
-- <<files/svg/Blue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = blue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Blue.png" img
--
-- @since 0.3.3
blue :: Color (SRGB 'NonLinear) Word8
blue :: Color (SRGB 'NonLinear) Word8
blue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
0 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- blueviolet = rgb(138, 43, 226)
-- @
--
-- <<files/svg/BlueViolet.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = blueViolet
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/BlueViolet.png" img
--
-- @since 0.3.3
blueViolet :: Color (SRGB 'NonLinear) Word8
blueViolet :: Color (SRGB 'NonLinear) Word8
blueViolet = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
138 Word8
43 Word8
226

-- | Defined in SVG1.1 as
--
-- @
-- brown = rgb(165, 42, 42)
-- @
--
-- <<files/svg/Brown.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = brown
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Brown.png" img
--
-- @since 0.3.3
brown :: Color (SRGB 'NonLinear) Word8
brown :: Color (SRGB 'NonLinear) Word8
brown = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
165 Word8
42 Word8
42

-- | Defined in SVG1.1 as
--
-- @
-- burlywood = rgb(222, 184, 135)
-- @
--
-- <<files/svg/BurlyWood.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = burlyWood
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/BurlyWood.png" img
--
-- @since 0.3.3
burlyWood :: Color (SRGB 'NonLinear) Word8
burlyWood :: Color (SRGB 'NonLinear) Word8
burlyWood = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
222 Word8
184 Word8
135

-- | Defined in SVG1.1 as
--
-- @
-- cadetblue = rgb(95, 158, 160)
-- @
--
-- <<files/svg/CadetBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = cadetBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/CadetBlue.png" img
--
-- @since 0.3.3
cadetBlue :: Color (SRGB 'NonLinear) Word8
cadetBlue :: Color (SRGB 'NonLinear) Word8
cadetBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
95 Word8
158 Word8
160

-- | Defined in SVG1.1 as
--
-- @
-- chartreuse = rgb(127, 255, 0)
-- @
--
-- <<files/svg/Chartreuse.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = chartreuse
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Chartreuse.png" img
--
-- @since 0.3.3
chartreuse :: Color (SRGB 'NonLinear) Word8
chartreuse :: Color (SRGB 'NonLinear) Word8
chartreuse = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
127 Word8
255 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- chocolate = rgb(210, 105, 30)
-- @
--
-- <<files/svg/Chocolate.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = chocolate
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Chocolate.png" img
--
-- @since 0.3.3
chocolate :: Color (SRGB 'NonLinear) Word8
chocolate :: Color (SRGB 'NonLinear) Word8
chocolate = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
210 Word8
105 Word8
30

-- | Defined in SVG1.1 as
--
-- @
-- coral = rgb(255, 127, 80)
-- @
--
-- <<files/svg/Coral.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = coral
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Coral.png" img
--
-- @since 0.3.3
coral :: Color (SRGB 'NonLinear) Word8
coral :: Color (SRGB 'NonLinear) Word8
coral = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
127 Word8
80

-- | Defined in SVG1.1 as
--
-- @
-- cornflowerblue = rgb(100, 149, 237)
-- @
--
-- <<files/svg/CornFlowerBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = cornFlowerBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/CornFlowerBlue.png" img
--
-- @since 0.3.3
cornFlowerBlue :: Color (SRGB 'NonLinear) Word8
cornFlowerBlue :: Color (SRGB 'NonLinear) Word8
cornFlowerBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
100 Word8
149 Word8
237

-- | Defined in SVG1.1 as
--
-- @
-- cornsilk = rgb(255, 248, 220)
-- @
--
-- <<files/svg/CornSilk.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = cornSilk
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/CornSilk.png" img
--
-- @since 0.3.3
cornSilk :: Color (SRGB 'NonLinear) Word8
cornSilk :: Color (SRGB 'NonLinear) Word8
cornSilk = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
248 Word8
220

-- | Defined in SVG1.1 as
--
-- @
-- crimson = rgb(220, 20, 60)
-- @
--
-- <<files/svg/Crimson.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = crimson
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Crimson.png" img
--
-- @since 0.3.3
crimson :: Color (SRGB 'NonLinear) Word8
crimson :: Color (SRGB 'NonLinear) Word8
crimson = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
220 Word8
20 Word8
60

-- | Defined in SVG1.1 as
--
-- @
-- cyan = rgb(0, 255, 255)
-- @
--
-- <<files/svg/Cyan.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = cyan
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Cyan.png" img
--
-- @since 0.3.3
cyan :: Color (SRGB 'NonLinear) Word8
cyan :: Color (SRGB 'NonLinear) Word8
cyan = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
255 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- darkblue = rgb(0, 0, 139)
-- @
--
-- <<files/svg/DarkBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkBlue.png" img
--
-- @since 0.3.3
darkBlue :: Color (SRGB 'NonLinear) Word8
darkBlue :: Color (SRGB 'NonLinear) Word8
darkBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
0 Word8
139

-- | Defined in SVG1.1 as
--
-- @
-- darkcyan = rgb(0, 139, 139)
-- @
--
-- <<files/svg/DarkCyan.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkCyan
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkCyan.png" img
--
-- @since 0.3.3
darkCyan :: Color (SRGB 'NonLinear) Word8
darkCyan :: Color (SRGB 'NonLinear) Word8
darkCyan = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
139 Word8
139

-- | Defined in SVG1.1 as
--
-- @
-- darkgoldenrod = rgb(184, 134, 11)
-- @
--
-- <<files/svg/DarkGoldenRod.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkGoldenRod
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkGoldenRod.png" img
--
-- @since 0.3.3
darkGoldenRod :: Color (SRGB 'NonLinear) Word8
darkGoldenRod :: Color (SRGB 'NonLinear) Word8
darkGoldenRod = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
184 Word8
134 Word8
11

-- | Defined in SVG1.1 as
--
-- @
-- darkgray = rgb(169, 169, 169)
-- @
--
-- <<files/svg/DarkGray.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkGray
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkGray.png" img
--
-- @since 0.3.3
darkGray :: Color (SRGB 'NonLinear) Word8
darkGray :: Color (SRGB 'NonLinear) Word8
darkGray = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
169 Word8
169 Word8
169

-- | Defined in SVG1.1 as
--
-- @
-- darkgreen = rgb(0, 100, 0)
-- @
--
-- <<files/svg/DarkGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkGreen.png" img
--
-- @since 0.3.3
darkGreen :: Color (SRGB 'NonLinear) Word8
darkGreen :: Color (SRGB 'NonLinear) Word8
darkGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
100 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- darkgrey = rgb(169, 169, 169)
-- @
--
-- <<files/svg/DarkGrey.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkGrey
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkGrey.png" img
--
-- @since 0.3.3
darkGrey :: Color (SRGB 'NonLinear) Word8
darkGrey :: Color (SRGB 'NonLinear) Word8
darkGrey = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
169 Word8
169 Word8
169

-- | Defined in SVG1.1 as
--
-- @
-- darkkhaki = rgb(189, 183, 107)
-- @
--
-- <<files/svg/DarkKhaki.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkKhaki
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkKhaki.png" img
--
-- @since 0.3.3
darkKhaki :: Color (SRGB 'NonLinear) Word8
darkKhaki :: Color (SRGB 'NonLinear) Word8
darkKhaki = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
189 Word8
183 Word8
107

-- | Defined in SVG1.1 as
--
-- @
-- darkmagenta = rgb(139, 0, 139)
-- @
--
-- <<files/svg/DarkMagenta.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkMagenta
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkMagenta.png" img
--
-- @since 0.3.3
darkMagenta :: Color (SRGB 'NonLinear) Word8
darkMagenta :: Color (SRGB 'NonLinear) Word8
darkMagenta = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
139 Word8
0 Word8
139

-- | Defined in SVG1.1 as
--
-- @
-- darkolivegreen = rgb(85, 107, 47)
-- @
--
-- <<files/svg/DarkOliveGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkOliveGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkOliveGreen.png" img
--
-- @since 0.3.3
darkOliveGreen :: Color (SRGB 'NonLinear) Word8
darkOliveGreen :: Color (SRGB 'NonLinear) Word8
darkOliveGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
85 Word8
107 Word8
47

-- | Defined in SVG1.1 as
--
-- @
-- darkorange = rgb(255, 140, 0)
-- @
--
-- <<files/svg/DarkOrange.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkOrange
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkOrange.png" img
--
-- @since 0.3.3
darkOrange :: Color (SRGB 'NonLinear) Word8
darkOrange :: Color (SRGB 'NonLinear) Word8
darkOrange = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
140 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- darkorchid = rgb(153, 50, 204)
-- @
--
-- <<files/svg/DarkOrchid.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkOrchid
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkOrchid.png" img
--
-- @since 0.3.3
darkOrchid :: Color (SRGB 'NonLinear) Word8
darkOrchid :: Color (SRGB 'NonLinear) Word8
darkOrchid = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
153 Word8
50 Word8
204

-- | Defined in SVG1.1 as
--
-- @
-- darkred = rgb(139, 0, 0)
-- @
--
-- <<files/svg/DarkRed.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkRed
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkRed.png" img
--
-- @since 0.3.3
darkRed :: Color (SRGB 'NonLinear) Word8
darkRed :: Color (SRGB 'NonLinear) Word8
darkRed = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
139 Word8
0 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- darksalmon = rgb(233, 150, 122)
-- @
--
-- <<files/svg/DarkSalmon.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkSalmon
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkSalmon.png" img
--
-- @since 0.3.3
darkSalmon :: Color (SRGB 'NonLinear) Word8
darkSalmon :: Color (SRGB 'NonLinear) Word8
darkSalmon = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
233 Word8
150 Word8
122

-- | Defined in SVG1.1 as
--
-- @
-- darkseagreen = rgb(143, 188, 143)
-- @
--
-- <<files/svg/DarkSeaGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkSeaGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkSeaGreen.png" img
--
-- @since 0.3.3
darkSeaGreen :: Color (SRGB 'NonLinear) Word8
darkSeaGreen :: Color (SRGB 'NonLinear) Word8
darkSeaGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
143 Word8
188 Word8
143

-- | Defined in SVG1.1 as
--
-- @
-- darkslateblue = rgb(72, 61, 139)
-- @
--
-- <<files/svg/DarkSlateBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkSlateBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkSlateBlue.png" img
--
-- @since 0.3.3
darkSlateBlue :: Color (SRGB 'NonLinear) Word8
darkSlateBlue :: Color (SRGB 'NonLinear) Word8
darkSlateBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
72 Word8
61 Word8
139

-- | Defined in SVG1.1 as
--
-- @
-- darkslategray = rgb(47, 79, 79)
-- @
--
-- <<files/svg/DarkSlateGray.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkSlateGray
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkSlateGray.png" img
--
-- @since 0.3.3
darkSlateGray :: Color (SRGB 'NonLinear) Word8
darkSlateGray :: Color (SRGB 'NonLinear) Word8
darkSlateGray = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
47 Word8
79 Word8
79

-- | Defined in SVG1.1 as
--
-- @
-- darkslategrey = rgb(47, 79, 79)
-- @
--
-- <<files/svg/DarkSlateGrey.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkSlateGrey
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkSlateGrey.png" img
--
-- @since 0.3.3
darkSlateGrey :: Color (SRGB 'NonLinear) Word8
darkSlateGrey :: Color (SRGB 'NonLinear) Word8
darkSlateGrey = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
47 Word8
79 Word8
79

-- | Defined in SVG1.1 as
--
-- @
-- darkturquoise = rgb(0, 206, 209)
-- @
--
-- <<files/svg/DarkTurquoise.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkTurquoise
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkTurquoise.png" img
--
-- @since 0.3.3
darkTurquoise :: Color (SRGB 'NonLinear) Word8
darkTurquoise :: Color (SRGB 'NonLinear) Word8
darkTurquoise = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
206 Word8
209

-- | Defined in SVG1.1 as
--
-- @
-- darkviolet = rgb(148, 0, 211)
-- @
--
-- <<files/svg/DarkViolet.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = darkViolet
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DarkViolet.png" img
--
-- @since 0.3.3
darkViolet :: Color (SRGB 'NonLinear) Word8
darkViolet :: Color (SRGB 'NonLinear) Word8
darkViolet = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
148 Word8
0 Word8
211

-- | Defined in SVG1.1 as
--
-- @
-- deeppink = rgb(255, 20, 147)
-- @
--
-- <<files/svg/DeepPink.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = deepPink
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DeepPink.png" img
--
-- @since 0.3.3
deepPink :: Color (SRGB 'NonLinear) Word8
deepPink :: Color (SRGB 'NonLinear) Word8
deepPink = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
20 Word8
147

-- | Defined in SVG1.1 as
--
-- @
-- deepskyblue = rgb(0, 191, 255)
-- @
--
-- <<files/svg/DeepSkyBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = deepSkyBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DeepSkyBlue.png" img
--
-- @since 0.3.3
deepSkyBlue :: Color (SRGB 'NonLinear) Word8
deepSkyBlue :: Color (SRGB 'NonLinear) Word8
deepSkyBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
191 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- dimgray = rgb(105, 105, 105)
-- @
--
-- <<files/svg/DimGray.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = dimGray
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DimGray.png" img
--
-- @since 0.3.3
dimGray :: Color (SRGB 'NonLinear) Word8
dimGray :: Color (SRGB 'NonLinear) Word8
dimGray = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
105 Word8
105 Word8
105

-- | Defined in SVG1.1 as
--
-- @
-- dimgrey = rgb(105, 105, 105)
-- @
--
-- <<files/svg/DimGrey.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = dimGrey
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DimGrey.png" img
--
-- @since 0.3.3
dimGrey :: Color (SRGB 'NonLinear) Word8
dimGrey :: Color (SRGB 'NonLinear) Word8
dimGrey = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
105 Word8
105 Word8
105

-- | Defined in SVG1.1 as
--
-- @
-- dodgerblue = rgb(30, 144, 255)
-- @
--
-- <<files/svg/DodgerBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = dodgerBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/DodgerBlue.png" img
--
-- @since 0.3.3
dodgerBlue :: Color (SRGB 'NonLinear) Word8
dodgerBlue :: Color (SRGB 'NonLinear) Word8
dodgerBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
30 Word8
144 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- firebrick = rgb(178, 34, 34)
-- @
--
-- <<files/svg/FireBrick.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = fireBrick
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/FireBrick.png" img
--
-- @since 0.3.3
fireBrick :: Color (SRGB 'NonLinear) Word8
fireBrick :: Color (SRGB 'NonLinear) Word8
fireBrick = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
178 Word8
34 Word8
34

-- | Defined in SVG1.1 as
--
-- @
-- floralwhite = rgb(255, 250, 240)
-- @
--
-- <<files/svg/FloralWhite.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = floralWhite
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/FloralWhite.png" img
--
-- @since 0.3.3
floralWhite :: Color (SRGB 'NonLinear) Word8
floralWhite :: Color (SRGB 'NonLinear) Word8
floralWhite = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
250 Word8
240

-- | Defined in SVG1.1 as
--
-- @
-- forestgreen = rgb(34, 139, 34)
-- @
--
-- <<files/svg/ForestGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = forestGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/ForestGreen.png" img
--
-- @since 0.3.3
forestGreen :: Color (SRGB 'NonLinear) Word8
forestGreen :: Color (SRGB 'NonLinear) Word8
forestGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
34 Word8
139 Word8
34

-- | Defined in SVG1.1 as
--
-- @
-- fuchsia = rgb(255, 0, 255)
-- @
--
-- <<files/svg/Fuchsia.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = fuchsia
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Fuchsia.png" img
--
-- @since 0.3.3
fuchsia :: Color (SRGB 'NonLinear) Word8
fuchsia :: Color (SRGB 'NonLinear) Word8
fuchsia = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
0 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- gainsboro = rgb(220, 220, 220)
-- @
--
-- <<files/svg/Gainsboro.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = gainsboro
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Gainsboro.png" img
--
-- @since 0.3.3
gainsboro :: Color (SRGB 'NonLinear) Word8
gainsboro :: Color (SRGB 'NonLinear) Word8
gainsboro = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
220 Word8
220 Word8
220

-- | Defined in SVG1.1 as
--
-- @
-- ghostwhite = rgb(248, 248, 255)
-- @
--
-- <<files/svg/GhostWhite.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = ghostWhite
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/GhostWhite.png" img
--
-- @since 0.3.3
ghostWhite :: Color (SRGB 'NonLinear) Word8
ghostWhite :: Color (SRGB 'NonLinear) Word8
ghostWhite = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
248 Word8
248 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- gold = rgb(255, 215, 0)
-- @
--
-- <<files/svg/Gold.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = gold
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Gold.png" img
--
-- @since 0.3.3
gold :: Color (SRGB 'NonLinear) Word8
gold :: Color (SRGB 'NonLinear) Word8
gold = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
215 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- goldenrod = rgb(218, 165, 32)
-- @
--
-- <<files/svg/GoldenRod.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = goldenRod
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/GoldenRod.png" img
--
-- @since 0.3.3
goldenRod :: Color (SRGB 'NonLinear) Word8
goldenRod :: Color (SRGB 'NonLinear) Word8
goldenRod = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
218 Word8
165 Word8
32

-- | Defined in SVG1.1 as
--
-- @
-- gray = rgb(128, 128, 128)
-- @
--
-- <<files/svg/Gray.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = gray
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Gray.png" img
--
-- @since 0.3.3
gray :: Color (SRGB 'NonLinear) Word8
gray :: Color (SRGB 'NonLinear) Word8
gray = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
128 Word8
128 Word8
128

-- | Defined in SVG1.1 as
--
-- @
-- grey = rgb(128, 128, 128)
-- @
--
-- <<files/svg/Grey.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = grey
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Grey.png" img
--
-- @since 0.3.3
grey :: Color (SRGB 'NonLinear) Word8
grey :: Color (SRGB 'NonLinear) Word8
grey = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
128 Word8
128 Word8
128

-- | Defined in SVG1.1 as
--
-- @
-- green = rgb(0, 128, 0)
-- @
--
-- <<files/svg/Green.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = green
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Green.png" img
--
-- @since 0.3.3
green :: Color (SRGB 'NonLinear) Word8
green :: Color (SRGB 'NonLinear) Word8
green = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
128 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- greenyellow = rgb(173, 255, 47)
-- @
--
-- <<files/svg/GreenYellow.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = greenYellow
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/GreenYellow.png" img
--
-- @since 0.3.3
greenYellow :: Color (SRGB 'NonLinear) Word8
greenYellow :: Color (SRGB 'NonLinear) Word8
greenYellow = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
173 Word8
255 Word8
47

-- | Defined in SVG1.1 as
--
-- @
-- honeydew = rgb(240, 255, 240)
-- @
--
-- <<files/svg/Honeydew.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = honeydew
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Honeydew.png" img
--
-- @since 0.3.3
honeydew :: Color (SRGB 'NonLinear) Word8
honeydew :: Color (SRGB 'NonLinear) Word8
honeydew = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
240 Word8
255 Word8
240

-- | Defined in SVG1.1 as
--
-- @
-- hotpink = rgb(255, 105, 180)
-- @
--
-- <<files/svg/HotPink.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = hotPink
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/HotPink.png" img
--
-- @since 0.3.3
hotPink :: Color (SRGB 'NonLinear) Word8
hotPink :: Color (SRGB 'NonLinear) Word8
hotPink = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
105 Word8
180

-- | Defined in SVG1.1 as
--
-- @
-- indianred = rgb(205, 92, 92)
-- @
--
-- <<files/svg/IndianRed.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = indianRed
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/IndianRed.png" img
--
-- @since 0.3.3
indianRed :: Color (SRGB 'NonLinear) Word8
indianRed :: Color (SRGB 'NonLinear) Word8
indianRed = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
205 Word8
92 Word8
92

-- | Defined in SVG1.1 as
--
-- @
-- indigo = rgb(75, 0, 130)
-- @
--
-- <<files/svg/Indigo.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = indigo
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Indigo.png" img
--
-- @since 0.3.3
indigo :: Color (SRGB 'NonLinear) Word8
indigo :: Color (SRGB 'NonLinear) Word8
indigo = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
75 Word8
0 Word8
130

-- | Defined in SVG1.1 as
--
-- @
-- ivory = rgb(255, 255, 240)
-- @
--
-- <<files/svg/Ivory.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = ivory
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Ivory.png" img
--
-- @since 0.3.3
ivory :: Color (SRGB 'NonLinear) Word8
ivory :: Color (SRGB 'NonLinear) Word8
ivory = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
255 Word8
240

-- | Defined in SVG1.1 as
--
-- @
-- khaki = rgb(240, 230, 140)
-- @
--
-- <<files/svg/Khaki.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = khaki
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Khaki.png" img
--
-- @since 0.3.3
khaki :: Color (SRGB 'NonLinear) Word8
khaki :: Color (SRGB 'NonLinear) Word8
khaki = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
240 Word8
230 Word8
140

-- | Defined in SVG1.1 as
--
-- @
-- lavender = rgb(230, 230, 250)
-- @
--
-- <<files/svg/Lavender.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lavender
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Lavender.png" img
--
-- @since 0.3.3
lavender :: Color (SRGB 'NonLinear) Word8
lavender :: Color (SRGB 'NonLinear) Word8
lavender = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
230 Word8
230 Word8
250

-- | Defined in SVG1.1 as
--
-- @
-- lavenderblush = rgb(255, 240, 245)
-- @
--
-- <<files/svg/LavenderBlush.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lavenderBlush
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LavenderBlush.png" img
--
-- @since 0.3.3
lavenderBlush :: Color (SRGB 'NonLinear) Word8
lavenderBlush :: Color (SRGB 'NonLinear) Word8
lavenderBlush = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
240 Word8
245

-- | Defined in SVG1.1 as
--
-- @
-- lawngreen = rgb(124, 252, 0)
-- @
--
-- <<files/svg/LawnGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lawnGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LawnGreen.png" img
--
-- @since 0.3.3
lawnGreen :: Color (SRGB 'NonLinear) Word8
lawnGreen :: Color (SRGB 'NonLinear) Word8
lawnGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
124 Word8
252 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- lemonchiffon = rgb(255, 250, 205)
-- @
--
-- <<files/svg/LemonChiffon.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lemonChiffon
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LemonChiffon.png" img
--
-- @since 0.3.3
lemonChiffon :: Color (SRGB 'NonLinear) Word8
lemonChiffon :: Color (SRGB 'NonLinear) Word8
lemonChiffon = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
250 Word8
205

-- | Defined in SVG1.1 as
--
-- @
-- lightblue = rgb(173, 216, 230)
-- @
--
-- <<files/svg/LightBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightBlue.png" img
--
-- @since 0.3.3
lightBlue :: Color (SRGB 'NonLinear) Word8
lightBlue :: Color (SRGB 'NonLinear) Word8
lightBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
173 Word8
216 Word8
230

-- | Defined in SVG1.1 as
--
-- @
-- lightcoral = rgb(240, 128, 128)
-- @
--
-- <<files/svg/LightCoral.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightCoral
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightCoral.png" img
--
-- @since 0.3.3
lightCoral :: Color (SRGB 'NonLinear) Word8
lightCoral :: Color (SRGB 'NonLinear) Word8
lightCoral = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
240 Word8
128 Word8
128

-- | Defined in SVG1.1 as
--
-- @
-- lightcyan = rgb(224, 255, 255)
-- @
--
-- <<files/svg/LightCyan.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightCyan
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightCyan.png" img
--
-- @since 0.3.3
lightCyan :: Color (SRGB 'NonLinear) Word8
lightCyan :: Color (SRGB 'NonLinear) Word8
lightCyan = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
224 Word8
255 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- lightgoldenrodyellow = rgb(250, 250, 210)
-- @
--
-- <<files/svg/LightGoldenRodYellow.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightGoldenRodYellow
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightGoldenRodYellow.png" img
--
-- @since 0.3.3
lightGoldenRodYellow :: Color (SRGB 'NonLinear) Word8
lightGoldenRodYellow :: Color (SRGB 'NonLinear) Word8
lightGoldenRodYellow = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
250 Word8
250 Word8
210

-- | Defined in SVG1.1 as
--
-- @
-- lightgray = rgb(211, 211, 211)
-- @
--
-- <<files/svg/LightGray.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightGray
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightGray.png" img
--
-- @since 0.3.3
lightGray :: Color (SRGB 'NonLinear) Word8
lightGray :: Color (SRGB 'NonLinear) Word8
lightGray = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
211 Word8
211 Word8
211

-- | Defined in SVG1.1 as
--
-- @
-- lightgreen = rgb(144, 238, 144)
-- @
--
-- <<files/svg/LightGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightGreen.png" img
--
-- @since 0.3.3
lightGreen :: Color (SRGB 'NonLinear) Word8
lightGreen :: Color (SRGB 'NonLinear) Word8
lightGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
144 Word8
238 Word8
144

-- | Defined in SVG1.1 as
--
-- @
-- lightgrey = rgb(211, 211, 211)
-- @
--
-- <<files/svg/LightGrey.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightGrey
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightGrey.png" img
--
-- @since 0.3.3
lightGrey :: Color (SRGB 'NonLinear) Word8
lightGrey :: Color (SRGB 'NonLinear) Word8
lightGrey = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
211 Word8
211 Word8
211

-- | Defined in SVG1.1 as
--
-- @
-- lightpink = rgb(255, 182, 193)
-- @
--
-- <<files/svg/LightPink.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightPink
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightPink.png" img
--
-- @since 0.3.3
lightPink :: Color (SRGB 'NonLinear) Word8
lightPink :: Color (SRGB 'NonLinear) Word8
lightPink = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
182 Word8
193

-- | Defined in SVG1.1 as
--
-- @
-- lightsalmon = rgb(255, 160, 122)
-- @
--
-- <<files/svg/LightSalmon.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightSalmon
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightSalmon.png" img
--
-- @since 0.3.3
lightSalmon :: Color (SRGB 'NonLinear) Word8
lightSalmon :: Color (SRGB 'NonLinear) Word8
lightSalmon = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
160 Word8
122

-- | Defined in SVG1.1 as
--
-- @
-- lightseagreen = rgb(32, 178, 170)
-- @
--
-- <<files/svg/LightSeaGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightSeaGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightSeaGreen.png" img
--
-- @since 0.3.3
lightSeaGreen :: Color (SRGB 'NonLinear) Word8
lightSeaGreen :: Color (SRGB 'NonLinear) Word8
lightSeaGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
32 Word8
178 Word8
170

-- | Defined in SVG1.1 as
--
-- @
-- lightskyblue = rgb(135, 206, 250)
-- @
--
-- <<files/svg/LightSkyBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightSkyBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightSkyBlue.png" img
--
-- @since 0.3.3
lightSkyBlue :: Color (SRGB 'NonLinear) Word8
lightSkyBlue :: Color (SRGB 'NonLinear) Word8
lightSkyBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
135 Word8
206 Word8
250

-- | Defined in SVG1.1 as
--
-- @
-- lightslategray = rgb(119, 136, 153)
-- @
--
-- <<files/svg/LightSlateGray.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightSlateGray
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightSlateGray.png" img
--
-- @since 0.3.3
lightSlateGray :: Color (SRGB 'NonLinear) Word8
lightSlateGray :: Color (SRGB 'NonLinear) Word8
lightSlateGray = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
119 Word8
136 Word8
153

-- | Defined in SVG1.1 as
--
-- @
-- lightslategrey = rgb(119, 136, 153)
-- @
--
-- <<files/svg/LightSlateGrey.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightSlateGrey
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightSlateGrey.png" img
--
-- @since 0.3.3
lightSlateGrey :: Color (SRGB 'NonLinear) Word8
lightSlateGrey :: Color (SRGB 'NonLinear) Word8
lightSlateGrey = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
119 Word8
136 Word8
153

-- | Defined in SVG1.1 as
--
-- @
-- lightsteelblue = rgb(176, 196, 222)
-- @
--
-- <<files/svg/LightSteelBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightSteelBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightSteelBlue.png" img
--
-- @since 0.3.3
lightSteelBlue :: Color (SRGB 'NonLinear) Word8
lightSteelBlue :: Color (SRGB 'NonLinear) Word8
lightSteelBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
176 Word8
196 Word8
222

-- | Defined in SVG1.1 as
--
-- @
-- lightyellow = rgb(255, 255, 224)
-- @
--
-- <<files/svg/LightYellow.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lightYellow
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LightYellow.png" img
--
-- @since 0.3.3
lightYellow :: Color (SRGB 'NonLinear) Word8
lightYellow :: Color (SRGB 'NonLinear) Word8
lightYellow = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
255 Word8
224

-- | Defined in SVG1.1 as
--
-- @
-- lime = rgb(0, 255, 0)
-- @
--
-- <<files/svg/Lime.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = lime
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Lime.png" img
--
-- @since 0.3.3
lime :: Color (SRGB 'NonLinear) Word8
lime :: Color (SRGB 'NonLinear) Word8
lime = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
255 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- limegreen = rgb(50, 205, 50)
-- @
--
-- <<files/svg/LimeGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = limeGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/LimeGreen.png" img
--
-- @since 0.3.3
limeGreen :: Color (SRGB 'NonLinear) Word8
limeGreen :: Color (SRGB 'NonLinear) Word8
limeGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
50 Word8
205 Word8
50

-- | Defined in SVG1.1 as
--
-- @
-- linen = rgb(250, 240, 230)
-- @
--
-- <<files/svg/Linen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = linen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Linen.png" img
--
-- @since 0.3.3
linen :: Color (SRGB 'NonLinear) Word8
linen :: Color (SRGB 'NonLinear) Word8
linen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
250 Word8
240 Word8
230

-- | Defined in SVG1.1 as
--
-- @
-- magenta = rgb(255, 0, 255)
-- @
--
-- <<files/svg/Magenta.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = magenta
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Magenta.png" img
--
-- @since 0.3.3
magenta :: Color (SRGB 'NonLinear) Word8
magenta :: Color (SRGB 'NonLinear) Word8
magenta = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
0 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- maroon = rgb(128, 0, 0)
-- @
--
-- <<files/svg/Maroon.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = maroon
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Maroon.png" img
--
-- @since 0.3.3
maroon :: Color (SRGB 'NonLinear) Word8
maroon :: Color (SRGB 'NonLinear) Word8
maroon = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
128 Word8
0 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- mediumaquamarine = rgb(102, 205, 170)
-- @
--
-- <<files/svg/MediumAquaMarine.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumAquaMarine
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumAquaMarine.png" img
--
-- @since 0.3.3
mediumAquaMarine :: Color (SRGB 'NonLinear) Word8
mediumAquaMarine :: Color (SRGB 'NonLinear) Word8
mediumAquaMarine = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
102 Word8
205 Word8
170

-- | Defined in SVG1.1 as
--
-- @
-- mediumblue = rgb(0, 0, 205)
-- @
--
-- <<files/svg/MediumBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumBlue.png" img
--
-- @since 0.3.3
mediumBlue :: Color (SRGB 'NonLinear) Word8
mediumBlue :: Color (SRGB 'NonLinear) Word8
mediumBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
0 Word8
205

-- | Defined in SVG1.1 as
--
-- @
-- mediumorchid = rgb(186, 85, 211)
-- @
--
-- <<files/svg/MediumOrchid.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumOrchid
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumOrchid.png" img
--
-- @since 0.3.3
mediumOrchid :: Color (SRGB 'NonLinear) Word8
mediumOrchid :: Color (SRGB 'NonLinear) Word8
mediumOrchid = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
186 Word8
85 Word8
211

-- | Defined in SVG1.1 as
--
-- @
-- mediumpurple = rgb(147, 112, 219)
-- @
--
-- <<files/svg/MediumPurple.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumPurple
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumPurple.png" img
--
-- @since 0.3.3
mediumPurple :: Color (SRGB 'NonLinear) Word8
mediumPurple :: Color (SRGB 'NonLinear) Word8
mediumPurple = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
147 Word8
112 Word8
219

-- | Defined in SVG1.1 as
--
-- @
-- mediumseagreen = rgb(60, 179, 113)
-- @
--
-- <<files/svg/MediumSeaGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumSeaGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumSeaGreen.png" img
--
-- @since 0.3.3
mediumSeaGreen :: Color (SRGB 'NonLinear) Word8
mediumSeaGreen :: Color (SRGB 'NonLinear) Word8
mediumSeaGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
60 Word8
179 Word8
113

-- | Defined in SVG1.1 as
--
-- @
-- mediumslateblue = rgb(123, 104, 238)
-- @
--
-- <<files/svg/MediumSlateBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumSlateBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumSlateBlue.png" img
--
-- @since 0.3.3
mediumSlateBlue :: Color (SRGB 'NonLinear) Word8
mediumSlateBlue :: Color (SRGB 'NonLinear) Word8
mediumSlateBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
123 Word8
104 Word8
238

-- | Defined in SVG1.1 as
--
-- @
-- mediumspringgreen = rgb(0, 250, 154)
-- @
--
-- <<files/svg/MediumSpringGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumSpringGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumSpringGreen.png" img
--
-- @since 0.3.3
mediumSpringGreen :: Color (SRGB 'NonLinear) Word8
mediumSpringGreen :: Color (SRGB 'NonLinear) Word8
mediumSpringGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
250 Word8
154

-- | Defined in SVG1.1 as
--
-- @
-- mediumturquoise = rgb(72, 209, 204)
-- @
--
-- <<files/svg/MediumTurquoise.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumTurquoise
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumTurquoise.png" img
--
-- @since 0.3.3
mediumTurquoise :: Color (SRGB 'NonLinear) Word8
mediumTurquoise :: Color (SRGB 'NonLinear) Word8
mediumTurquoise = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
72 Word8
209 Word8
204

-- | Defined in SVG1.1 as
--
-- @
-- mediumvioletred = rgb(199, 21, 133)
-- @
--
-- <<files/svg/MediumVioletRed.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mediumVioletRed
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MediumVioletRed.png" img
--
-- @since 0.3.3
mediumVioletRed :: Color (SRGB 'NonLinear) Word8
mediumVioletRed :: Color (SRGB 'NonLinear) Word8
mediumVioletRed = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
199 Word8
21 Word8
133

-- | Defined in SVG1.1 as
--
-- @
-- midnightblue = rgb(25, 25, 112)
-- @
--
-- <<files/svg/MidnightBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = midnightBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MidnightBlue.png" img
--
-- @since 0.3.3
midnightBlue :: Color (SRGB 'NonLinear) Word8
midnightBlue :: Color (SRGB 'NonLinear) Word8
midnightBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
25 Word8
25 Word8
112

-- | Defined in SVG1.1 as
--
-- @
-- mintcream = rgb(245, 255, 250)
-- @
--
-- <<files/svg/MintCream.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mintCream
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MintCream.png" img
--
-- @since 0.3.3
mintCream :: Color (SRGB 'NonLinear) Word8
mintCream :: Color (SRGB 'NonLinear) Word8
mintCream = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
245 Word8
255 Word8
250

-- | Defined in SVG1.1 as
--
-- @
-- mistyrose = rgb(255, 228, 225)
-- @
--
-- <<files/svg/MistyRose.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = mistyRose
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/MistyRose.png" img
--
-- @since 0.3.3
mistyRose :: Color (SRGB 'NonLinear) Word8
mistyRose :: Color (SRGB 'NonLinear) Word8
mistyRose = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
228 Word8
225

-- | Defined in SVG1.1 as
--
-- @
-- moccasin = rgb(255, 228, 181)
-- @
--
-- <<files/svg/Moccasin.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = moccasin
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Moccasin.png" img
--
-- @since 0.3.3
moccasin :: Color (SRGB 'NonLinear) Word8
moccasin :: Color (SRGB 'NonLinear) Word8
moccasin = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
228 Word8
181

-- | Defined in SVG1.1 as
--
-- @
-- navajowhite = rgb(255, 222, 173)
-- @
--
-- <<files/svg/NavajoWhite.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = navajoWhite
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/NavajoWhite.png" img
--
-- @since 0.3.3
navajoWhite :: Color (SRGB 'NonLinear) Word8
navajoWhite :: Color (SRGB 'NonLinear) Word8
navajoWhite = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
222 Word8
173

-- | Defined in SVG1.1 as
--
-- @
-- navy = rgb(0, 0, 128)
-- @
--
-- <<files/svg/Navy.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = navy
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Navy.png" img
--
-- @since 0.3.3
navy :: Color (SRGB 'NonLinear) Word8
navy :: Color (SRGB 'NonLinear) Word8
navy = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
0 Word8
128

-- | Defined in SVG1.1 as
--
-- @
-- oldlace = rgb(253, 245, 230)
-- @
--
-- <<files/svg/OldLace.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = oldLace
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/OldLace.png" img
--
-- @since 0.3.3
oldLace :: Color (SRGB 'NonLinear) Word8
oldLace :: Color (SRGB 'NonLinear) Word8
oldLace = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
253 Word8
245 Word8
230

-- | Defined in SVG1.1 as
--
-- @
-- olive = rgb(128, 128, 0)
-- @
--
-- <<files/svg/Olive.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = olive
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Olive.png" img
--
-- @since 0.3.3
olive :: Color (SRGB 'NonLinear) Word8
olive :: Color (SRGB 'NonLinear) Word8
olive = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
128 Word8
128 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- olivedrab = rgb(107, 142, 35)
-- @
--
-- <<files/svg/OliveDrab.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = oliveDrab
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/OliveDrab.png" img
--
-- @since 0.3.3
oliveDrab :: Color (SRGB 'NonLinear) Word8
oliveDrab :: Color (SRGB 'NonLinear) Word8
oliveDrab = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
107 Word8
142 Word8
35

-- | Defined in SVG1.1 as
--
-- @
-- orange = rgb(255, 165, 0)
-- @
--
-- <<files/svg/Orange.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = orange
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Orange.png" img
--
-- @since 0.3.3
orange :: Color (SRGB 'NonLinear) Word8
orange :: Color (SRGB 'NonLinear) Word8
orange = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
165 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- orangered = rgb(255, 69, 0)
-- @
--
-- <<files/svg/OrangeRed.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = orangeRed
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/OrangeRed.png" img
--
-- @since 0.3.3
orangeRed :: Color (SRGB 'NonLinear) Word8
orangeRed :: Color (SRGB 'NonLinear) Word8
orangeRed = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
69 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- orchid = rgb(218, 112, 214)
-- @
--
-- <<files/svg/Orchid.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = orchid
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Orchid.png" img
--
-- @since 0.3.3
orchid :: Color (SRGB 'NonLinear) Word8
orchid :: Color (SRGB 'NonLinear) Word8
orchid = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
218 Word8
112 Word8
214

-- | Defined in SVG1.1 as
--
-- @
-- palegoldenrod = rgb(238, 232, 170)
-- @
--
-- <<files/svg/PaleGoldenRod.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = paleGoldenRod
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/PaleGoldenRod.png" img
--
-- @since 0.3.3
paleGoldenRod :: Color (SRGB 'NonLinear) Word8
paleGoldenRod :: Color (SRGB 'NonLinear) Word8
paleGoldenRod = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
238 Word8
232 Word8
170

-- | Defined in SVG1.1 as
--
-- @
-- palegreen = rgb(152, 251, 152)
-- @
--
-- <<files/svg/PaleGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = paleGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/PaleGreen.png" img
--
-- @since 0.3.3
paleGreen :: Color (SRGB 'NonLinear) Word8
paleGreen :: Color (SRGB 'NonLinear) Word8
paleGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
152 Word8
251 Word8
152

-- | Defined in SVG1.1 as
--
-- @
-- paleturquoise = rgb(175, 238, 238)
-- @
--
-- <<files/svg/PaleTurquoise.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = paleTurquoise
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/PaleTurquoise.png" img
--
-- @since 0.3.3
paleTurquoise :: Color (SRGB 'NonLinear) Word8
paleTurquoise :: Color (SRGB 'NonLinear) Word8
paleTurquoise = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
175 Word8
238 Word8
238

-- | Defined in SVG1.1 as
--
-- @
-- palevioletred = rgb(219, 112, 147)
-- @
--
-- <<files/svg/PaleVioletRed.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = paleVioletRed
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/PaleVioletRed.png" img
--
-- @since 0.3.3
paleVioletRed :: Color (SRGB 'NonLinear) Word8
paleVioletRed :: Color (SRGB 'NonLinear) Word8
paleVioletRed = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
219 Word8
112 Word8
147

-- | Defined in SVG1.1 as
--
-- @
-- papayawhip = rgb(255, 239, 213)
-- @
--
-- <<files/svg/PapayaWhip.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = papayaWhip
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/PapayaWhip.png" img
--
-- @since 0.3.3
papayaWhip :: Color (SRGB 'NonLinear) Word8
papayaWhip :: Color (SRGB 'NonLinear) Word8
papayaWhip = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
239 Word8
213

-- | Defined in SVG1.1 as
--
-- @
-- peachpuff = rgb(255, 218, 185)
-- @
--
-- <<files/svg/PeachPuff.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = peachPuff
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/PeachPuff.png" img
--
-- @since 0.3.3
peachPuff :: Color (SRGB 'NonLinear) Word8
peachPuff :: Color (SRGB 'NonLinear) Word8
peachPuff = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
218 Word8
185

-- | Defined in SVG1.1 as
--
-- @
-- peru = rgb(205, 133, 63)
-- @
--
-- <<files/svg/Peru.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = peru
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Peru.png" img
--
-- @since 0.3.3
peru :: Color (SRGB 'NonLinear) Word8
peru :: Color (SRGB 'NonLinear) Word8
peru = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
205 Word8
133 Word8
63

-- | Defined in SVG1.1 as
--
-- @
-- pink = rgb(255, 192, 203)
-- @
--
-- <<files/svg/Pink.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = pink
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Pink.png" img
--
-- @since 0.3.3
pink :: Color (SRGB 'NonLinear) Word8
pink :: Color (SRGB 'NonLinear) Word8
pink = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
192 Word8
203

-- | Defined in SVG1.1 as
--
-- @
-- plum = rgb(221, 160, 221)
-- @
--
-- <<files/svg/Plum.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = plum
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Plum.png" img
--
-- @since 0.3.3
plum :: Color (SRGB 'NonLinear) Word8
plum :: Color (SRGB 'NonLinear) Word8
plum = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
221 Word8
160 Word8
221

-- | Defined in SVG1.1 as
--
-- @
-- powderblue = rgb(176, 224, 230)
-- @
--
-- <<files/svg/PowderBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = powderBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/PowderBlue.png" img
--
-- @since 0.3.3
powderBlue :: Color (SRGB 'NonLinear) Word8
powderBlue :: Color (SRGB 'NonLinear) Word8
powderBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
176 Word8
224 Word8
230

-- | Defined in SVG1.1 as
--
-- @
-- purple = rgb(128, 0, 128)
-- @
--
-- <<files/svg/Purple.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = purple
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Purple.png" img
--
-- @since 0.3.3
purple :: Color (SRGB 'NonLinear) Word8
purple :: Color (SRGB 'NonLinear) Word8
purple = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
128 Word8
0 Word8
128

-- | Defined in SVG1.1 as
--
-- @
-- red = rgb(255, 0, 0)
-- @
--
-- <<files/svg/Red.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = red
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Red.png" img
--
-- @since 0.3.3
red :: Color (SRGB 'NonLinear) Word8
red :: Color (SRGB 'NonLinear) Word8
red = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
0 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- rosybrown = rgb(188, 143, 143)
-- @
--
-- <<files/svg/RosyBrown.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = rosyBrown
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/RosyBrown.png" img
--
-- @since 0.3.3
rosyBrown :: Color (SRGB 'NonLinear) Word8
rosyBrown :: Color (SRGB 'NonLinear) Word8
rosyBrown = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
188 Word8
143 Word8
143

-- | Defined in SVG1.1 as
--
-- @
-- royalblue = rgb(65, 105, 225)
-- @
--
-- <<files/svg/RoyalBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = royalBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/RoyalBlue.png" img
--
-- @since 0.3.3
royalBlue :: Color (SRGB 'NonLinear) Word8
royalBlue :: Color (SRGB 'NonLinear) Word8
royalBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
65 Word8
105 Word8
225

-- | Defined in SVG1.1 as
--
-- @
-- saddlebrown = rgb(139, 69, 19)
-- @
--
-- <<files/svg/SaddleBrown.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = saddleBrown
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SaddleBrown.png" img
--
-- @since 0.3.3
saddleBrown :: Color (SRGB 'NonLinear) Word8
saddleBrown :: Color (SRGB 'NonLinear) Word8
saddleBrown = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
139 Word8
69 Word8
19

-- | Defined in SVG1.1 as
--
-- @
-- salmon = rgb(250, 128, 114)
-- @
--
-- <<files/svg/Salmon.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = salmon
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Salmon.png" img
--
-- @since 0.3.3
salmon :: Color (SRGB 'NonLinear) Word8
salmon :: Color (SRGB 'NonLinear) Word8
salmon = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
250 Word8
128 Word8
114

-- | Defined in SVG1.1 as
--
-- @
-- sandybrown = rgb(244, 164, 96)
-- @
--
-- <<files/svg/SandyBrown.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = sandyBrown
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SandyBrown.png" img
--
-- @since 0.3.3
sandyBrown :: Color (SRGB 'NonLinear) Word8
sandyBrown :: Color (SRGB 'NonLinear) Word8
sandyBrown = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
244 Word8
164 Word8
96

-- | Defined in SVG1.1 as
--
-- @
-- seagreen = rgb(46, 139, 87)
-- @
--
-- <<files/svg/SeaGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = seaGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SeaGreen.png" img
--
-- @since 0.3.3
seaGreen :: Color (SRGB 'NonLinear) Word8
seaGreen :: Color (SRGB 'NonLinear) Word8
seaGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
46 Word8
139 Word8
87

-- | Defined in SVG1.1 as
--
-- @
-- seashell = rgb(255, 245, 238)
-- @
--
-- <<files/svg/Seashell.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = seashell
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Seashell.png" img
--
-- @since 0.3.3
seashell :: Color (SRGB 'NonLinear) Word8
seashell :: Color (SRGB 'NonLinear) Word8
seashell = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
245 Word8
238

-- | Defined in SVG1.1 as
--
-- @
-- sienna = rgb(160, 82, 45)
-- @
--
-- <<files/svg/Sienna.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = sienna
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Sienna.png" img
--
-- @since 0.3.3
sienna :: Color (SRGB 'NonLinear) Word8
sienna :: Color (SRGB 'NonLinear) Word8
sienna = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
160 Word8
82 Word8
45

-- | Defined in SVG1.1 as
--
-- @
-- silver = rgb(192, 192, 192)
-- @
--
-- <<files/svg/Silver.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = silver
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Silver.png" img
--
-- @since 0.3.3
silver :: Color (SRGB 'NonLinear) Word8
silver :: Color (SRGB 'NonLinear) Word8
silver = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
192 Word8
192 Word8
192

-- | Defined in SVG1.1 as
--
-- @
-- skyblue = rgb(135, 206, 235)
-- @
--
-- <<files/svg/SkyBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = skyBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SkyBlue.png" img
--
-- @since 0.3.3
skyBlue :: Color (SRGB 'NonLinear) Word8
skyBlue :: Color (SRGB 'NonLinear) Word8
skyBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
135 Word8
206 Word8
235

-- | Defined in SVG1.1 as
--
-- @
-- slateblue = rgb(106, 90, 205)
-- @
--
-- <<files/svg/SlateBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = slateBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SlateBlue.png" img
--
-- @since 0.3.3
slateBlue :: Color (SRGB 'NonLinear) Word8
slateBlue :: Color (SRGB 'NonLinear) Word8
slateBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
106 Word8
90 Word8
205

-- | Defined in SVG1.1 as
--
-- @
-- slategray = rgb(112, 128, 144)
-- @
--
-- <<files/svg/SlateGray.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = slateGray
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SlateGray.png" img
--
-- @since 0.3.3
slateGray :: Color (SRGB 'NonLinear) Word8
slateGray :: Color (SRGB 'NonLinear) Word8
slateGray = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
112 Word8
128 Word8
144

-- | Defined in SVG1.1 as
--
-- @
-- slategrey = rgb(112, 128, 144)
-- @
--
-- <<files/svg/SlateGrey.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = slateGrey
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SlateGrey.png" img
--
-- @since 0.3.3
slateGrey :: Color (SRGB 'NonLinear) Word8
slateGrey :: Color (SRGB 'NonLinear) Word8
slateGrey = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
112 Word8
128 Word8
144

-- | Defined in SVG1.1 as
--
-- @
-- snow = rgb(255, 250, 250)
-- @
--
-- <<files/svg/Snow.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = snow
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Snow.png" img
--
-- @since 0.3.3
snow :: Color (SRGB 'NonLinear) Word8
snow :: Color (SRGB 'NonLinear) Word8
snow = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
250 Word8
250

-- | Defined in SVG1.1 as
--
-- @
-- springgreen = rgb(0, 255, 127)
-- @
--
-- <<files/svg/SpringGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = springGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SpringGreen.png" img
--
-- @since 0.3.3
springGreen :: Color (SRGB 'NonLinear) Word8
springGreen :: Color (SRGB 'NonLinear) Word8
springGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
255 Word8
127

-- | Defined in SVG1.1 as
--
-- @
-- steelblue = rgb(70, 130, 180)
-- @
--
-- <<files/svg/SteelBlue.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = steelBlue
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/SteelBlue.png" img
--
-- @since 0.3.3
steelBlue :: Color (SRGB 'NonLinear) Word8
steelBlue :: Color (SRGB 'NonLinear) Word8
steelBlue = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
70 Word8
130 Word8
180

-- | Defined in SVG1.1 as
--
-- @
-- tan = rgb(210, 180, 140)
-- @
--
-- <<files/svg/Tan.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = tan
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Tan.png" img
--
-- @since 0.3.3
tan :: Color (SRGB 'NonLinear) Word8
tan :: Color (SRGB 'NonLinear) Word8
tan = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
210 Word8
180 Word8
140

-- | Defined in SVG1.1 as
--
-- @
-- teal = rgb(0, 128, 128)
-- @
--
-- <<files/svg/Teal.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = teal
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Teal.png" img
--
-- @since 0.3.3
teal :: Color (SRGB 'NonLinear) Word8
teal :: Color (SRGB 'NonLinear) Word8
teal = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
0 Word8
128 Word8
128

-- | Defined in SVG1.1 as
--
-- @
-- thistle = rgb(216, 191, 216)
-- @
--
-- <<files/svg/Thistle.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = thistle
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Thistle.png" img
--
-- @since 0.3.3
thistle :: Color (SRGB 'NonLinear) Word8
thistle :: Color (SRGB 'NonLinear) Word8
thistle = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
216 Word8
191 Word8
216

-- | Defined in SVG1.1 as
--
-- @
-- tomato = rgb(255, 99, 71)
-- @
--
-- <<files/svg/Tomato.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = tomato
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Tomato.png" img
--
-- @since 0.3.3
tomato :: Color (SRGB 'NonLinear) Word8
tomato :: Color (SRGB 'NonLinear) Word8
tomato = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
99 Word8
71

-- | Defined in SVG1.1 as
--
-- @
-- turquoise = rgb(64, 224, 208)
-- @
--
-- <<files/svg/Turquoise.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = turquoise
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Turquoise.png" img
--
-- @since 0.3.3
turquoise :: Color (SRGB 'NonLinear) Word8
turquoise :: Color (SRGB 'NonLinear) Word8
turquoise = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
64 Word8
224 Word8
208

-- | Defined in SVG1.1 as
--
-- @
-- violet = rgb(238, 130, 238)
-- @
--
-- <<files/svg/Violet.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = violet
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Violet.png" img
--
-- @since 0.3.3
violet :: Color (SRGB 'NonLinear) Word8
violet :: Color (SRGB 'NonLinear) Word8
violet = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
238 Word8
130 Word8
238

-- | Defined in SVG1.1 as
--
-- @
-- wheat = rgb(245, 222, 179)
-- @
--
-- <<files/svg/Wheat.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = wheat
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Wheat.png" img
--
-- @since 0.3.3
wheat :: Color (SRGB 'NonLinear) Word8
wheat :: Color (SRGB 'NonLinear) Word8
wheat = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
245 Word8
222 Word8
179

-- | Defined in SVG1.1 as
--
-- @
-- white = rgb(255, 255, 255)
-- @
--
-- <<files/svg/White.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = white
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/White.png" img
--
-- @since 0.3.3
white :: Color (SRGB 'NonLinear) Word8
white :: Color (SRGB 'NonLinear) Word8
white = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
255 Word8
255

-- | Defined in SVG1.1 as
--
-- @
-- whitesmoke = rgb(245, 245, 245)
-- @
--
-- <<files/svg/WhiteSmoke.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = whiteSmoke
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/WhiteSmoke.png" img
--
-- @since 0.3.3
whiteSmoke :: Color (SRGB 'NonLinear) Word8
whiteSmoke :: Color (SRGB 'NonLinear) Word8
whiteSmoke = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
245 Word8
245 Word8
245

-- | Defined in SVG1.1 as
--
-- @
-- yellow = rgb(255, 255, 0)
-- @
--
-- <<files/svg/Yellow.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = yellow
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/Yellow.png" img
--
-- @since 0.3.3
yellow :: Color (SRGB 'NonLinear) Word8
yellow :: Color (SRGB 'NonLinear) Word8
yellow = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
255 Word8
255 Word8
0

-- | Defined in SVG1.1 as
--
-- @
-- yellowgreen = rgb(154, 205, 50)
-- @
--
-- <<files/svg/YellowGreen.png>>
--
-- ===__Example__
--
-- >>> import Codec.Picture as JP
-- >>> import Codec.Picture.Png (writePng)
-- >>> let ColorSRGB r g b = yellowGreen
-- >>> let img = JP.generateImage (\_ _ -> JP.PixelRGB8 r g b) 200 34
-- >>> writePng "files/svg/YellowGreen.png" img
--
-- @since 0.3.3
yellowGreen :: Color (SRGB 'NonLinear) Word8
yellowGreen :: Color (SRGB 'NonLinear) Word8
yellowGreen = Word8 -> Word8 -> Word8 -> Color (SRGB 'NonLinear) Word8
forall e (l :: Linearity). e -> e -> e -> Color (SRGB l) e
ColorSRGB Word8
154 Word8
205 Word8
50