Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- newtype Color a = Color (Maybe a)
- data Enum8
- enum8toWord8 :: Enum8 -> Word8
- black :: Enum8
- red :: Enum8
- green :: Enum8
- yellow :: Enum8
- blue :: Enum8
- magenta :: Enum8
- cyan :: Enum8
- white :: Enum8
- grey :: Word8
- brightRed :: Word8
- brightGreen :: Word8
- brightYellow :: Word8
- brightBlue :: Word8
- brightMagenta :: Word8
- brightCyan :: Word8
- brightWhite :: Word8
- data Format = Format {}
- underline :: Lens' Format Bool
- strikeout :: Lens' Format Bool
- italic :: Lens' Format Bool
- invisible :: Lens' Format Bool
- inverse :: Lens' Format Bool
- faint :: Lens' Format Bool
- bold :: Lens' Format Bool
- blink :: Lens' Format Bool
- data Style a = Style {}
- format :: forall a. Lens' (Style a) Format
- fore :: forall a. Lens' (Style a) (Color a)
- back :: forall a. Lens' (Style a) (Color a)
- data Scheme = Scheme {}
- style8 :: Lens' Scheme (Style Enum8)
- style256 :: Lens' Scheme (Style Word8)
- data Chunk = Chunk {}
- chunk :: Text -> Chunk
- yarn :: Lens' Chunk Text
- scheme :: Lens' Chunk Scheme
- data Radiant = Radiant {}
- color8 :: Lens' Radiant (Color Enum8)
- color256 :: Lens' Radiant (Color Word8)
Documentation
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.
Instances
Functor Color Source # | |
Foldable Color Source # | |
Defined in Rainbow.Types 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 # elem :: Eq a => a -> Color a -> Bool # maximum :: Ord a => Color a -> a # minimum :: Ord a => Color a -> a # | |
Traversable Color Source # | |
Eq a => Eq (Color a) Source # | |
Ord a => Ord (Color a) Source # | |
Show a => Show (Color a) Source # | |
Generic (Color a) Source # | |
Semigroup (Color a) Source # | |
Monoid (Color a) Source # | Takes the last non-Nothing Color. |
type Rep (Color a) Source # | |
Defined in Rainbow.Types |
A simple enumeration for eight values. Represents eight colors.
Instances
Bounded Enum8 Source # | |
Enum Enum8 Source # | |
Eq Enum8 Source # | |
Ord Enum8 Source # | |
Show Enum8 Source # | |
Generic Enum8 Source # | |
type Rep Enum8 Source # | |
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)))) |
enum8toWord8 :: Enum8 -> Word8 Source #
brightGreen :: Word8 Source #
brightYellow :: Word8 Source #
brightBlue :: Word8 Source #
brightCyan :: Word8 Source #
brightWhite :: Word8 Source #
Text formatting such as bold, italic, etc.
Instances
The foreground and background color, and the Format
. This
represents all colors and formatting attributes for either an 8- or
256-color terminal.
Instances
Holds the Style
for both 8- and 256-color terminals.
Instances
Eq Scheme Source # | |
Ord Scheme Source # | |
Show Scheme Source # | |
Generic Scheme Source # | |
Semigroup Scheme Source # | |
Monoid Scheme Source # | |
type Rep Scheme Source # | |
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)))) |
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.
Instances
Eq Chunk Source # | |
Ord Chunk Source # | |
Show Chunk Source # | |
IsString Chunk Source # | Creates a |
Defined in Rainbow.Types fromString :: String -> Chunk # | |
Generic Chunk Source # | |
Semigroup Chunk Source # | Uses the underlying |
Monoid Chunk Source # | Uses the underlying |
type Rep Chunk Source # | |
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))) |
Stores colors that may affect 8-color terminals, 256-color terminals, both, or neither.
Instances
Eq Radiant Source # | |
Ord Radiant Source # | |
Show Radiant Source # | |
Generic Radiant Source # | |
Semigroup Radiant Source # | |
Monoid Radiant Source # | Uses the underlying |
type Rep Radiant Source # | |
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)))) |