{-# LANGUAGE OverloadedStrings, CPP #-}

-- | Make your documents colorful using this module.
--
--   Different functionalities are provided, like changing the color of
--   the text and the paper, or creating colorful boxes.
module Text.LaTeX.Packages.Color
 ( -- * Color package
   pcolor
   -- * Package options
 , monochrome
 , dvipsnames
 , nodvipsnames
 , usenames
   -- * Types
 , Color (..)
 , ColorName (..)
 , ColorModel (..)
 , ColSpec (..)
   -- * Words
   -- | RGB255 colors are determined by three parameters of the 'Word8' type.
   --   Values of type 'Word8' lie within 0 and 255.
 , Word8
   -- * Commands
 , pagecolor
 , color
 , textcolor
 , colorbox , fcolorbox
 , normalcolor
   ) where

#if !MIN_VERSION_base(4,11,0)
import Text.LaTeX.Base.Syntax ((<>))
#endif
import Text.LaTeX.Base.Class
import Text.LaTeX.Base.Render
import Text.LaTeX.Base.Types
--
import Data.Text (toLower)
import Data.Word (Word8)

-- | The 'pcolor' package.
--
-- > usepackage [] pcolor
pcolor :: PackageName
pcolor :: PackageName
pcolor = PackageName
"color"

-- | To convert all colour commands to black and white,
--   for previewers that cannot handle colour.
monochrome :: LaTeXC l => l
monochrome :: l
monochrome = l
"monochrome"

dvipsnames :: LaTeXC l => l
dvipsnames :: l
dvipsnames = l
"dvipsnames"

nodvipsnames :: LaTeXC l => l
nodvipsnames :: l
nodvipsnames = l
"nodvipsnames"

usenames :: LaTeXC l => l
usenames :: l
usenames = l
"usenames"

-- | Color specification.
data ColSpec =
   DefColor Color
 | ModColor ColorModel
 | DvipsColor ColorName
   deriving Int -> ColSpec -> ShowS
[ColSpec] -> ShowS
ColSpec -> PackageName
(Int -> ColSpec -> ShowS)
-> (ColSpec -> PackageName) -> ([ColSpec] -> ShowS) -> Show ColSpec
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [ColSpec] -> ShowS
$cshowList :: [ColSpec] -> ShowS
show :: ColSpec -> PackageName
$cshow :: ColSpec -> PackageName
showsPrec :: Int -> ColSpec -> ShowS
$cshowsPrec :: Int -> ColSpec -> ShowS
Show

-- | Basic colors.
data Color =
   Red
 | Green
 | Blue
 | Yellow
 | Cyan
 | Magenta
 | Black
 | White
   deriving Int -> Color -> ShowS
[Color] -> ShowS
Color -> PackageName
(Int -> Color -> ShowS)
-> (Color -> PackageName) -> ([Color] -> ShowS) -> Show Color
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [Color] -> ShowS
$cshowList :: [Color] -> ShowS
show :: Color -> PackageName
$cshow :: Color -> PackageName
showsPrec :: Int -> Color -> ShowS
$cshowsPrec :: Int -> Color -> ShowS
Show

-- | Specify your own color using one of the different color models.
data ColorModel =
   RGB Float Float Float
     -- ^ Each parameter determines the proportion of red, green and
     --   blue, with a value within the [0,1] interval.
 | RGB255 Word8 Word8 Word8
 | GrayM Float
     -- ^ Grayscale, from 0 (black) to 1 (white).
 | HTML String
 | CMYK Float Float Float Float
   deriving Int -> ColorModel -> ShowS
[ColorModel] -> ShowS
ColorModel -> PackageName
(Int -> ColorModel -> ShowS)
-> (ColorModel -> PackageName)
-> ([ColorModel] -> ShowS)
-> Show ColorModel
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [ColorModel] -> ShowS
$cshowList :: [ColorModel] -> ShowS
show :: ColorModel -> PackageName
$cshow :: ColorModel -> PackageName
showsPrec :: Int -> ColorModel -> ShowS
$cshowsPrec :: Int -> ColorModel -> ShowS
Show

-- | Other predefined colors.
data ColorName =
   Apricot       | Aquamarine  | Bittersweet
 | BlueGreen     | BlueViolet  | BrickRed
 | Brown         | BurntOrange | CadetBlue
 | CarnationPink | Cerulean    | CornflowerBlue
 | Dandelion     | DarkOrchid  | Emerald
 | ForestGreen   | Fuchsia     | Goldenrod
 | Gray          | GreenYellow | JungleGreen
 | Lavender      | LimeGreen   | Mahogany
 | Maroon        | Melon       | MidnightBlue
 | Mulberry      | NavyBlue    | OliveGreen
 | Orange        | OrangeRed   | Orchid
 | Peach         | Periwinkle  | PineGreen
 | Plum          | ProcessBlue | Purple
 | RawSienna     | RedOrange   | RedViolet
 | Rhodamine     | RoyalBlue   | RubineRed
 | Salmon        | SeaGreen    | Sepia
 | SkyBlue       | SpringGreen | Tan
 | TealBlue      | Thistle     | Turquoise
 | Violet        | VioletRed   | WildStrawberry
 | YellowGreen   | YellowOrange
   deriving Int -> ColorName -> ShowS
[ColorName] -> ShowS
ColorName -> PackageName
(Int -> ColorName -> ShowS)
-> (ColorName -> PackageName)
-> ([ColorName] -> ShowS)
-> Show ColorName
forall a.
(Int -> a -> ShowS)
-> (a -> PackageName) -> ([a] -> ShowS) -> Show a
showList :: [ColorName] -> ShowS
$cshowList :: [ColorName] -> ShowS
show :: ColorName -> PackageName
$cshow :: ColorName -> PackageName
showsPrec :: Int -> ColorName -> ShowS
$cshowsPrec :: Int -> ColorName -> ShowS
Show

instance Render Color where
 render :: Color -> Text
render = Text -> Text
toLower (Text -> Text) -> (Color -> Text) -> Color -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> Text
forall a. IsString a => PackageName -> a
fromString (PackageName -> Text) -> (Color -> PackageName) -> Color -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color -> PackageName
forall a. Show a => a -> PackageName
show

instance Render ColorModel where
 render :: ColorModel -> Text
render (RGB Float
r Float
g Float
b) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"[rgb]{" , [Float] -> Text
forall a. Render a => [a] -> Text
renderCommas [Float
r,Float
g,Float
b] , Text
"}" ]
 render (RGB255 Word8
r Word8
g Word8
b) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"[RGB]{" , [Word8] -> Text
forall a. Render a => [a] -> Text
renderCommas [Word8
r,Word8
g,Word8
b] , Text
"}" ]
 render (GrayM Float
k) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"[gray]{" , Float -> Text
forall a. Render a => a -> Text
render Float
k , Text
"}"]
 render (HTML PackageName
str) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"[HTML]{" , PackageName -> Text
forall a. IsString a => PackageName -> a
fromString PackageName
str , Text
"}" ]
 render (CMYK Float
c Float
m Float
y Float
k) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"[cmyk]{" , [Float] -> Text
forall a. Render a => [a] -> Text
renderCommas [Float
c,Float
m,Float
y,Float
k] , Text
"}" ]

instance Render ColorName where
 render :: ColorName -> Text
render = PackageName -> Text
forall a. IsString a => PackageName -> a
fromString (PackageName -> Text)
-> (ColorName -> PackageName) -> ColorName -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColorName -> PackageName
forall a. Show a => a -> PackageName
show

instance Render ColSpec where
 render :: ColSpec -> Text
render (DefColor Color
c)   = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"{" , Color -> Text
forall a. Render a => a -> Text
render Color
c , Text
"}" ]
 render (ModColor ColorModel
cm)  = ColorModel -> Text
forall a. Render a => a -> Text
render ColorModel
cm
 render (DvipsColor ColorName
c) = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"{" , ColorName -> Text
forall a. Render a => a -> Text
render ColorName
c , Text
"}" ]

-- Commands

-- | Set the background color for the current and following pages.
pagecolor :: LaTeXC l => ColSpec -> l
pagecolor :: ColSpec -> l
pagecolor = (PackageName -> l
forall l. LaTeXC l => PackageName -> l
commS PackageName
"pagecolor" l -> l -> l
forall a. Semigroup a => a -> a -> a
<>) (l -> l) -> (ColSpec -> l) -> ColSpec -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColSpec -> l
forall a l. (Render a, LaTeXC l) => a -> l
rendertex

-- | Switch to a new text color.
color :: LaTeXC l => ColSpec -> l
color :: ColSpec -> l
color = (PackageName -> l
forall l. LaTeXC l => PackageName -> l
commS PackageName
"color" l -> l -> l
forall a. Semigroup a => a -> a -> a
<>) (l -> l) -> (ColSpec -> l) -> ColSpec -> l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColSpec -> l
forall a l. (Render a, LaTeXC l) => a -> l
rendertex

-- | Set the text of its argument in the given colour.
textcolor :: LaTeXC l => ColSpec -> l -> l
textcolor :: ColSpec -> l -> l
textcolor ColSpec
cs l
l = PackageName -> l
forall l. LaTeXC l => PackageName -> l
commS PackageName
"textcolor" l -> l -> l
forall a. Semigroup a => a -> a -> a
<> ColSpec -> l
forall a l. (Render a, LaTeXC l) => a -> l
rendertex ColSpec
cs
              l -> l -> l
forall a. Semigroup a => a -> a -> a
<> l -> l
forall l. LaTeXC l => l -> l
braces l
l

-- | Put its argument in a box with the given colour as background.
colorbox :: LaTeXC l => ColSpec -> l -> l
colorbox :: ColSpec -> l -> l
colorbox ColSpec
cs l
l = PackageName -> l
forall l. LaTeXC l => PackageName -> l
commS PackageName
"colorbox" l -> l -> l
forall a. Semigroup a => a -> a -> a
<> ColSpec -> l
forall a l. (Render a, LaTeXC l) => a -> l
rendertex ColSpec
cs
             l -> l -> l
forall a. Semigroup a => a -> a -> a
<> l -> l
forall l. LaTeXC l => l -> l
braces l
l

-- | Application of @fcolorbox cs1 cs2 l@ put @l@ in a framed box with
--   @cs1@ as frame color and @cs2@ as background color.
fcolorbox :: LaTeXC l => ColSpec -> ColSpec -> l -> l
fcolorbox :: ColSpec -> ColSpec -> l -> l
fcolorbox ColSpec
cs1 ColSpec
cs2 l
l =
    PackageName -> l
forall l. LaTeXC l => PackageName -> l
commS PackageName
"fcolorbox" l -> l -> l
forall a. Semigroup a => a -> a -> a
<> ColSpec -> l
forall a l. (Render a, LaTeXC l) => a -> l
rendertex ColSpec
cs1
                      l -> l -> l
forall a. Semigroup a => a -> a -> a
<> ColSpec -> l
forall a l. (Render a, LaTeXC l) => a -> l
rendertex ColSpec
cs2
 l -> l -> l
forall a. Semigroup a => a -> a -> a
<> l -> l
forall l. LaTeXC l => l -> l
braces l
l

-- | Switch to the colour that was active at the end of the preamble.
--   Thus, placing a 'color' command in the preamble can change the
--   standard colour of the whole document.
normalcolor :: LaTeXC l => l
normalcolor :: l
normalcolor = PackageName -> l
forall l. LaTeXC l => PackageName -> l
comm0 PackageName
"normalcolor"