rainbow-0.34.2.2: 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 # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Foldable Color Source # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Ord a => Ord (Color a) Source # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

Methods

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

show :: Color a -> String #

showList :: [Color a] -> ShowS #

Generic (Color a) Source # 
Instance details

Defined in Rainbow.Types

Associated Types

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

Methods

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

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

Semigroup (Color a) Source # 
Instance details

Defined in Rainbow.Types

Methods

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

sconcat :: NonEmpty (Color a) -> Color a #

stimes :: Integral b => b -> Color a -> Color a #

Monoid (Color a) Source #

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

Instance details

Defined in Rainbow.Types

Methods

mempty :: Color a #

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

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

type Rep (Color a) Source # 
Instance details

Defined in Rainbow.Types

type Rep (Color a) = D1 (MetaData "Color" "Rainbow.Types" "rainbow-0.34.2.2-1ah5PZE6w84FK2I3qiFqVN" True) (C1 (MetaCons "Color" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in Rainbow.Types

Enum Enum8 Source # 
Instance details

Defined in Rainbow.Types

Eq Enum8 Source # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Ord Enum8 Source # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

Methods

showsPrec :: Int -> Enum8 -> ShowS #

show :: Enum8 -> String #

showList :: [Enum8] -> ShowS #

Generic Enum8 Source # 
Instance details

Defined in Rainbow.Types

Associated Types

type Rep Enum8 :: Type -> Type #

Methods

from :: Enum8 -> Rep Enum8 x #

to :: Rep Enum8 x -> Enum8 #

type Rep Enum8 Source # 
Instance details

Defined in Rainbow.Types

type Rep Enum8 = D1 (MetaData "Enum8" "Rainbow.Types" "rainbow-0.34.2.2-1ah5PZE6w84FK2I3qiFqVN" False) (((C1 (MetaCons "E0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "E1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "E2" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "E3" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "E4" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "E5" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "E6" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "E7" PrefixI False) (U1 :: Type -> Type))))

data Format Source #

Text formatting such as bold, italic, etc.

Constructors

Format 
Instances
Eq Format Source # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Ord Format Source # 
Instance details

Defined in Rainbow.Types

Show Format Source # 
Instance details

Defined in Rainbow.Types

Generic Format Source # 
Instance details

Defined in Rainbow.Types

Associated Types

type Rep Format :: Type -> Type #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

Semigroup Format Source # 
Instance details

Defined in Rainbow.Types

Monoid Format Source #

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

Instance details

Defined in Rainbow.Types

type Rep Format Source # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Foldable Style Source # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Ord a => Ord (Style a) Source # 
Instance details

Defined in Rainbow.Types

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 # 
Instance details

Defined in Rainbow.Types

Methods

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

show :: Style a -> String #

showList :: [Style a] -> ShowS #

Generic (Style a) Source # 
Instance details

Defined in Rainbow.Types

Associated Types

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

Methods

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

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

Semigroup (Style a) Source # 
Instance details

Defined in Rainbow.Types

Methods

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

sconcat :: NonEmpty (Style a) -> Style a #

stimes :: Integral b => b -> Style a -> Style a #

Monoid (Style a) Source #

Uses the underlying Monoid instances for Color and Format.

Instance details

Defined in Rainbow.Types

Methods

mempty :: Style a #

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

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

type Rep (Style a) Source # 
Instance details

Defined in Rainbow.Types

type Rep (Style a) = D1 (MetaData "Style" "Rainbow.Types" "rainbow-0.34.2.2-1ah5PZE6w84FK2I3qiFqVN" False) (C1 (MetaCons "Style" PrefixI True) (S1 (MetaSel (Just "_fore") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Color a)) :*: (S1 (MetaSel (Just "_back") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Color a)) :*: S1 (MetaSel (Just "_format") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Format))))

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 # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Ord Scheme Source # 
Instance details

Defined in Rainbow.Types

Show Scheme Source # 
Instance details

Defined in Rainbow.Types

Generic Scheme Source # 
Instance details

Defined in Rainbow.Types

Associated Types

type Rep Scheme :: Type -> Type #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

Semigroup Scheme Source # 
Instance details

Defined in Rainbow.Types

Monoid Scheme Source # 
Instance details

Defined in Rainbow.Types

type Rep Scheme Source # 
Instance details

Defined in Rainbow.Types

type Rep Scheme = D1 (MetaData "Scheme" "Rainbow.Types" "rainbow-0.34.2.2-1ah5PZE6w84FK2I3qiFqVN" False) (C1 (MetaCons "Scheme" PrefixI True) (S1 (MetaSel (Just "_style8") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Style Enum8)) :*: S1 (MetaSel (Just "_style256") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Style Word8))))

data Chunk 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
Eq Chunk Source # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Ord Chunk Source # 
Instance details

Defined in Rainbow.Types

Methods

compare :: Chunk -> Chunk -> Ordering #

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

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

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

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

max :: Chunk -> Chunk -> Chunk #

min :: Chunk -> Chunk -> Chunk #

Show Chunk Source # 
Instance details

Defined in Rainbow.Types

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

IsString Chunk Source #

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

Instance details

Defined in Rainbow.Types

Methods

fromString :: String -> Chunk #

Generic Chunk Source # 
Instance details

Defined in Rainbow.Types

Associated Types

type Rep Chunk :: Type -> Type #

Methods

from :: Chunk -> Rep Chunk x #

to :: Rep Chunk x -> Chunk #

Semigroup Chunk Source #

Uses the underlying Semigroup instances for both the underlying Scheme and the underlying Text.

Instance details

Defined in Rainbow.Types

Methods

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

sconcat :: NonEmpty Chunk -> Chunk #

stimes :: Integral b => b -> Chunk -> Chunk #

Monoid Chunk Source #

Uses the underlying Monoid instances for the Scheme and for the underlying Text. Therefore mempty will have no formatting, no colors, and no text.

Instance details

Defined in Rainbow.Types

Methods

mempty :: Chunk #

mappend :: Chunk -> Chunk -> Chunk #

mconcat :: [Chunk] -> Chunk #

type Rep Chunk Source # 
Instance details

Defined in Rainbow.Types

type Rep Chunk = D1 (MetaData "Chunk" "Rainbow.Types" "rainbow-0.34.2.2-1ah5PZE6w84FK2I3qiFqVN" False) (C1 (MetaCons "Chunk" PrefixI True) (S1 (MetaSel (Just "_scheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scheme) :*: S1 (MetaSel (Just "_yarn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

chunk :: Text -> Chunk Source #

Creates a Chunk with no formatting and with the given text. A Chunk is also an instance of IsString so you can create them with the OverloadedStrings extension. Such a Chunk has the text of the string and no formatting.

data Radiant Source #

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

Constructors

Radiant 
Instances
Eq Radiant Source # 
Instance details

Defined in Rainbow.Types

Methods

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

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

Ord Radiant Source # 
Instance details

Defined in Rainbow.Types

Show Radiant Source # 
Instance details

Defined in Rainbow.Types

Generic Radiant Source # 
Instance details

Defined in Rainbow.Types

Associated Types

type Rep Radiant :: Type -> Type #

Methods

from :: Radiant -> Rep Radiant x #

to :: Rep Radiant x -> Radiant #

Semigroup Radiant Source # 
Instance details

Defined in Rainbow.Types

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.

Instance details

Defined in Rainbow.Types

type Rep Radiant Source # 
Instance details

Defined in Rainbow.Types

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