-----------------------------------------------------------------------------
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE OverloadedLabels      #-}
-----------------------------------------------------------------------------
{-# OPTIONS_GHC -fno-warn-orphans  #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Miso.CSS.Color
-- Copyright   :  (C) 2016-2025 David M. Johnson
-- License     :  BSD3-style (see the file LICENSE)
-- Maintainer  :  David M. Johnson <code@dmj.io>
-- Stability   :  experimental
-- Portability :  non-portable
-----------------------------------------------------------------------------
module Miso.CSS.Color
  ( -- *** Types
    Color (RGB, RGBA, HSL, HSLA, Hex)
    -- *** Smart constructor
  , rgba
  , rgb
  , hsl
  , hsla
  , hex
  , var
    -- *** Render
  , renderColor
    -- *** Colors
  , transparent
  , aliceblue
  , antiquewhite
  , aqua
  , aquamarine
  , azure
  , beige
  , bisque
  , black
  , blanchedalmond
  , blue
  , blueviolet
  , brown
  , burlywood
  , cadetblue
  , chartreuse
  , chocolate
  , coral
  , cornflowerblue
  , cornsilk
  , crimson
  , cyan
  , darkblue
  , darkcyan
  , darkgoldenrod
  , darkgray
  , darkgreen
  , darkgrey
  , darkkhaki
  , darkmagenta
  , darkolivegreen
  , darkorange
  , darkorchid
  , darkred
  , darksalmon
  , darkseagreen
  , darkslateblue
  , darkslategray
  , darkslategrey
  , darkturquoise
  , darkviolet
  , deeppink
  , deepskyblue
  , dimgray
  , dimgrey
  , dodgerblue
  , firebrick
  , floralwhite
  , forestgreen
  , fuchsia
  , gainsboro
  , ghostwhite
  , gold
  , goldenrod
  , gray
  , green
  , greenyellow
  , grey
  , honeydew
  , hotpink
  , indianred
  , indigo
  , ivory
  , khaki
  , lavender
  , lavenderblush
  , lawngreen
  , lemonchiffon
  , lightblue
  , lightcoral
  , lightcyan
  , lightgoldenrodyellow
  , lightgray
  , lightgreen
  , lightgrey
  , lightpink
  , lightsalmon
  , lightseagreen
  , lightskyblue
  , lightslategray
  , lightslategrey
  , lightsteelblue
  , lightyellow
  , lime
  , limegreen
  , linen
  , magenta
  , maroon
  , mediumaquamarine
  , mediumblue
  , mediumorchid
  , mediumpurple
  , mediumseagreen
  , mediumslateblue
  , mediumspringgreen
  , mediumturquoise
  , mediumvioletred
  , midnightblue
  , mintcream
  , mistyrose
  , moccasin
  , navajowhite
  , navy
  , oldlace
  , olive
  , olivedrab
  , orange
  , orangered
  , orchid
  , palegoldenrod
  , palegreen
  , paleturquoise
  , palevioletred
  , papayawhip
  , peachpuff
  , peru
  , pink
  , plum
  , powderblue
  , purple
  , red
  , rosybrown
  , royalblue
  , saddlebrown
  , salmon
  , sandybrown
  , seagreen
  , seashell
  , sienna
  , silver
  , skyblue
  , slateblue
  , slategray
  , slategrey
  , snow
  , springgreen
  , steelblue
  , tan
  , teal
  , thistle
  , tomato
  , turquoise
  , violet
  , wheat
  , white
  , whitesmoke
  , yellow
  , yellowgreen
  ) where
-----------------------------------------------------------------------------
import           Miso.String (MisoString, ms)
import qualified Miso.String as MS
-----------------------------------------------------------------------------
import           Data.Proxy
import           GHC.TypeLits
import           GHC.OverloadedLabels
import           Language.Javascript.JSaddle (ToJSVal(..), MakeArgs(..))
import           Prelude hiding (tan)
-----------------------------------------------------------------------------
-- | Data type for expressing Color
data Color
  = RGBA Int Int Int Double
  -- ^ Red, green, blue and alpha transparency. See [here](https://www.w3schools.com/colors/colors_rgb.asp)
  | RGB Int Int Int
  -- ^ Red, green, blue. See [here](https://www.w3schools.com/colors/colors_rgb.asp)
  | HSL Int Int Int
  -- ^ Hue, saturation, light. See [here](https://www.w3schools.com/colors/colors_hsl.asp)
  | HSLA Int Int Int Double
  -- ^ Hue, saturation, light and alpha transparency. See [here](https://www.w3schools.com/colors/colors_hsl.asp)
  | Hex MisoString
  -- ^ Hexadecimal representation of a color. See [here](https://www.w3schools.com/colors/colors_hexadecimal.asp)
  | VarColor MisoString
  -- ^ A CSS variable
  deriving (Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
(Int -> Color -> ShowS)
-> (Color -> String) -> ([Color] -> ShowS) -> Show Color
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Color -> ShowS
showsPrec :: Int -> Color -> ShowS
$cshow :: Color -> String
show :: Color -> String
$cshowList :: [Color] -> ShowS
showList :: [Color] -> ShowS
Show, Color -> Color -> Bool
(Color -> Color -> Bool) -> (Color -> Color -> Bool) -> Eq Color
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
/= :: Color -> Color -> Bool
Eq)
-----------------------------------------------------------------------------
-- | 'IsLabel' instance on 'Color'
--
-- @
-- grey :: Color
-- grey = #cccccc
-- @
instance KnownSymbol color => IsLabel color Color where
  fromLabel :: Color
fromLabel = MisoString -> Color
Hex (String -> MisoString
forall str. ToMisoString str => str -> MisoString
ms String
color)
    where
      color :: String
color = Proxy color -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @color)
-----------------------------------------------------------------------------
-- | 'IsLabel' instance on 'MisoString' for construction of hex colors as strings
--
-- @
-- grey :: MisoString
-- grey = #cccccc
-- @
instance KnownSymbol hex => IsLabel hex MisoString where
  fromLabel :: MisoString
fromLabel = String -> MisoString
forall str. ToMisoString str => str -> MisoString
ms (String
"#" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Proxy hex -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @hex))
-----------------------------------------------------------------------------
-- | 'MakeArgs' instance for 'Color'
instance MakeArgs Color where
  makeArgs :: Color -> JSM [JSVal]
makeArgs Color
color = (JSVal -> [JSVal] -> [JSVal]
forall a. a -> [a] -> [a]
:[]) (JSVal -> [JSVal]) -> JSM JSVal -> JSM [JSVal]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Color -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Color
color
-----------------------------------------------------------------------------
-- | 'ToJSVal' instance for 'Color'
instance ToJSVal Color where
  toJSVal :: Color -> JSM JSVal
toJSVal = MisoString -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal (MisoString -> JSM JSVal)
-> (Color -> MisoString) -> Color -> JSM JSVal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color -> MisoString
renderColor
-----------------------------------------------------------------------------
-- | Renders a 'Color' as 'MisoString'
--
-- >>> renderColor (hex "ccc")
-- "#ccc"
-- 
renderColor :: Color -> MisoString
renderColor :: Color -> MisoString
renderColor (RGBA Int
r Int
g Int
b Double
a) = MisoString
"rgba(" MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
values MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
")"
  where
    values :: MisoString
values = MisoString -> [MisoString] -> MisoString
MS.intercalate MisoString
","
      [ Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
r
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
g
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
b
      , Double -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Double
a
      ]
renderColor (RGB Int
r Int
g Int
b) = MisoString
"rgb(" MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
values MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
")"
  where
    values :: MisoString
values = MisoString -> [MisoString] -> MisoString
MS.intercalate MisoString
","
      [ Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
r
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
g
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
b
      ]
renderColor (HSLA Int
h Int
s Int
l Double
a) = MisoString
"hsla(" MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
values MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
")"
  where
    values :: MisoString
values = MisoString -> [MisoString] -> MisoString
MS.intercalate MisoString
","
      [ Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
h
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
s
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
l
      , Double -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Double
a
      ]
renderColor (HSL Int
h Int
s Int
l) = MisoString
"hsl(" MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
values MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
")"
  where
    values :: MisoString
values = MisoString -> [MisoString] -> MisoString
MS.intercalate MisoString
","
      [ Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
h
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
s
      , Int -> MisoString
forall str. ToMisoString str => str -> MisoString
MS.ms Int
l
      ]
renderColor (Hex MisoString
s) = MisoString
"#" MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
s
renderColor (VarColor MisoString
n) = MisoString
"var(--" MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
n MisoString -> MisoString -> MisoString
forall a. Semigroup a => a -> a -> a
<> MisoString
")"
-----------------------------------------------------------------------------
-- | Smart constructor for a [CSS variable](https://developer.mozilla.org/en-US/docs/Web/CSS/CSS_cascading_variables/Using_CSS_custom_properties).
--
-- >>> renderColor (var "foo")
-- "var(--foo)"
-- 
var :: MisoString -> Color
var :: MisoString -> Color
var = MisoString -> Color
VarColor
-----------------------------------------------------------------------------
-- | Smart constructor for an [RGBA](https://www.w3schools.com/css/css_colors_rgb.asp) 'Color' value.
--
-- >>> renderColor (rgba 0 0 0 1.0)
-- "rgba(0,0,0,1.0)"
--
rgba :: Int -> Int -> Int -> Double -> Color
rgba :: Int -> Int -> Int -> Double -> Color
rgba = Int -> Int -> Int -> Double -> Color
RGBA
-----------------------------------------------------------------------------
-- | Smart constructor for an [RGB](https://www.w3schools.com/css/css_colors_rgb.asp) 'Color' value.
--
-- >>> renderColor (rgb 0 0 0)
-- "rgb(0,0,0)"
--
rgb :: Int -> Int -> Int -> Color
rgb :: Int -> Int -> Int -> Color
rgb = Int -> Int -> Int -> Color
RGB
-----------------------------------------------------------------------------
-- | Smart constructor for an [HSL](https://www.w3schools.com/css/css_colors_hsl.asp) 'Color' value.
--
-- >>> renderColor (hsl 0 0 0)
-- "hsl(0,0,0)"
--
hsl :: Int -> Int -> Int -> Color
hsl :: Int -> Int -> Int -> Color
hsl = Int -> Int -> Int -> Color
HSL
-----------------------------------------------------------------------------
-- | Smart constructor for a [HSLA](https://www.w3schools.com/css/css_colors_hsl.asp) 'Color' value.
--
-- >>> renderColor (hsla 0 0 0 1.0)
-- "hsla(0,0,0,1.0)"
--
hsla :: Int -> Int -> Int -> Double -> Color
hsla :: Int -> Int -> Int -> Double -> Color
hsla = Int -> Int -> Int -> Double -> Color
HSLA
-----------------------------------------------------------------------------
-- | Smart constructor for a 'Hex' 'Color'
--
-- >>> renderColor (hsla 0 0 0 1.0)
-- "hsl(0,0,0,1.0)"
--
hex :: MisoString -> Color
hex :: MisoString -> Color
hex = MisoString -> Color
Hex
-----------------------------------------------------------------------------
-- | Smart constructor for the 'transparent' color
--
-- >>> renderColor transparent
-- "rgba(0,0,0,0.0)"
--
transparent :: Color
transparent :: Color
transparent = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
0 Int
0 Double
0
-- <svg xmlns="http://www.w3.org/2000/svg" width="100" height="100"><rect width="100" height="100" fill="goldenrod"/></svg>
-- data:image/svg+xml;base64,
-----------------------------------------------------------------------------
-- | Smart constructor for the 'aliceblue' 'Color'.
--
-- >>> renderColor aliceblue
-- "rgba(240,248,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYWxpY2VibHVlIi8+PC9zdmc+>>
--
aliceblue :: Color
aliceblue :: Color
aliceblue = Int -> Int -> Int -> Double -> Color
rgba Int
240 Int
248 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'antiquewhite' 'Color'.
--
-- >>> renderColor antiquewhite
-- "rgba(250,235,215,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYW50aXF1ZXdoaXRlIi8+PC9zdmc+>>
--
antiquewhite :: Color
antiquewhite :: Color
antiquewhite = Int -> Int -> Int -> Double -> Color
rgba Int
250 Int
235 Int
215 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'aqua' 'Color'.
--
-- >>> renderColor aqua
-- "rgba(0,255,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYXF1YSIvPjwvc3ZnPg==>>
--
aqua :: Color
aqua :: Color
aqua = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
255 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'aquamarine' 'Color'.
--
-- >>> renderColor aquamarine
-- "rgba(127,255,212,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYXF1YW1hcmluZSIvPjwvc3ZnPg==>>
--
aquamarine :: Color
aquamarine :: Color
aquamarine = Int -> Int -> Int -> Double -> Color
rgba Int
127 Int
255 Int
212 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'azure' 'Color'.
--
-- >>> renderColor azure
-- "rgba(240,255,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYXp1cmUiLz48L3N2Zz4=>>
--
azure :: Color
azure :: Color
azure = Int -> Int -> Int -> Double -> Color
rgba Int
240 Int
255 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'beige' 'Color'.
--
-- >>> renderColor beige
-- "rgba(245,245,220,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYmVpZ2UiLz48L3N2Zz4=>>
--
beige :: Color
beige :: Color
beige = Int -> Int -> Int -> Double -> Color
rgba Int
245 Int
245 Int
220 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'bisque' 'Color'.
--
-- >>> renderColor bisque
-- "rgba(255,228,196,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYmlzcXVlIi8+PC9zdmc+>>
--
bisque :: Color
bisque :: Color
bisque = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
228 Int
196 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'black' 'Color'.
--
-- >>> renderColor black
-- "rgba(0,0,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYmxhY2siLz48L3N2Zz4=>>
--
black :: Color
black :: Color
black = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
0 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'blanchedalmond' 'Color'.
--
-- >>> renderColor blanchedalmond
-- "rgba(255,235,205,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYmxhbmNoZWRhbG1vbmQiLz48L3N2Zz4=>>
--
blanchedalmond :: Color
blanchedalmond :: Color
blanchedalmond = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
235 Int
205 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'blue' 'Color'.
--
-- >>> renderColor blue
-- "rgba(0,0,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYmx1ZSIvPjwvc3ZnPg==>>
--
blue :: Color
blue :: Color
blue = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
0 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'blueviolet' 'Color'.
--
-- >>> renderColor blueviolet
-- "rgba(138,43,226,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYmx1ZXZpb2xldCIvPjwvc3ZnPg==>>
--
blueviolet :: Color
blueviolet :: Color
blueviolet = Int -> Int -> Int -> Double -> Color
rgba Int
138 Int
43 Int
226 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'brown' 'Color'.
--
-- >>> renderColor brown
-- "rgba(165,42,42,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYnJvd24iLz48L3N2Zz4=>>
--
brown :: Color
brown :: Color
brown = Int -> Int -> Int -> Double -> Color
rgba Int
165 Int
42 Int
42 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'burlywood' 'Color'.
--
-- >>> renderColor burlywood
-- "rgba(222,184,135,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iYnVybHl3b29kIi8+PC9zdmc+>>
--
burlywood :: Color
burlywood :: Color
burlywood = Int -> Int -> Int -> Double -> Color
rgba Int
222 Int
184 Int
135 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'cadetblue' 'Color'.
--
-- >>> renderColor cadetblue
-- "rgba(95,158,160,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY2FkZXRibHVlIi8+PC9zdmc+>>
--
cadetblue :: Color
cadetblue :: Color
cadetblue = Int -> Int -> Int -> Double -> Color
rgba Int
95 Int
158 Int
160 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'chartreuse' 'Color'.
--
-- >>> renderColor chartreuse
-- "rgba(127,255,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY2hhcnRyZXVzZSIvPjwvc3ZnPg==>>
--
chartreuse :: Color
chartreuse :: Color
chartreuse = Int -> Int -> Int -> Double -> Color
rgba Int
127 Int
255 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'chocolate' 'Color'.
--
-- >>> renderColor chocolate
-- "rgba(210,105,30,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY2hvY29sYXRlIi8+PC9zdmc+>>
--
chocolate :: Color
chocolate :: Color
chocolate = Int -> Int -> Int -> Double -> Color
rgba Int
210 Int
105 Int
30 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'coral' 'Color'.
--
-- >>> renderColor coral
-- "rgba(255,127,80,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY29yYWwiLz48L3N2Zz4=>>
--
coral :: Color
coral :: Color
coral = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
127 Int
80 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'cornflowerblue' 'Color'.
--
-- >>> renderColor cornflowerblue
-- "rgba(100,149,237,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY29ybmZsb3dlcmJsdWUiLz48L3N2Zz4=>>
--
cornflowerblue :: Color
cornflowerblue :: Color
cornflowerblue = Int -> Int -> Int -> Double -> Color
rgba Int
100 Int
149 Int
237 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'cornsilk' 'Color'.
--
-- >>> renderColor cornsilk
-- "rgba(255,248,220,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY29ybnNpbGsiLz48L3N2Zz4=>>
--
cornsilk :: Color
cornsilk :: Color
cornsilk = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
248 Int
220 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'crimson' 'Color'.
--
-- >>> renderColor crimson
-- "rgba(220,20,60,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY3JpbXNvbiIvPjwvc3ZnPg==>>
--
crimson :: Color
crimson :: Color
crimson = Int -> Int -> Int -> Double -> Color
rgba Int
220 Int
20 Int
60 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'cyan' 'Color'.
--
-- >>> renderColor cyan
-- "rgba(0,255,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iY3lhbiIvPjwvc3ZnPg==>>
--
cyan :: Color
cyan :: Color
cyan = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
255 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkblue' 'Color'.
--
-- >>> renderColor darkblue
-- "rgba(0,0,139,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya2JsdWUiLz48L3N2Zz4=>>
--
darkblue :: Color
darkblue :: Color
darkblue = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
0 Int
139 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkcyan' 'Color'.
--
-- >>> renderColor darkcyan
-- "rgba(0,139,139,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya2N5YW4iLz48L3N2Zz4=>>
--
darkcyan :: Color
darkcyan :: Color
darkcyan = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
139 Int
139 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkgoldenrod' 'Color'.
--
-- >>> renderColor darkgoldenrod
-- "rgba(184,134,11,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya2dvbGRlbnJvZCIvPjwvc3ZnPg==>>
--
darkgoldenrod :: Color
darkgoldenrod :: Color
darkgoldenrod = Int -> Int -> Int -> Double -> Color
rgba Int
184 Int
134 Int
11 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkgray' 'Color'.
--
-- >>> renderColor darkgray
-- "rgba(169,169,169,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya2dyYXkiLz48L3N2Zz4=>>
--
darkgray :: Color
darkgray :: Color
darkgray = Int -> Int -> Int -> Double -> Color
rgba Int
169 Int
169 Int
169 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkgreen' 'Color'.
--
-- >>> renderColor darkgreen
-- "rgba(0,100,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya2dyZWVuIi8+PC9zdmc+>>
--
darkgreen :: Color
darkgreen :: Color
darkgreen = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
100 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkgrey' 'Color'.
--
-- >>> renderColor darkgrey
-- "rgba(169,169,169,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya2dyZXkiLz48L3N2Zz4=>>
--
darkgrey :: Color
darkgrey :: Color
darkgrey = Int -> Int -> Int -> Double -> Color
rgba Int
169 Int
169 Int
169 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkkhaki' 'Color'.
--
-- >>> renderColor darkkhaki
-- "rgba(189,183,107,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya2toYWtpIi8+PC9zdmc+>>
--
darkkhaki :: Color
darkkhaki :: Color
darkkhaki = Int -> Int -> Int -> Double -> Color
rgba Int
189 Int
183 Int
107 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkmagenta' 'Color'.
--
-- >>> renderColor darkmagenta
-- "rgba(139,0,139,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya21hZ2VudGEiLz48L3N2Zz4=>>
--
darkmagenta :: Color
darkmagenta :: Color
darkmagenta = Int -> Int -> Int -> Double -> Color
rgba Int
139 Int
0 Int
139 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkolivegreen' 'Color'.
--
-- >>> renderColor darkolivegreen
-- "rgba(85,107,47,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya29saXZlZ3JlZW4iLz48L3N2Zz4=>>
--
darkolivegreen :: Color
darkolivegreen :: Color
darkolivegreen = Int -> Int -> Int -> Double -> Color
rgba Int
85 Int
107 Int
47 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkorange' 'Color'.
--
-- >>> renderColor darkorange
-- "rgba(255,140,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya29yYW5nZSIvPjwvc3ZnPg==>>
--
darkorange :: Color
darkorange :: Color
darkorange = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
140 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkorchid' 'Color'.
--
-- >>> renderColor darkorchid
-- "rgba(153,50,204,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya29yY2hpZCIvPjwvc3ZnPg==>>
--
darkorchid :: Color
darkorchid :: Color
darkorchid = Int -> Int -> Int -> Double -> Color
rgba Int
153 Int
50 Int
204 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkred' 'Color'.
--
-- >>> renderColor darkred
-- "rgba(139,0,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3JlZCIvPjwvc3ZnPg==>>
--
darkred :: Color
darkred :: Color
darkred = Int -> Int -> Int -> Double -> Color
rgba Int
139 Int
0 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darksalmon' 'Color'.
--
-- >>> renderColor darksalmon
-- "rgba(233,150,122,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3NhbG1vbiIvPjwvc3ZnPg==>>
--
darksalmon :: Color
darksalmon :: Color
darksalmon = Int -> Int -> Int -> Double -> Color
rgba Int
233 Int
150 Int
122 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkseagreen' 'Color'.
--
-- >>> renderColor darkseagreen
-- "rgba(143,188,143,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3NlYWdyZWVuIi8+PC9zdmc+>>
--
darkseagreen :: Color
darkseagreen :: Color
darkseagreen = Int -> Int -> Int -> Double -> Color
rgba Int
143 Int
188 Int
143 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkslateblue' 'Color'.
--
-- >>> renderColor darkslateblue
-- "rgba(72,61,139,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3NsYXRlYmx1ZSIvPjwvc3ZnPg==>>
--
darkslateblue :: Color
darkslateblue :: Color
darkslateblue = Int -> Int -> Int -> Double -> Color
rgba Int
72 Int
61 Int
139 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkslategray' 'Color'.
--
-- >>> renderColor darkslategray
-- "rgba(47,79,79,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3NsYXRlZ3JheSIvPjwvc3ZnPg==>>
--
darkslategray :: Color
darkslategray :: Color
darkslategray = Int -> Int -> Int -> Double -> Color
rgba Int
47 Int
79 Int
79 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkslategrey' 'Color'.
--
-- >>> renderColor darkslategrey
-- "rgba(47,79,79,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3NsYXRlZ3JleSIvPjwvc3ZnPg==>>
--
darkslategrey :: Color
darkslategrey :: Color
darkslategrey = Int -> Int -> Int -> Double -> Color
rgba Int
47 Int
79 Int
79 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkturquoise' 'Color'.
--
-- >>> renderColor darkturquoise
-- "rgba(0,206,209,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3R1cnF1b2lzZSIvPjwvc3ZnPg==>>
--
darkturquoise :: Color
darkturquoise :: Color
darkturquoise = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
206 Int
209 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'darkviolet' 'Color'.
--
-- >>> renderColor darkviolet
-- "rgba(148,0,211,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGFya3Zpb2xldCIvPjwvc3ZnPg==>>
--
darkviolet :: Color
darkviolet :: Color
darkviolet = Int -> Int -> Int -> Double -> Color
rgba Int
148 Int
0 Int
211 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'deeppink' 'Color'.
--
-- >>> renderColor deeppink
-- "rgba(255,20,147,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGVlcHBpbmsiLz48L3N2Zz4=>>
--
deeppink :: Color
deeppink :: Color
deeppink = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
20 Int
147 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'deepskyblue' 'Color'.
--
-- >>> renderColor deepskyblue
-- "rgba(0,191,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGVlcHNreWJsdWUiLz48L3N2Zz4=>>
--
deepskyblue :: Color
deepskyblue :: Color
deepskyblue = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
191 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'dimgray' 'Color'.
--
-- >>> renderColor dimgray
-- "rgba(105,105,105,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGltZ3JheSIvPjwvc3ZnPg==>>
--
dimgray :: Color
dimgray :: Color
dimgray = Int -> Int -> Int -> Double -> Color
rgba Int
105 Int
105 Int
105 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'dimgrey' 'Color'.
--
-- >>> renderColor dimgrey
-- "rgba(105,105,105,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZGltZ3JleSIvPjwvc3ZnPg==>>
--
dimgrey :: Color
dimgrey :: Color
dimgrey = Int -> Int -> Int -> Double -> Color
rgba Int
105 Int
105 Int
105 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'dodgerblue' 'Color'.
--
-- >>> renderColor dodgerblue
-- "rgba(30,144,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZG9kZ2VyYmx1ZSIvPjwvc3ZnPg==>>
--
dodgerblue :: Color
dodgerblue :: Color
dodgerblue = Int -> Int -> Int -> Double -> Color
rgba Int
30 Int
144 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'firebrick' 'Color'.
--
-- >>> renderColor firebrick
-- "rgba(178,34,34,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZmlyZWJyaWNrIi8+PC9zdmc+>>
--
firebrick :: Color
firebrick :: Color
firebrick = Int -> Int -> Int -> Double -> Color
rgba Int
178 Int
34 Int
34 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'floralwhite' 'Color'.
--
-- >>> renderColor floralwhite
-- "rgba(255,250,240,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZmxvcmFsd2hpdGUiLz48L3N2Zz4=>>
--
floralwhite :: Color
floralwhite :: Color
floralwhite = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
250 Int
240 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'forestgreen' 'Color'.
--
-- >>> renderColor forestgreen
-- "rgba(34,139,34,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZm9yZXN0Z3JlZW4iLz48L3N2Zz4=>>
--
forestgreen :: Color
forestgreen :: Color
forestgreen = Int -> Int -> Int -> Double -> Color
rgba Int
34 Int
139 Int
34 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'fuchsia' 'Color'.
--
-- >>> renderColor fuchsia
-- "rgba(255,0,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZnVjaHNpYSIvPjwvc3ZnPg==>>
--
fuchsia :: Color
fuchsia :: Color
fuchsia = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
0 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'gainsboro' 'Color'.
--
-- >>> renderColor gainsboro
-- "rgba(220,220,220,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ2FpbnNib3JvIi8+PC9zdmc+>>
--
gainsboro :: Color
gainsboro :: Color
gainsboro = Int -> Int -> Int -> Double -> Color
rgba Int
220 Int
220 Int
220 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'ghostwhite' 'Color'.
--
-- >>> renderColor ghostwhite
-- "rgba(248,248,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ2hvc3R3aGl0ZSIvPjwvc3ZnPg==>>
--
ghostwhite :: Color
ghostwhite :: Color
ghostwhite = Int -> Int -> Int -> Double -> Color
rgba Int
248 Int
248 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'gold' 'Color'.
--
-- >>> renderColor gold
-- "rgba(255,215,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ29sZCIvPjwvc3ZnPg==>>
--
gold :: Color
gold :: Color
gold = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
215 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'goldenrod' 'Color'.
--
-- >>> renderColor goldenrod
-- "rgba(218,165,32,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ29sZGVucm9kIi8+PC9zdmc+>>
--
goldenrod :: Color
goldenrod :: Color
goldenrod = Int -> Int -> Int -> Double -> Color
rgba Int
218 Int
165 Int
32 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'gray' 'Color'.
--
-- >>> renderColor gray
-- "rgba(128,128,128,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ3JheSIvPjwvc3ZnPg==>>
--
gray :: Color
gray :: Color
gray = Int -> Int -> Int -> Double -> Color
rgba Int
128 Int
128 Int
128 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'green' 'Color'.
--
-- >>> renderColor green
-- "rgba(0,128,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ3JlZW4iLz48L3N2Zz4=>>
--
green :: Color
green :: Color
green = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
128 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'greenyellow' 'Color'.
--
-- >>> renderColor greenyellow
-- "rgba(173,255,47,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ3JlZW55ZWxsb3ciLz48L3N2Zz4=>>
--
greenyellow :: Color
greenyellow :: Color
greenyellow = Int -> Int -> Int -> Double -> Color
rgba Int
173 Int
255 Int
47 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'grey' 'Color'.
--
-- >>> renderColor grey
-- "rgba(128,128,128,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iZ3JleSIvPjwvc3ZnPg==>>
--
grey :: Color
grey :: Color
grey = Int -> Int -> Int -> Double -> Color
rgba Int
128 Int
128 Int
128 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'honeydew' 'Color'.
--
-- >>> renderColor honeydew
-- "rgba(240,255,240,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iaG9uZXlkZXciLz48L3N2Zz4=>>
--
honeydew :: Color
honeydew :: Color
honeydew = Int -> Int -> Int -> Double -> Color
rgba Int
240 Int
255 Int
240 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'hotpink' 'Color'.
--
-- >>> renderColor hotpink
-- "rgba(255,105,180,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iaG90cGluayIvPjwvc3ZnPg==>>
--
hotpink :: Color
hotpink :: Color
hotpink = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
105 Int
180 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'indianred' 'Color'.
--
-- >>> renderColor indianred
-- "rgba(205,92,92,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iaW5kaWFucmVkIi8+PC9zdmc+>>
--
indianred :: Color
indianred :: Color
indianred = Int -> Int -> Int -> Double -> Color
rgba Int
205 Int
92 Int
92 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'indigo' 'Color'.
--
-- >>> renderColor indigo
-- "rgba(75,0,130,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iaW5kaWdvIi8+PC9zdmc+>>
--
indigo :: Color
indigo :: Color
indigo = Int -> Int -> Int -> Double -> Color
rgba Int
75 Int
0 Int
130 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'ivory' 'Color'.
--
-- >>> renderColor ivory
-- "rgba(255,255,240,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0iaXZvcnkiLz48L3N2Zz4=>>
--
ivory :: Color
ivory :: Color
ivory = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
255 Int
240 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'khaki' 'Color'.
--
-- >>> renderColor khaki
-- "rgba(240,230,140,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ia2hha2kiLz48L3N2Zz4=>>
--
khaki :: Color
khaki :: Color
khaki = Int -> Int -> Int -> Double -> Color
rgba Int
240 Int
230 Int
140 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lavender' 'Color'.
--
-- >>> renderColor lavender
-- "rgba(230,230,250,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGF2ZW5kZXIiLz48L3N2Zz4=>>
--
lavender :: Color
lavender :: Color
lavender = Int -> Int -> Int -> Double -> Color
rgba Int
230 Int
230 Int
250 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lavenderblush' 'Color'.
--
-- >>> renderColor lavenderblush
-- "rgba(255,240,245,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGF2ZW5kZXJibHVzaCIvPjwvc3ZnPg==>>
--
lavenderblush :: Color
lavenderblush :: Color
lavenderblush = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
240 Int
245 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lawngreen' 'Color'.
--
-- >>> renderColor lawngreen
-- "rgba(124,252,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGF3bmdyZWVuIi8+PC9zdmc+>>
--
lawngreen :: Color
lawngreen :: Color
lawngreen = Int -> Int -> Int -> Double -> Color
rgba Int
124 Int
252 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lemonchiffon' 'Color'.
--
-- >>> renderColor lemonchiffon
-- "rgba(255,250,205,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGVtb25jaGlmZm9uIi8+PC9zdmc+>>
--
lemonchiffon :: Color
lemonchiffon :: Color
lemonchiffon = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
250 Int
205 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightblue' 'Color'.
--
-- >>> renderColor lightblue
-- "rgba(173,216,230,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRibHVlIi8+PC9zdmc+>>
--
lightblue :: Color
lightblue :: Color
lightblue = Int -> Int -> Int -> Double -> Color
rgba Int
173 Int
216 Int
230 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightcoral' 'Color'.
--
-- >>> renderColor lightcoral
-- "rgba(240,128,128,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRjb3JhbCIvPjwvc3ZnPg==>>
--
lightcoral :: Color
lightcoral :: Color
lightcoral = Int -> Int -> Int -> Double -> Color
rgba Int
240 Int
128 Int
128 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightcyan' 'Color'.
--
-- >>> renderColor lightcyan
-- "rgba(224,255,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRjeWFuIi8+PC9zdmc+>>
--
lightcyan :: Color
lightcyan :: Color
lightcyan = Int -> Int -> Int -> Double -> Color
rgba Int
224 Int
255 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightgoldenrodyellow' 'Color'.
--
-- >>> renderColor lightgoldenrodyellow
-- "rgba(250,250,210,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRnb2xkZW5yb2R5ZWxsb3ciLz48L3N2Zz4=>>
--
lightgoldenrodyellow :: Color
lightgoldenrodyellow :: Color
lightgoldenrodyellow = Int -> Int -> Int -> Double -> Color
rgba Int
250 Int
250 Int
210 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightgray' 'Color'.
--
-- >>> renderColor lightgray
-- "rgba(211,211,211,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRncmF5Ii8+PC9zdmc+>>
--
lightgray :: Color
lightgray :: Color
lightgray = Int -> Int -> Int -> Double -> Color
rgba Int
211 Int
211 Int
211 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightgreen' 'Color'.
--
-- >>> renderColor lightgreen
-- "rgba(144,238,144,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRncmVlbiIvPjwvc3ZnPg==>>
--
lightgreen :: Color
lightgreen :: Color
lightgreen = Int -> Int -> Int -> Double -> Color
rgba Int
144 Int
238 Int
144 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightgrey' 'Color'.
--
-- >>> renderColor lightgrey
-- "rgba(211,211,211,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRncmV5Ii8+PC9zdmc+>>
--
lightgrey :: Color
lightgrey :: Color
lightgrey = Int -> Int -> Int -> Double -> Color
rgba Int
211 Int
211 Int
211 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightpink' 'Color'.
--
-- >>> renderColor lightpink
-- "rgba(255,182,193,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRwaW5rIi8+PC9zdmc+>>
--
lightpink :: Color
lightpink :: Color
lightpink = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
182 Int
193 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightsalmon' 'Color'.
--
-- >>> renderColor lightsalmon
-- "rgba(255,160,122,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRzYWxtb24iLz48L3N2Zz4=>>
--
lightsalmon :: Color
lightsalmon :: Color
lightsalmon = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
160 Int
122 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightseagreen' 'Color'.
--
-- >>> renderColor lightseagreen
-- "rgba(32,178,170,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRzZWFncmVlbiIvPjwvc3ZnPg==>>
--
lightseagreen :: Color
lightseagreen :: Color
lightseagreen = Int -> Int -> Int -> Double -> Color
rgba Int
32 Int
178 Int
170 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightskyblue' 'Color'.
--
-- >>> renderColor lightskyblue
-- "rgba(135,206,250,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRza3libHVlIi8+PC9zdmc+>>
--
lightskyblue :: Color
lightskyblue :: Color
lightskyblue = Int -> Int -> Int -> Double -> Color
rgba Int
135 Int
206 Int
250 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightslategray' 'Color'.
--
-- >>> renderColor lightslategray
-- "rgba(119,136,153,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRzbGF0ZWdyYXkiLz48L3N2Zz4=>>
--
lightslategray :: Color
lightslategray :: Color
lightslategray = Int -> Int -> Int -> Double -> Color
rgba Int
119 Int
136 Int
153 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightslategrey' 'Color'.
--
-- >>> renderColor lightslategrey
-- "rgba(119,136,153,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRzbGF0ZWdyZXkiLz48L3N2Zz4=>>
--
lightslategrey :: Color
lightslategrey :: Color
lightslategrey = Int -> Int -> Int -> Double -> Color
rgba Int
119 Int
136 Int
153 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightsteelblue' 'Color'.
--
-- >>> renderColor lightsteelblue
-- "rgba(176,196,222,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHRzdGVlbGJsdWUiLz48L3N2Zz4=>>
--
lightsteelblue :: Color
lightsteelblue :: Color
lightsteelblue = Int -> Int -> Int -> Double -> Color
rgba Int
176 Int
196 Int
222 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lightyellow' 'Color'.
--
-- >>> renderColor lightyellow
-- "rgba(255,255,224,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGlnaHR5ZWxsb3ciLz48L3N2Zz4=>>
--
lightyellow :: Color
lightyellow :: Color
lightyellow = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
255 Int
224 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'lime' 'Color'.
--
-- >>> renderColor lime
-- "rgba(0,255,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGltZSIvPjwvc3ZnPg==>>
--
lime :: Color
lime :: Color
lime = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
255 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'limegreen' 'Color'.
--
-- >>> renderColor limegreen
-- "rgba(50,205,50,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGltZWdyZWVuIi8+PC9zdmc+>>
--
limegreen :: Color
limegreen :: Color
limegreen = Int -> Int -> Int -> Double -> Color
rgba Int
50 Int
205 Int
50 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'linen' 'Color'.
--
-- >>> renderColor linen
-- "rgba(250,240,230,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibGluZW4iLz48L3N2Zz4=>>
--
linen :: Color
linen :: Color
linen = Int -> Int -> Int -> Double -> Color
rgba Int
250 Int
240 Int
230 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'magenta' 'Color'.
--
-- >>> renderColor magenta
-- "rgba(255,0,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWFnZW50YSIvPjwvc3ZnPg==>>
--
magenta :: Color
magenta :: Color
magenta = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
0 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'maroon' 'Color'.
--
-- >>> renderColor maroon
-- "rgba(128,0,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWFyb29uIi8+PC9zdmc+>>
--
maroon :: Color
maroon :: Color
maroon = Int -> Int -> Int -> Double -> Color
rgba Int
128 Int
0 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumaquamarine' 'Color'.
--
-- >>> renderColor mediumaquamarine
-- "rgba(102,205,170,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtYXF1YW1hcmluZSIvPjwvc3ZnPg==>>
--
mediumaquamarine :: Color
mediumaquamarine :: Color
mediumaquamarine = Int -> Int -> Int -> Double -> Color
rgba Int
102 Int
205 Int
170 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumblue' 'Color'.
--
-- >>> renderColor mediumblue
-- "rgba(0,0,205,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtYmx1ZSIvPjwvc3ZnPg==>>
--
mediumblue :: Color
mediumblue :: Color
mediumblue = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
0 Int
205 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumorchid' 'Color'.
--
-- >>> renderColor mediumorchid
-- "rgba(186,85,211,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtb3JjaGlkIi8+PC9zdmc+>>
--
mediumorchid :: Color
mediumorchid :: Color
mediumorchid = Int -> Int -> Int -> Double -> Color
rgba Int
186 Int
85 Int
211 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumpurple' 'Color'.
--
-- >>> renderColor mediumpurple
-- "rgba(147,112,219,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtcHVycGxlIi8+PC9zdmc+>>
--
mediumpurple :: Color
mediumpurple :: Color
mediumpurple = Int -> Int -> Int -> Double -> Color
rgba Int
147 Int
112 Int
219 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumseagreen' 'Color'.
--
-- >>> renderColor mediumseagreen
-- "rgba(60,179,113,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtc2VhZ3JlZW4iLz48L3N2Zz4=>>
--
mediumseagreen :: Color
mediumseagreen :: Color
mediumseagreen = Int -> Int -> Int -> Double -> Color
rgba Int
60 Int
179 Int
113 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumslateblue' 'Color'.
--
-- >>> renderColor mediumslateblue
-- "rgba(123,104,238,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtc2xhdGVibHVlIi8+PC9zdmc+>>
--
mediumslateblue :: Color
mediumslateblue :: Color
mediumslateblue = Int -> Int -> Int -> Double -> Color
rgba Int
123 Int
104 Int
238 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumspringgreen' 'Color'.
--
-- >>> renderColor mediumspringgreen
-- "rgba(0,250,154,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtc3ByaW5nZ3JlZW4iLz48L3N2Zz4=>>
--
mediumspringgreen :: Color
mediumspringgreen :: Color
mediumspringgreen = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
250 Int
154 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumturquoise' 'Color'.
--
-- >>> renderColor mediumturquoise
-- "rgba(72,209,204,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtdHVycXVvaXNlIi8+PC9zdmc+>>
--
mediumturquoise :: Color
mediumturquoise :: Color
mediumturquoise = Int -> Int -> Int -> Double -> Color
rgba Int
72 Int
209 Int
204 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mediumvioletred' 'Color'.
--
-- >>> renderColor mediumvioletred
-- "rgba(199,21,133,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWVkaXVtdmlvbGV0cmVkIi8+PC9zdmc+>>
--
mediumvioletred :: Color
mediumvioletred :: Color
mediumvioletred = Int -> Int -> Int -> Double -> Color
rgba Int
199 Int
21 Int
133 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'midnightblue' 'Color'.
--
-- >>> renderColor midnightblue
-- "rgba(25,25,112,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWlkbmlnaHRibHVlIi8+PC9zdmc+>>
--
midnightblue :: Color
midnightblue :: Color
midnightblue = Int -> Int -> Int -> Double -> Color
rgba Int
25 Int
25 Int
112 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mintcream' 'Color'.
--
-- >>> renderColor mintcream
-- "rgba(245,255,250,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWludGNyZWFtIi8+PC9zdmc+>>
--
mintcream :: Color
mintcream :: Color
mintcream = Int -> Int -> Int -> Double -> Color
rgba Int
245 Int
255 Int
250 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'mistyrose' 'Color'.
--
-- >>> renderColor mistyrose
-- "rgba(255,228,225,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibWlzdHlyb3NlIi8+PC9zdmc+>>
--
mistyrose :: Color
mistyrose :: Color
mistyrose = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
228 Int
225 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'moccasin' 'Color'.
--
-- >>> renderColor moccasin
-- "rgba(255,228,181,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibW9jY2FzaW4iLz48L3N2Zz4=>>
--
moccasin :: Color
moccasin :: Color
moccasin = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
228 Int
181 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'navajowhite' 'Color'.
--
-- >>> renderColor navajowhite
-- "rgba(255,222,173,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibmF2YWpvd2hpdGUiLz48L3N2Zz4=>>
--
navajowhite :: Color
navajowhite :: Color
navajowhite = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
222 Int
173 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'navy' 'Color'.
--
-- >>> renderColor navy
-- "rgba(0,0,128,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ibmF2eSIvPjwvc3ZnPg==>>
--
navy :: Color
navy :: Color
navy = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
0 Int
128 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'oldlace' 'Color'.
--
-- >>> renderColor oldlace
-- "rgba(253,245,230,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ib2xkbGFjZSIvPjwvc3ZnPg==>>
--
oldlace :: Color
oldlace :: Color
oldlace = Int -> Int -> Int -> Double -> Color
rgba Int
253 Int
245 Int
230 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'olive' 'Color'.
--
-- >>> renderColor olive
-- "rgba(128,128,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ib2xpdmUiLz48L3N2Zz4=>>
--
olive :: Color
olive :: Color
olive = Int -> Int -> Int -> Double -> Color
rgba Int
128 Int
128 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'olivedrab' 'Color'.
--
-- >>> renderColor olivedrab
-- "rgba(107,142,35,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ib2xpdmVkcmFiIi8+PC9zdmc+>>
--
olivedrab :: Color
olivedrab :: Color
olivedrab = Int -> Int -> Int -> Double -> Color
rgba Int
107 Int
142 Int
35 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'orange' 'Color'.
--
-- >>> renderColor orange
-- "rgba(255,165,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ib3JhbmdlIi8+PC9zdmc+>>
--
orange :: Color
orange :: Color
orange = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
165 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'orangered' 'Color'.
--
-- >>> renderColor orangered
-- "rgba(255,69,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ib3JhbmdlcmVkIi8+PC9zdmc+>>
--
orangered :: Color
orangered :: Color
orangered = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
69 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'orchid' 'Color'.
--
-- >>> renderColor orchid
-- "rgba(218,112,214,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ib3JjaGlkIi8+PC9zdmc+>>
--
orchid :: Color
orchid :: Color
orchid = Int -> Int -> Int -> Double -> Color
rgba Int
218 Int
112 Int
214 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'palegoldenrod' 'Color'.
--
-- >>> renderColor palegoldenrod
-- "rgba(238,232,170,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGFsZWdvbGRlbnJvZCIvPjwvc3ZnPg==>>
--
palegoldenrod :: Color
palegoldenrod :: Color
palegoldenrod = Int -> Int -> Int -> Double -> Color
rgba Int
238 Int
232 Int
170 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'palegreen' 'Color'.
--
-- >>> renderColor palegreen
-- "rgba(152,251,152,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGFsZWdyZWVuIi8+PC9zdmc+>>
--
palegreen :: Color
palegreen :: Color
palegreen = Int -> Int -> Int -> Double -> Color
rgba Int
152 Int
251 Int
152 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'paleturquoise' 'Color'.
--
-- >>> renderColor paleturquoise
-- "rgba(175,238,238,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGFsZXR1cnF1b2lzZSIvPjwvc3ZnPg==>>
--
paleturquoise :: Color
paleturquoise :: Color
paleturquoise = Int -> Int -> Int -> Double -> Color
rgba Int
175 Int
238 Int
238 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'palevioletred' 'Color'.
--
-- >>> renderColor palevioletred
-- "rgba(219,112,147,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGFsZXZpb2xldHJlZCIvPjwvc3ZnPg==>>
--
palevioletred :: Color
palevioletred :: Color
palevioletred = Int -> Int -> Int -> Double -> Color
rgba Int
219 Int
112 Int
147 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'papayawhip' 'Color'.
--
-- >>> renderColor papayawhip
-- "rgba(255,239,213,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGFwYXlhd2hpcCIvPjwvc3ZnPg==>>
--
papayawhip :: Color
papayawhip :: Color
papayawhip = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
239 Int
213 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'peachpuff' 'Color'.
--
-- >>> renderColor peachpuff
-- "rgba(255,218,185,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGVhY2hwdWZmIi8+PC9zdmc+>>
--
peachpuff :: Color
peachpuff :: Color
peachpuff = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
218 Int
185 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'peru' 'Color'.
--
-- >>> renderColor peru
-- "rgba(205,133,63,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGVydSIvPjwvc3ZnPg==>>
--
peru :: Color
peru :: Color
peru = Int -> Int -> Int -> Double -> Color
rgba Int
205 Int
133 Int
63 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'pink' 'Color'.
--
-- >>> renderColor pink
-- "rgba(255,192,203,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGluayIvPjwvc3ZnPg==>>
--
pink :: Color
pink :: Color
pink = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
192 Int
203 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'plum' 'Color'.
--
-- >>> renderColor plum
-- "rgba(221,160,221,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icGx1bSIvPjwvc3ZnPg==>>
--
plum :: Color
plum :: Color
plum = Int -> Int -> Int -> Double -> Color
rgba Int
221 Int
160 Int
221 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'powderblue' 'Color'.
--
-- >>> renderColor powderblue
-- "rgba(176,224,230,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icG93ZGVyYmx1ZSIvPjwvc3ZnPg==>>
--
powderblue :: Color
powderblue :: Color
powderblue = Int -> Int -> Int -> Double -> Color
rgba Int
176 Int
224 Int
230 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'purple' 'Color'.
--
-- >>> renderColor purple
-- "rgba(128,0,128,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icHVycGxlIi8+PC9zdmc+>>
--
purple :: Color
purple :: Color
purple = Int -> Int -> Int -> Double -> Color
rgba Int
128 Int
0 Int
128 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'red' 'Color'.
--
-- >>> renderColor red
-- "rgba (255,0,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icmVkIi8+PC9zdmc+>>
--
red :: Color
red :: Color
red = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
0 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'rosybrown' 'Color'.
--
-- >>> renderColor rosybrown
-- "rgba(188,143,143,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icm9zeWJyb3duIi8+PC9zdmc+>>
--
rosybrown :: Color
rosybrown :: Color
rosybrown = Int -> Int -> Int -> Double -> Color
rgba Int
188 Int
143 Int
143 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'royalblue' 'Color'.
--
-- >>> renderColor royalblue
-- "rgba(65,105,225,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0icm95YWxibHVlIi8+PC9zdmc+>>
--
royalblue :: Color
royalblue :: Color
royalblue = Int -> Int -> Int -> Double -> Color
rgba Int
65 Int
105 Int
225 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'saddlebrown' 'Color'.
--
-- >>> renderColor saddlebrown
-- "rgba(139,69,19,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2FkZGxlYnJvd24iLz48L3N2Zz4=>>
--
saddlebrown :: Color
saddlebrown :: Color
saddlebrown = Int -> Int -> Int -> Double -> Color
rgba Int
139 Int
69 Int
19 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'salmon' 'Color'.
--
-- >>> renderColor salmon
-- "rgba(250,128,114,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2FsbW9uIi8+PC9zdmc+>>
--
salmon :: Color
salmon :: Color
salmon = Int -> Int -> Int -> Double -> Color
rgba Int
250 Int
128 Int
114 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'sandybrown' 'Color'.
--
-- >>> renderColor sandybrown
-- "rgba(244,164,96,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2FuZHlicm93biIvPjwvc3ZnPg==>>
--
sandybrown :: Color
sandybrown :: Color
sandybrown = Int -> Int -> Int -> Double -> Color
rgba Int
244 Int
164 Int
96 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'seagreen' 'Color'.
--
-- >>> renderColor seagreen
-- "rgba(46,139,87,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2VhZ3JlZW4iLz48L3N2Zz4=>>
--
seagreen :: Color
seagreen :: Color
seagreen = Int -> Int -> Int -> Double -> Color
rgba Int
46 Int
139 Int
87 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'seashell' 'Color'.
--
-- >>> renderColor seashell
-- "rgba(255,245,238,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2Vhc2hlbGwiLz48L3N2Zz4=>>
--
seashell :: Color
seashell :: Color
seashell = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
245 Int
238 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'sienna' 'Color'.
--
-- >>> renderColor sienna
-- "rgba(160,82,45,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2llbm5hIi8+PC9zdmc+>>
--
sienna :: Color
sienna :: Color
sienna = Int -> Int -> Int -> Double -> Color
rgba Int
160 Int
82 Int
45 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'silver' 'Color'.
--
-- >>> renderColor silver
-- "rgba(192,192,192,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2lsdmVyIi8+PC9zdmc+>>
--
silver :: Color
silver :: Color
silver = Int -> Int -> Int -> Double -> Color
rgba Int
192 Int
192 Int
192 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'skyblue' 'Color'.
--
-- >>> renderColor skyblue
-- "rgba(135,206,235,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2t5Ymx1ZSIvPjwvc3ZnPg==>>
--
skyblue :: Color
skyblue :: Color
skyblue = Int -> Int -> Int -> Double -> Color
rgba Int
135 Int
206 Int
235 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'slateblue' 'Color'.
--
-- >>> renderColor slateblue
-- "rgba(106,90,205,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2xhdGVibHVlIi8+PC9zdmc+>>
--
slateblue :: Color
slateblue :: Color
slateblue = Int -> Int -> Int -> Double -> Color
rgba Int
106 Int
90 Int
205 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'slategray' 'Color'.
--
-- >>> renderColor slategray
-- "rgba(112,128,144,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2xhdGVncmF5Ii8+PC9zdmc+>>
--
slategray :: Color
slategray :: Color
slategray = Int -> Int -> Int -> Double -> Color
rgba Int
112 Int
128 Int
144 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'slategrey' 'Color'.
--
-- >>> renderColor slategrey
-- "rgba(112,128,144,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic2xhdGVncmV5Ii8+PC9zdmc+>>
--
slategrey :: Color
slategrey :: Color
slategrey = Int -> Int -> Int -> Double -> Color
rgba Int
112 Int
128 Int
144 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'snow' 'Color'.
--
-- >>> renderColor snow
-- "rgba(255,250,250,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic25vdyIvPjwvc3ZnPg==>>
--
snow :: Color
snow :: Color
snow = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
250 Int
250 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'springgreen' 'Color'.
--
-- >>> renderColor springgreen
-- "rgba(0,255,127,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic3ByaW5nZ3JlZW4iLz48L3N2Zz4=>>
--
springgreen :: Color
springgreen :: Color
springgreen = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
255 Int
127 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'steelblue' 'Color'.
--
-- >>> renderColor steelblue
-- "rgba(70,130,180,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ic3RlZWxibHVlIi8+PC9zdmc+>>
--
steelblue :: Color
steelblue :: Color
steelblue = Int -> Int -> Int -> Double -> Color
rgba Int
70 Int
130 Int
180 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'tan' 'Color'.
--
-- >>> renderColor tan
-- "rgba(210,180,140,1.<<data:image/svg+xml;base64,0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0idGFuIi8+PC9zdmc+>>
--
tan :: Color
tan :: Color
tan = Int -> Int -> Int -> Double -> Color
rgba Int
210 Int
180 Int
140 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'teal' 'Color'.
--
-- >>> renderColor teal
-- "rgba(0,128,128,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0idGVhbCIvPjwvc3ZnPg==>>
--
teal :: Color
teal :: Color
teal = Int -> Int -> Int -> Double -> Color
rgba Int
0 Int
128 Int
128 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'thistle' 'Color'.
--
-- >>> renderColor thistle
-- "rgba(216,191,216,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0idGhpc3RsZSIvPjwvc3ZnPg==>>
--
thistle :: Color
thistle :: Color
thistle = Int -> Int -> Int -> Double -> Color
rgba Int
216 Int
191 Int
216 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'tomato' 'Color'.
--
-- >>> renderColor tomato
-- "rgba(255,99,71,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0idG9tYXRvIi8+PC9zdmc+>>
--
tomato :: Color
tomato :: Color
tomato = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
99 Int
71 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'turquoise' 'Color'.
--
-- >>> renderColor turquoise
-- "rgba(64,224,208,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0idHVycXVvaXNlIi8+PC9zdmc+>>
--
turquoise :: Color
turquoise :: Color
turquoise = Int -> Int -> Int -> Double -> Color
rgba Int
64 Int
224 Int
208 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'violet' 'Color'.
--
-- >>> renderColor violet
-- "rgba(238,130,238,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0idmlvbGV0Ii8+PC9zdmc+>>
--
violet :: Color
violet :: Color
violet = Int -> Int -> Int -> Double -> Color
rgba Int
238 Int
130 Int
238 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'wheat' 'Color'.
--
-- >>> renderColor wheat
-- "rgba(245,222,179,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0id2hlYXQiLz48L3N2Zz4=>>
--
wheat :: Color
wheat :: Color
wheat = Int -> Int -> Int -> Double -> Color
rgba Int
245 Int
222 Int
179 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'white' 'Color'.
--
-- >>> renderColor white
-- "rgba(255,255,255,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0id2hpdGUiLz48L3N2Zz4=>>
--
white :: Color
white :: Color
white = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
255 Int
255 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'whitesmoke' 'Color'.
--
-- >>> renderColor whitesmoke
-- "rgba(245,245,245,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0id2hpdGVzbW9rZSIvPjwvc3ZnPg==>>
--
whitesmoke :: Color
whitesmoke :: Color
whitesmoke = Int -> Int -> Int -> Double -> Color
rgba Int
245 Int
245 Int
245 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'yellow' 'Color'.
--
-- >>> renderColor yellow
-- "rgba(255,255,0,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ieWVsbG93Ii8+PC9zdmc+>>
--
yellow :: Color
yellow :: Color
yellow = Int -> Int -> Int -> Double -> Color
rgba Int
255 Int
255 Int
0 Double
1
-----------------------------------------------------------------------------
-- | Smart constructor for the 'yellowgreen' 'Color'.
--
-- >>> renderColor yellowgreen
-- "rgba(154,205,50,1.0)"
--
-- <<data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHdpZHRoPSIxMDAiIGhlaWdodD0iMTAwIj48cmVjdCB3aWR0aD0iMTAwIiBoZWlnaHQ9IjEwMCIgZmlsbD0ieWVsbG93Z3JlZW4iLz48L3N2Zz4=>>
--
yellowgreen :: Color
yellowgreen :: Color
yellowgreen = Int -> Int -> Int -> Double -> Color
rgba Int
154 Int
205 Int
50 Double
1
-----------------------------------------------------------------------------