HaTeX-3.20.0.1: The Haskell LaTeX library.

Safe HaskellSafe
LanguageHaskell2010

Text.LaTeX.Packages.Color

Contents

Description

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.

Synopsis

Color package

pcolor :: PackageName Source #

The pcolor package.

usepackage [] pcolor

Package options

monochrome :: LaTeXC l => l Source #

To convert all colour commands to black and white, for previewers that cannot handle colour.

Types

data Color Source #

Basic colors.

Constructors

Red 
Green 
Blue 
Yellow 
Cyan 
Magenta 
Black 
White 
Instances
Show Color Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Render Color Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

Methods

render :: Color -> Text Source #

data ColorModel Source #

Specify your own color using one of the different color models.

Constructors

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 
Instances
Show ColorModel Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

Render ColorModel Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

data ColSpec Source #

Color specification.

Instances
Show ColSpec Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

Render ColSpec Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

Methods

render :: ColSpec -> Text Source #

Words

RGB255 colors are determined by three parameters of the Word8 type. Values of type Word8 lie within 0 and 255.

data Word8 #

8-bit unsigned integer type

Instances
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word8

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word8 -> c Word8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 #

toConstr :: Word8 -> Constr #

dataTypeOf :: Word8 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word8) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word8) #

gmapT :: (forall b. Data b => b -> b) -> Word8 -> Word8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

Function Word8 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word8 -> b) -> Word8 :-> b #

Arbitrary Word8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Word8 #

shrink :: Word8 -> [Word8] #

CoArbitrary Word8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Word8 -> Gen b -> Gen b #

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Random Word8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] #

randoms :: RandomGen g => g -> [Word8] #

randomRIO :: (Word8, Word8) -> IO Word8 #

randomIO :: IO Word8 #

Pretty Word8 
Instance details

Defined in Text.PrettyPrint.Free.Internal

Methods

pretty :: Word8 -> Doc e #

prettyList :: [Word8] -> Doc e #

Render Word8 Source # 
Instance details

Defined in Text.LaTeX.Base.Render

Methods

render :: Word8 -> Text Source #

Commands

pagecolor :: LaTeXC l => ColSpec -> l Source #

Set the background color for the current and following pages.

color :: LaTeXC l => ColSpec -> l Source #

Switch to a new text color.

textcolor :: LaTeXC l => ColSpec -> l -> l Source #

Set the text of its argument in the given colour.

colorbox :: LaTeXC l => ColSpec -> l -> l Source #

Put its argument in a box with the given colour as background.

fcolorbox :: LaTeXC l => ColSpec -> ColSpec -> l -> l Source #

Application of fcolorbox cs1 cs2 l put l in a framed box with cs1 as frame color and cs2 as background color.

normalcolor :: LaTeXC l => l Source #

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.