Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Text.LaTeX.Packages.Color
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
- pcolor :: PackageName
- monochrome :: LaTeXC l => l
- dvipsnames :: LaTeXC l => l
- nodvipsnames :: LaTeXC l => l
- usenames :: LaTeXC l => l
- data Color
- 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
- data ColorModel
- data ColSpec
- data Word8
- pagecolor :: LaTeXC l => ColSpec -> l
- color :: LaTeXC l => ColSpec -> l
- textcolor :: LaTeXC l => ColSpec -> l -> l
- colorbox :: LaTeXC l => ColSpec -> l -> l
- fcolorbox :: LaTeXC l => ColSpec -> ColSpec -> l -> l
- normalcolor :: LaTeXC l => l
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.
dvipsnames :: LaTeXC l => l Source #
nodvipsnames :: LaTeXC l => l Source #
Types
Basic colors.
Instances
Other predefined colors.
Constructors
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
Render ColorModel Source # | |
Defined in Text.LaTeX.Packages.Color | |
Show ColorModel Source # | |
Defined in Text.LaTeX.Packages.Color Methods showsPrec :: Int -> ColorModel -> ShowS # show :: ColorModel -> String # showList :: [ColorModel] -> ShowS # |
Color specification.
Constructors
DefColor Color | |
ModColor ColorModel | |
DvipsColor ColorName |
Words
RGB255 colors are determined by three parameters of the Word8
type.
Values of type Word8
lie within 0 and 255.
8-bit unsigned integer type
Instances
Render Word8 Source # | |
Arbitrary Word8 | |
CoArbitrary Word8 | |
Defined in Test.QuickCheck.Arbitrary Methods coarbitrary :: Word8 -> Gen b -> Gen b # | |
Function Word8 | |
Data Word8 | Since: base-4.0.0.0 |
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 # 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 :: forall r r'. (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 # | |
Bits Word8 | Since: base-2.1 |
Defined in GHC.Word Methods (.&.) :: Word8 -> Word8 -> Word8 # (.|.) :: Word8 -> Word8 -> Word8 # xor :: Word8 -> Word8 -> Word8 # complement :: Word8 -> Word8 # shift :: Word8 -> Int -> Word8 # rotate :: Word8 -> Int -> Word8 # setBit :: Word8 -> Int -> Word8 # clearBit :: Word8 -> Int -> Word8 # complementBit :: Word8 -> Int -> Word8 # testBit :: Word8 -> Int -> Bool # bitSizeMaybe :: Word8 -> Maybe Int # shiftL :: Word8 -> Int -> Word8 # unsafeShiftL :: Word8 -> Int -> Word8 # shiftR :: Word8 -> Int -> Word8 # unsafeShiftR :: Word8 -> Int -> Word8 # rotateL :: Word8 -> Int -> Word8 # | |
FiniteBits Word8 | Since: base-4.6.0.0 |
Defined in GHC.Word Methods finiteBitSize :: Word8 -> Int # countLeadingZeros :: Word8 -> Int # countTrailingZeros :: Word8 -> Int # | |
Bounded Word8 | Since: base-2.1 |
Enum Word8 | Since: base-2.1 |
Ix Word8 | Since: base-2.1 |
Num Word8 | Since: base-2.1 |
Read Word8 | Since: base-2.1 |
Integral Word8 | Since: base-2.1 |
Real Word8 | Since: base-2.1 |
Defined in GHC.Word Methods toRational :: Word8 -> Rational # | |
Show Word8 | Since: base-2.1 |
NFData Word8 | |
Defined in Control.DeepSeq | |
Eq Word8 | Since: base-2.1 |
Ord Word8 | Since: base-2.1 |
Hashable Word8 | |
Defined in Data.Hashable.Class | |
Pretty Word8 | |
Defined in Prettyprinter.Internal | |
Random Word8 | |
Uniform Word8 | |
Defined in System.Random.Internal Methods uniformM :: StatefulGen g m => g -> m Word8 # | |
UniformRange Word8 | |
Defined in System.Random.Internal | |
Lift Word8 | |
Commands
pagecolor :: LaTeXC l => ColSpec -> l Source #
Set the background color for the current and following pages.
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.