| Copyright | Daniel Mendler (c) 2017 |
|---|---|
| License | MIT (see the file LICENSE) |
| Maintainer | mail@daniel-mendler.de |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Data.Monoid.Colorful.Flat
Contents
Description
Synopsis
- data Colored a
- data Style
- data Color
- data Term
- hGetTerm :: Handle -> IO Term
- getTerm :: IO Term
- hPrintColored :: Foldable f => (Handle -> a -> IO ()) -> Handle -> Term -> f (Colored a) -> IO ()
- printColored :: Foldable f => (a -> IO ()) -> Term -> f (Colored a) -> IO ()
- hPrintColoredIO :: Handle -> Term -> [Colored (IO ())] -> IO ()
- printColoredIO :: Term -> [Colored (IO ())] -> IO ()
- hPrintColoredS :: Foldable f => Handle -> Term -> f (Colored String) -> IO ()
- printColoredS :: Foldable f => Term -> f (Colored String) -> IO ()
- showColored :: (Foldable f, Monoid o) => (a -> o) -> (SGRCode -> o) -> Term -> f (Colored a) -> o
- showColoredM :: (Foldable f, Monad m, Monoid o) => (a -> m o) -> (SGRCode -> m o) -> Term -> f (Colored a) -> m o
- showColoredS :: Foldable f => Term -> f (Colored String) -> ShowS
- (<>) :: Semigroup a => a -> a -> a
Colored datatypes
Instances
Rendering style
Constructors
| Bold | Bold font |
| Italic | Italic font |
| Underline | Underlined text |
| Invert | Invert foreground and background color |
| Blink | Blinking |
Instances
| Bounded Style Source # | |
| Enum Style Source # | |
Defined in Data.Monoid.Colorful.Color | |
| Eq Style Source # | |
| Ord Style Source # | |
| Read Style Source # | |
| Show Style Source # | |
| Generic Style Source # | |
| type Rep Style Source # | |
Defined in Data.Monoid.Colorful.Color type Rep Style = D1 (MetaData "Style" "Data.Monoid.Colorful.Color" "colorful-monoids-0.2.1.3-KQ4pdXOAU8zLHhz6xJWI7W" False) ((C1 (MetaCons "Bold" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Italic" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Underline" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Invert" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Blink" PrefixI False) (U1 :: Type -> Type)))) | |
Named colors, 256 and RGB colors for more capable terminals.
Constructors
| DefaultColor | Default terminal color (terminal specific) |
| Black | |
| Red | |
| Green | |
| Yellow | |
| Blue | |
| Magenta | |
| Cyan | |
| White | |
| DullBlack | |
| DullRed | |
| DullGreen | |
| DullYellow | |
| DullBlue | |
| DullMagenta | |
| DullCyan | |
| DullWhite | |
| Color256 !Word8 | Color from 256 color scheme. Color is automatically reduced to 8 colors for less capable terminals. |
| RGB !Word8 !Word8 !Word8 | True color. Color is automatically reduced to 256 or 8 colors for less capable terminals. |
Instances
Terminal type
Terminal type. For less capable terminals the color depth is automatically reduced.
Constructors
| TermDumb | Dumb terminal - no color output |
| Term8 | 8 colors supported |
| Term256 | 256 colors supported |
| TermRGB | True colors supported |
| TermWin | Windows terminal. Will use emulation (Not yet implemented). |
Instances
| Bounded Term Source # | |
| Enum Term Source # | |
| Eq Term Source # | |
| Ord Term Source # | |
| Read Term Source # | |
| Show Term Source # | |
| Generic Term Source # | |
| type Rep Term Source # | |
Defined in Data.Monoid.Colorful.Term type Rep Term = D1 (MetaData "Term" "Data.Monoid.Colorful.Term" "colorful-monoids-0.2.1.3-KQ4pdXOAU8zLHhz6xJWI7W" False) ((C1 (MetaCons "TermDumb" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Term8" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Term256" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TermRGB" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TermWin" PrefixI False) (U1 :: Type -> Type)))) | |
hGetTerm :: Handle -> IO Term Source #
The action (hGetTerm handle) determines the terminal type of the file handle.
The terminal type is determined by checking if the file handle points to a device
and by looking at the $TERM environment variable.
Colorful printing to file handle
hPrintColored :: Foldable f => (Handle -> a -> IO ()) -> Handle -> Term -> f (Colored a) -> IO () Source #
Show with ANSI escape sequences
showColored :: (Foldable f, Monoid o) => (a -> o) -> (SGRCode -> o) -> Term -> f (Colored a) -> o Source #
showColoredM :: (Foldable f, Monad m, Monoid o) => (a -> m o) -> (SGRCode -> m o) -> Term -> f (Colored a) -> m o Source #