rainbow-0.28.0.0: Print text to terminal with colors and effects

Safe HaskellNone
LanguageHaskell2010

Rainbow.Types

Description

All the main types in Rainbow. Using this module you can specify that you want different formatting for 8- and 256-color terminals. Many of the names in this module conflict with the names in Rainbow, so it's probably best to import this module qualified.

Synopsis

Documentation

newtype Color a Source #

A color; a Nothing value means that the terminal's default color is used. The type of the Maybe generally will be an Enum8 to represent one of 8 colors, or a Word8 to represent one of 256 colors.

Constructors

Color (Maybe a) 

Instances

Functor Color Source # 

Methods

fmap :: (a -> b) -> Color a -> Color b #

(<$) :: a -> Color b -> Color a #

Foldable Color Source # 

Methods

fold :: Monoid m => Color m -> m #

foldMap :: Monoid m => (a -> m) -> Color a -> m #

foldr :: (a -> b -> b) -> b -> Color a -> b #

foldr' :: (a -> b -> b) -> b -> Color a -> b #

foldl :: (b -> a -> b) -> b -> Color a -> b #

foldl' :: (b -> a -> b) -> b -> Color a -> b #

foldr1 :: (a -> a -> a) -> Color a -> a #

foldl1 :: (a -> a -> a) -> Color a -> a #

toList :: Color a -> [a] #

null :: Color a -> Bool #

length :: Color a -> Int #

elem :: Eq a => a -> Color a -> Bool #

maximum :: Ord a => Color a -> a #

minimum :: Ord a => Color a -> a #

sum :: Num a => Color a -> a #

product :: Num a => Color a -> a #

Traversable Color Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Color a -> f (Color b) #

sequenceA :: Applicative f => Color (f a) -> f (Color a) #

mapM :: Monad m => (a -> m b) -> Color a -> m (Color b) #

sequence :: Monad m => Color (m a) -> m (Color a) #

Eq a => Eq (Color a) Source # 

Methods

(==) :: Color a -> Color a -> Bool #

(/=) :: Color a -> Color a -> Bool #

Ord a => Ord (Color a) Source # 

Methods

compare :: Color a -> Color a -> Ordering #

(<) :: Color a -> Color a -> Bool #

(<=) :: Color a -> Color a -> Bool #

(>) :: Color a -> Color a -> Bool #

(>=) :: Color a -> Color a -> Bool #

max :: Color a -> Color a -> Color a #

min :: Color a -> Color a -> Color a #

Show a => Show (Color a) Source # 

Methods

showsPrec :: Int -> Color a -> ShowS #

show :: Color a -> String #

showList :: [Color a] -> ShowS #

Generic (Color a) Source # 

Associated Types

type Rep (Color a) :: * -> * #

Methods

from :: Color a -> Rep (Color a) x #

to :: Rep (Color a) x -> Color a #

Monoid (Color a) Source #

Takes the last non-Nothing Color. mempty is no color.

Methods

mempty :: Color a #

mappend :: Color a -> Color a -> Color a #

mconcat :: [Color a] -> Color a #

type Rep (Color a) Source # 
type Rep (Color a) = D1 (MetaData "Color" "Rainbow.Types" "rainbow-0.28.0.0-HC43teMlUhD6MGJmXYIKIC" True) (C1 (MetaCons "Color" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))

data Enum8 Source #

A simple enumeration for eight values. Represents eight colors.

Constructors

E0 
E1 
E2 
E3 
E4 
E5 
E6 
E7 

Instances

Bounded Enum8 Source # 
Enum Enum8 Source # 
Eq Enum8 Source # 

Methods

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

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

Ord Enum8 Source # 

Methods

compare :: Enum8 -> Enum8 -> Ordering #

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

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

(>) :: Enum8 -> Enum8 -> Bool #

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

max :: Enum8 -> Enum8 -> Enum8 #

min :: Enum8 -> Enum8 -> Enum8 #

Show Enum8 Source # 

Methods

showsPrec :: Int -> Enum8 -> ShowS #

show :: Enum8 -> String #

showList :: [Enum8] -> ShowS #

Generic Enum8 Source # 

Associated Types

type Rep Enum8 :: * -> * #

Methods

from :: Enum8 -> Rep Enum8 x #

to :: Rep Enum8 x -> Enum8 #

type Rep Enum8 Source # 
type Rep Enum8 = D1 (MetaData "Enum8" "Rainbow.Types" "rainbow-0.28.0.0-HC43teMlUhD6MGJmXYIKIC" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "E0" PrefixI False) U1) (C1 (MetaCons "E1" PrefixI False) U1)) ((:+:) (C1 (MetaCons "E2" PrefixI False) U1) (C1 (MetaCons "E3" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "E4" PrefixI False) U1) (C1 (MetaCons "E5" PrefixI False) U1)) ((:+:) (C1 (MetaCons "E6" PrefixI False) U1) (C1 (MetaCons "E7" PrefixI False) U1))))

data Format Source #

Text formatting such as bold, italic, etc.

Constructors

Format 

Instances

Eq Format Source # 

Methods

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

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

Ord Format Source # 
Show Format Source # 
Generic Format Source # 

Associated Types

type Rep Format :: * -> * #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

Monoid Format Source #

For each field, the resulting field is True if either field is True. For mempty, every field is False.

type Rep Format Source # 

data Style a Source #

The foreground and background color, and the Format. This represents all colors and formatting attributes for either an 8- or 256-color terminal.

Constructors

Style 

Fields

Instances

Functor Style Source # 

Methods

fmap :: (a -> b) -> Style a -> Style b #

(<$) :: a -> Style b -> Style a #

Foldable Style Source # 

Methods

fold :: Monoid m => Style m -> m #

foldMap :: Monoid m => (a -> m) -> Style a -> m #

foldr :: (a -> b -> b) -> b -> Style a -> b #

foldr' :: (a -> b -> b) -> b -> Style a -> b #

foldl :: (b -> a -> b) -> b -> Style a -> b #

foldl' :: (b -> a -> b) -> b -> Style a -> b #

foldr1 :: (a -> a -> a) -> Style a -> a #

foldl1 :: (a -> a -> a) -> Style a -> a #

toList :: Style a -> [a] #

null :: Style a -> Bool #

length :: Style a -> Int #

elem :: Eq a => a -> Style a -> Bool #

maximum :: Ord a => Style a -> a #

minimum :: Ord a => Style a -> a #

sum :: Num a => Style a -> a #

product :: Num a => Style a -> a #

Traversable Style Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Style a -> f (Style b) #

sequenceA :: Applicative f => Style (f a) -> f (Style a) #

mapM :: Monad m => (a -> m b) -> Style a -> m (Style b) #

sequence :: Monad m => Style (m a) -> m (Style a) #

Eq a => Eq (Style a) Source # 

Methods

(==) :: Style a -> Style a -> Bool #

(/=) :: Style a -> Style a -> Bool #

Ord a => Ord (Style a) Source # 

Methods

compare :: Style a -> Style a -> Ordering #

(<) :: Style a -> Style a -> Bool #

(<=) :: Style a -> Style a -> Bool #

(>) :: Style a -> Style a -> Bool #

(>=) :: Style a -> Style a -> Bool #

max :: Style a -> Style a -> Style a #

min :: Style a -> Style a -> Style a #

Show a => Show (Style a) Source # 

Methods

showsPrec :: Int -> Style a -> ShowS #

show :: Style a -> String #

showList :: [Style a] -> ShowS #

Generic (Style a) Source # 

Associated Types

type Rep (Style a) :: * -> * #

Methods

from :: Style a -> Rep (Style a) x #

to :: Rep (Style a) x -> Style a #

Monoid (Style a) Source #

Uses the underlying Monoid instances for Color and Format.

Methods

mempty :: Style a #

mappend :: Style a -> Style a -> Style a #

mconcat :: [Style a] -> Style a #

type Rep (Style a) Source # 

format :: forall a. Lens' (Style a) Format Source #

fore :: forall a. Lens' (Style a) (Color a) Source #

back :: forall a. Lens' (Style a) (Color a) Source #

data Scheme Source #

Holds the Style for both 8- and 256-color terminals.

Constructors

Scheme 

Instances

Eq Scheme Source # 

Methods

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

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

Ord Scheme Source # 
Show Scheme Source # 
Generic Scheme Source # 

Associated Types

type Rep Scheme :: * -> * #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

Monoid Scheme Source # 
type Rep Scheme Source # 
type Rep Scheme = D1 (MetaData "Scheme" "Rainbow.Types" "rainbow-0.28.0.0-HC43teMlUhD6MGJmXYIKIC" False) (C1 (MetaCons "Scheme" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_style8") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Style Enum8))) (S1 (MetaSel (Just Symbol "_style256") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Style Word8)))))

data Chunk a Source #

A chunk is some textual data coupled with a description of what color the text is, attributes like whether it is bold or underlined, etc. The chunk knows what foreground and background colors and what attributes to use for both an 8 color terminal and a 256 color terminal.

Constructors

Chunk 

Fields

Instances

Functor Chunk Source # 

Methods

fmap :: (a -> b) -> Chunk a -> Chunk b #

(<$) :: a -> Chunk b -> Chunk a #

Foldable Chunk Source # 

Methods

fold :: Monoid m => Chunk m -> m #

foldMap :: Monoid m => (a -> m) -> Chunk a -> m #

foldr :: (a -> b -> b) -> b -> Chunk a -> b #

foldr' :: (a -> b -> b) -> b -> Chunk a -> b #

foldl :: (b -> a -> b) -> b -> Chunk a -> b #

foldl' :: (b -> a -> b) -> b -> Chunk a -> b #

foldr1 :: (a -> a -> a) -> Chunk a -> a #

foldl1 :: (a -> a -> a) -> Chunk a -> a #

toList :: Chunk a -> [a] #

null :: Chunk a -> Bool #

length :: Chunk a -> Int #

elem :: Eq a => a -> Chunk a -> Bool #

maximum :: Ord a => Chunk a -> a #

minimum :: Ord a => Chunk a -> a #

sum :: Num a => Chunk a -> a #

product :: Num a => Chunk a -> a #

Traversable Chunk Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Chunk a -> f (Chunk b) #

sequenceA :: Applicative f => Chunk (f a) -> f (Chunk a) #

mapM :: Monad m => (a -> m b) -> Chunk a -> m (Chunk b) #

sequence :: Monad m => Chunk (m a) -> m (Chunk a) #

Eq a => Eq (Chunk a) Source # 

Methods

(==) :: Chunk a -> Chunk a -> Bool #

(/=) :: Chunk a -> Chunk a -> Bool #

Ord a => Ord (Chunk a) Source # 

Methods

compare :: Chunk a -> Chunk a -> Ordering #

(<) :: Chunk a -> Chunk a -> Bool #

(<=) :: Chunk a -> Chunk a -> Bool #

(>) :: Chunk a -> Chunk a -> Bool #

(>=) :: Chunk a -> Chunk a -> Bool #

max :: Chunk a -> Chunk a -> Chunk a #

min :: Chunk a -> Chunk a -> Chunk a #

Show a => Show (Chunk a) Source # 

Methods

showsPrec :: Int -> Chunk a -> ShowS #

show :: Chunk a -> String #

showList :: [Chunk a] -> ShowS #

Generic (Chunk a) Source # 

Associated Types

type Rep (Chunk a) :: * -> * #

Methods

from :: Chunk a -> Rep (Chunk a) x #

to :: Rep (Chunk a) x -> Chunk a #

Monoid a => Monoid (Chunk a) Source #

Uses the underlying Monoid instances for the Style and for the particular _yarn. Therefore mempty will have no formatting and no colors and will generally have no text, though whether or not there is any text depends on the mempty for the type of the _yarn.

Methods

mempty :: Chunk a #

mappend :: Chunk a -> Chunk a -> Chunk a #

mconcat :: [Chunk a] -> Chunk a #

type Rep (Chunk a) Source # 
type Rep (Chunk a) = D1 (MetaData "Chunk" "Rainbow.Types" "rainbow-0.28.0.0-HC43teMlUhD6MGJmXYIKIC" False) (C1 (MetaCons "Chunk" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_scheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scheme)) (S1 (MetaSel (Just Symbol "_yarn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

chunk :: a -> Chunk a Source #

Creates a Chunk with no formatting and with the given text.

yarn :: forall a a. Lens (Chunk a) (Chunk a) a a Source #

scheme :: forall a. Lens' (Chunk a) Scheme Source #

data Radiant Source #

Stores colors that may affect 8-color terminals, 256-color terminals, both, or neither.

Constructors

Radiant 

Instances

Eq Radiant Source # 

Methods

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

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

Ord Radiant Source # 
Show Radiant Source # 
Generic Radiant Source # 

Associated Types

type Rep Radiant :: * -> * #

Methods

from :: Radiant -> Rep Radiant x #

to :: Rep Radiant x -> Radiant #

Monoid Radiant Source #

Uses the underlying Monoid instance for the Colors. Thus the last non-Nothing Color is used. This can be useful to specify one color for 8-color terminals and a different color for 256-color terminals.

type Rep Radiant Source # 
type Rep Radiant = D1 (MetaData "Radiant" "Rainbow.Types" "rainbow-0.28.0.0-HC43teMlUhD6MGJmXYIKIC" False) (C1 (MetaCons "Radiant" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_color8") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Color Enum8))) (S1 (MetaSel (Just Symbol "_color256") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Color Word8)))))