#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif

{-| The \'ANSI\' standards refer to the visual style of displaying characters as
their \'graphic rendition\'. The style includes the color of a character or its
background, the intensity (bold, normal or faint) of a character, or whether the
character is italic or underlined (single or double), blinking (slowly or
rapidly) or visible or not. The \'ANSI\' codes to establish the graphic
rendition for subsequent text are referred to as SELECT GRAPHIC RENDITION (SGR).

This module exports types and functions used to represent SGR aspects. See also
'System.Console.ANSI.setSGR' and related functions provided by the
@ansi-terminal@ package.
-}
module System.Console.ANSI.Types
  (
  -- * Types used to represent SGR aspects

    SGR (..)
  , ConsoleLayer (..)
  , Color (..)
  , ColorIntensity (..)
  , ConsoleIntensity (..)
  , Underlining (..)
  , BlinkSpeed (..)
  -- * Constructors of xterm 256-color palette indices

  , xterm6LevelRGB
  , xterm24LevelGray
  , xtermSystem
  ) where

import Data.Ix (Ix)
import Data.Word (Word8)

import Data.Colour (Colour)

-- | ANSI's eight standard colors. They come in two intensities, which are

-- controlled by 'ColorIntensity'. Many terminals allow the colors of the

-- standard palette to be customised, so that, for example,

-- @setSGR [ SetColor Foreground Vivid Green ]@ may not result in bright green

-- characters.

data Color
  = Black
  | Red
  | Green
  | Yellow
  | Blue
  | Magenta
  | Cyan
  | White
  deriving (Color
forall a. a -> a -> Bounded a
maxBound :: Color
$cmaxBound :: Color
minBound :: Color
$cminBound :: Color
Bounded, Int -> Color
Color -> Int
Color -> [Color]
Color -> Color
Color -> Color -> [Color]
Color -> Color -> Color -> [Color]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Color -> Color -> Color -> [Color]
$cenumFromThenTo :: Color -> Color -> Color -> [Color]
enumFromTo :: Color -> Color -> [Color]
$cenumFromTo :: Color -> Color -> [Color]
enumFromThen :: Color -> Color -> [Color]
$cenumFromThen :: Color -> Color -> [Color]
enumFrom :: Color -> [Color]
$cenumFrom :: Color -> [Color]
fromEnum :: Color -> Int
$cfromEnum :: Color -> Int
toEnum :: Int -> Color
$ctoEnum :: Int -> Color
pred :: Color -> Color
$cpred :: Color -> Color
succ :: Color -> Color
$csucc :: Color -> Color
Enum, Color -> Color -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c== :: Color -> Color -> Bool
Eq, Ord Color
(Color, Color) -> Int
(Color, Color) -> [Color]
(Color, Color) -> Color -> Bool
(Color, Color) -> Color -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (Color, Color) -> Int
$cunsafeRangeSize :: (Color, Color) -> Int
rangeSize :: (Color, Color) -> Int
$crangeSize :: (Color, Color) -> Int
inRange :: (Color, Color) -> Color -> Bool
$cinRange :: (Color, Color) -> Color -> Bool
unsafeIndex :: (Color, Color) -> Color -> Int
$cunsafeIndex :: (Color, Color) -> Color -> Int
index :: (Color, Color) -> Color -> Int
$cindex :: (Color, Color) -> Color -> Int
range :: (Color, Color) -> [Color]
$crange :: (Color, Color) -> [Color]
Ix, Eq Color
Color -> Color -> Bool
Color -> Color -> Ordering
Color -> Color -> Color
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Color -> Color -> Color
$cmin :: Color -> Color -> Color
max :: Color -> Color -> Color
$cmax :: Color -> Color -> Color
>= :: Color -> Color -> Bool
$c>= :: Color -> Color -> Bool
> :: Color -> Color -> Bool
$c> :: Color -> Color -> Bool
<= :: Color -> Color -> Bool
$c<= :: Color -> Color -> Bool
< :: Color -> Color -> Bool
$c< :: Color -> Color -> Bool
compare :: Color -> Color -> Ordering
$ccompare :: Color -> Color -> Ordering
Ord, ReadPrec [Color]
ReadPrec Color
Int -> ReadS Color
ReadS [Color]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Color]
$creadListPrec :: ReadPrec [Color]
readPrec :: ReadPrec Color
$creadPrec :: ReadPrec Color
readList :: ReadS [Color]
$creadList :: ReadS [Color]
readsPrec :: Int -> ReadS Color
$creadsPrec :: Int -> ReadS Color
Read, Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Color] -> ShowS
$cshowList :: [Color] -> ShowS
show :: Color -> String
$cshow :: Color -> String
showsPrec :: Int -> Color -> ShowS
$cshowsPrec :: Int -> Color -> ShowS
Show)

-- | ANSI's standard colors come in two intensities

data ColorIntensity
  = Dull
  | Vivid
  deriving (ColorIntensity
forall a. a -> a -> Bounded a
maxBound :: ColorIntensity
$cmaxBound :: ColorIntensity
minBound :: ColorIntensity
$cminBound :: ColorIntensity
Bounded, ColorIntensity -> ColorIntensity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorIntensity -> ColorIntensity -> Bool
$c/= :: ColorIntensity -> ColorIntensity -> Bool
== :: ColorIntensity -> ColorIntensity -> Bool
$c== :: ColorIntensity -> ColorIntensity -> Bool
Eq, Int -> ColorIntensity
ColorIntensity -> Int
ColorIntensity -> [ColorIntensity]
ColorIntensity -> ColorIntensity
ColorIntensity -> ColorIntensity -> [ColorIntensity]
ColorIntensity
-> ColorIntensity -> ColorIntensity -> [ColorIntensity]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ColorIntensity
-> ColorIntensity -> ColorIntensity -> [ColorIntensity]
$cenumFromThenTo :: ColorIntensity
-> ColorIntensity -> ColorIntensity -> [ColorIntensity]
enumFromTo :: ColorIntensity -> ColorIntensity -> [ColorIntensity]
$cenumFromTo :: ColorIntensity -> ColorIntensity -> [ColorIntensity]
enumFromThen :: ColorIntensity -> ColorIntensity -> [ColorIntensity]
$cenumFromThen :: ColorIntensity -> ColorIntensity -> [ColorIntensity]
enumFrom :: ColorIntensity -> [ColorIntensity]
$cenumFrom :: ColorIntensity -> [ColorIntensity]
fromEnum :: ColorIntensity -> Int
$cfromEnum :: ColorIntensity -> Int
toEnum :: Int -> ColorIntensity
$ctoEnum :: Int -> ColorIntensity
pred :: ColorIntensity -> ColorIntensity
$cpred :: ColorIntensity -> ColorIntensity
succ :: ColorIntensity -> ColorIntensity
$csucc :: ColorIntensity -> ColorIntensity
Enum, Ord ColorIntensity
(ColorIntensity, ColorIntensity) -> Int
(ColorIntensity, ColorIntensity) -> [ColorIntensity]
(ColorIntensity, ColorIntensity) -> ColorIntensity -> Bool
(ColorIntensity, ColorIntensity) -> ColorIntensity -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (ColorIntensity, ColorIntensity) -> Int
$cunsafeRangeSize :: (ColorIntensity, ColorIntensity) -> Int
rangeSize :: (ColorIntensity, ColorIntensity) -> Int
$crangeSize :: (ColorIntensity, ColorIntensity) -> Int
inRange :: (ColorIntensity, ColorIntensity) -> ColorIntensity -> Bool
$cinRange :: (ColorIntensity, ColorIntensity) -> ColorIntensity -> Bool
unsafeIndex :: (ColorIntensity, ColorIntensity) -> ColorIntensity -> Int
$cunsafeIndex :: (ColorIntensity, ColorIntensity) -> ColorIntensity -> Int
index :: (ColorIntensity, ColorIntensity) -> ColorIntensity -> Int
$cindex :: (ColorIntensity, ColorIntensity) -> ColorIntensity -> Int
range :: (ColorIntensity, ColorIntensity) -> [ColorIntensity]
$crange :: (ColorIntensity, ColorIntensity) -> [ColorIntensity]
Ix, Eq ColorIntensity
ColorIntensity -> ColorIntensity -> Bool
ColorIntensity -> ColorIntensity -> Ordering
ColorIntensity -> ColorIntensity -> ColorIntensity
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ColorIntensity -> ColorIntensity -> ColorIntensity
$cmin :: ColorIntensity -> ColorIntensity -> ColorIntensity
max :: ColorIntensity -> ColorIntensity -> ColorIntensity
$cmax :: ColorIntensity -> ColorIntensity -> ColorIntensity
>= :: ColorIntensity -> ColorIntensity -> Bool
$c>= :: ColorIntensity -> ColorIntensity -> Bool
> :: ColorIntensity -> ColorIntensity -> Bool
$c> :: ColorIntensity -> ColorIntensity -> Bool
<= :: ColorIntensity -> ColorIntensity -> Bool
$c<= :: ColorIntensity -> ColorIntensity -> Bool
< :: ColorIntensity -> ColorIntensity -> Bool
$c< :: ColorIntensity -> ColorIntensity -> Bool
compare :: ColorIntensity -> ColorIntensity -> Ordering
$ccompare :: ColorIntensity -> ColorIntensity -> Ordering
Ord, ReadPrec [ColorIntensity]
ReadPrec ColorIntensity
Int -> ReadS ColorIntensity
ReadS [ColorIntensity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ColorIntensity]
$creadListPrec :: ReadPrec [ColorIntensity]
readPrec :: ReadPrec ColorIntensity
$creadPrec :: ReadPrec ColorIntensity
readList :: ReadS [ColorIntensity]
$creadList :: ReadS [ColorIntensity]
readsPrec :: Int -> ReadS ColorIntensity
$creadsPrec :: Int -> ReadS ColorIntensity
Read, Int -> ColorIntensity -> ShowS
[ColorIntensity] -> ShowS
ColorIntensity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColorIntensity] -> ShowS
$cshowList :: [ColorIntensity] -> ShowS
show :: ColorIntensity -> String
$cshow :: ColorIntensity -> String
showsPrec :: Int -> ColorIntensity -> ShowS
$cshowsPrec :: Int -> ColorIntensity -> ShowS
Show)

-- | ANSI colors can be set on two different layers

data ConsoleLayer
  = Foreground
  | Background
  deriving (ConsoleLayer
forall a. a -> a -> Bounded a
maxBound :: ConsoleLayer
$cmaxBound :: ConsoleLayer
minBound :: ConsoleLayer
$cminBound :: ConsoleLayer
Bounded, ConsoleLayer -> ConsoleLayer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConsoleLayer -> ConsoleLayer -> Bool
$c/= :: ConsoleLayer -> ConsoleLayer -> Bool
== :: ConsoleLayer -> ConsoleLayer -> Bool
$c== :: ConsoleLayer -> ConsoleLayer -> Bool
Eq, Int -> ConsoleLayer
ConsoleLayer -> Int
ConsoleLayer -> [ConsoleLayer]
ConsoleLayer -> ConsoleLayer
ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
ConsoleLayer -> ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ConsoleLayer -> ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
$cenumFromThenTo :: ConsoleLayer -> ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
enumFromTo :: ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
$cenumFromTo :: ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
enumFromThen :: ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
$cenumFromThen :: ConsoleLayer -> ConsoleLayer -> [ConsoleLayer]
enumFrom :: ConsoleLayer -> [ConsoleLayer]
$cenumFrom :: ConsoleLayer -> [ConsoleLayer]
fromEnum :: ConsoleLayer -> Int
$cfromEnum :: ConsoleLayer -> Int
toEnum :: Int -> ConsoleLayer
$ctoEnum :: Int -> ConsoleLayer
pred :: ConsoleLayer -> ConsoleLayer
$cpred :: ConsoleLayer -> ConsoleLayer
succ :: ConsoleLayer -> ConsoleLayer
$csucc :: ConsoleLayer -> ConsoleLayer
Enum, Ord ConsoleLayer
(ConsoleLayer, ConsoleLayer) -> Int
(ConsoleLayer, ConsoleLayer) -> [ConsoleLayer]
(ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Bool
(ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (ConsoleLayer, ConsoleLayer) -> Int
$cunsafeRangeSize :: (ConsoleLayer, ConsoleLayer) -> Int
rangeSize :: (ConsoleLayer, ConsoleLayer) -> Int
$crangeSize :: (ConsoleLayer, ConsoleLayer) -> Int
inRange :: (ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Bool
$cinRange :: (ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Bool
unsafeIndex :: (ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Int
$cunsafeIndex :: (ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Int
index :: (ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Int
$cindex :: (ConsoleLayer, ConsoleLayer) -> ConsoleLayer -> Int
range :: (ConsoleLayer, ConsoleLayer) -> [ConsoleLayer]
$crange :: (ConsoleLayer, ConsoleLayer) -> [ConsoleLayer]
Ix, Eq ConsoleLayer
ConsoleLayer -> ConsoleLayer -> Bool
ConsoleLayer -> ConsoleLayer -> Ordering
ConsoleLayer -> ConsoleLayer -> ConsoleLayer
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConsoleLayer -> ConsoleLayer -> ConsoleLayer
$cmin :: ConsoleLayer -> ConsoleLayer -> ConsoleLayer
max :: ConsoleLayer -> ConsoleLayer -> ConsoleLayer
$cmax :: ConsoleLayer -> ConsoleLayer -> ConsoleLayer
>= :: ConsoleLayer -> ConsoleLayer -> Bool
$c>= :: ConsoleLayer -> ConsoleLayer -> Bool
> :: ConsoleLayer -> ConsoleLayer -> Bool
$c> :: ConsoleLayer -> ConsoleLayer -> Bool
<= :: ConsoleLayer -> ConsoleLayer -> Bool
$c<= :: ConsoleLayer -> ConsoleLayer -> Bool
< :: ConsoleLayer -> ConsoleLayer -> Bool
$c< :: ConsoleLayer -> ConsoleLayer -> Bool
compare :: ConsoleLayer -> ConsoleLayer -> Ordering
$ccompare :: ConsoleLayer -> ConsoleLayer -> Ordering
Ord, ReadPrec [ConsoleLayer]
ReadPrec ConsoleLayer
Int -> ReadS ConsoleLayer
ReadS [ConsoleLayer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConsoleLayer]
$creadListPrec :: ReadPrec [ConsoleLayer]
readPrec :: ReadPrec ConsoleLayer
$creadPrec :: ReadPrec ConsoleLayer
readList :: ReadS [ConsoleLayer]
$creadList :: ReadS [ConsoleLayer]
readsPrec :: Int -> ReadS ConsoleLayer
$creadsPrec :: Int -> ReadS ConsoleLayer
Read, Int -> ConsoleLayer -> ShowS
[ConsoleLayer] -> ShowS
ConsoleLayer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConsoleLayer] -> ShowS
$cshowList :: [ConsoleLayer] -> ShowS
show :: ConsoleLayer -> String
$cshow :: ConsoleLayer -> String
showsPrec :: Int -> ConsoleLayer -> ShowS
$cshowsPrec :: Int -> ConsoleLayer -> ShowS
Show)

-- | ANSI blink speeds: values other than 'NoBlink' are not widely supported

data BlinkSpeed
  = SlowBlink -- ^ Less than 150 blinks per minute

  | RapidBlink -- ^ More than 150 blinks per minute

  | NoBlink
  deriving (BlinkSpeed
forall a. a -> a -> Bounded a
maxBound :: BlinkSpeed
$cmaxBound :: BlinkSpeed
minBound :: BlinkSpeed
$cminBound :: BlinkSpeed
Bounded, BlinkSpeed -> BlinkSpeed -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlinkSpeed -> BlinkSpeed -> Bool
$c/= :: BlinkSpeed -> BlinkSpeed -> Bool
== :: BlinkSpeed -> BlinkSpeed -> Bool
$c== :: BlinkSpeed -> BlinkSpeed -> Bool
Eq, Int -> BlinkSpeed
BlinkSpeed -> Int
BlinkSpeed -> [BlinkSpeed]
BlinkSpeed -> BlinkSpeed
BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
BlinkSpeed -> BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: BlinkSpeed -> BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
$cenumFromThenTo :: BlinkSpeed -> BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
enumFromTo :: BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
$cenumFromTo :: BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
enumFromThen :: BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
$cenumFromThen :: BlinkSpeed -> BlinkSpeed -> [BlinkSpeed]
enumFrom :: BlinkSpeed -> [BlinkSpeed]
$cenumFrom :: BlinkSpeed -> [BlinkSpeed]
fromEnum :: BlinkSpeed -> Int
$cfromEnum :: BlinkSpeed -> Int
toEnum :: Int -> BlinkSpeed
$ctoEnum :: Int -> BlinkSpeed
pred :: BlinkSpeed -> BlinkSpeed
$cpred :: BlinkSpeed -> BlinkSpeed
succ :: BlinkSpeed -> BlinkSpeed
$csucc :: BlinkSpeed -> BlinkSpeed
Enum, Ord BlinkSpeed
(BlinkSpeed, BlinkSpeed) -> Int
(BlinkSpeed, BlinkSpeed) -> [BlinkSpeed]
(BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Bool
(BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (BlinkSpeed, BlinkSpeed) -> Int
$cunsafeRangeSize :: (BlinkSpeed, BlinkSpeed) -> Int
rangeSize :: (BlinkSpeed, BlinkSpeed) -> Int
$crangeSize :: (BlinkSpeed, BlinkSpeed) -> Int
inRange :: (BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Bool
$cinRange :: (BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Bool
unsafeIndex :: (BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Int
$cunsafeIndex :: (BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Int
index :: (BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Int
$cindex :: (BlinkSpeed, BlinkSpeed) -> BlinkSpeed -> Int
range :: (BlinkSpeed, BlinkSpeed) -> [BlinkSpeed]
$crange :: (BlinkSpeed, BlinkSpeed) -> [BlinkSpeed]
Ix, Eq BlinkSpeed
BlinkSpeed -> BlinkSpeed -> Bool
BlinkSpeed -> BlinkSpeed -> Ordering
BlinkSpeed -> BlinkSpeed -> BlinkSpeed
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BlinkSpeed -> BlinkSpeed -> BlinkSpeed
$cmin :: BlinkSpeed -> BlinkSpeed -> BlinkSpeed
max :: BlinkSpeed -> BlinkSpeed -> BlinkSpeed
$cmax :: BlinkSpeed -> BlinkSpeed -> BlinkSpeed
>= :: BlinkSpeed -> BlinkSpeed -> Bool
$c>= :: BlinkSpeed -> BlinkSpeed -> Bool
> :: BlinkSpeed -> BlinkSpeed -> Bool
$c> :: BlinkSpeed -> BlinkSpeed -> Bool
<= :: BlinkSpeed -> BlinkSpeed -> Bool
$c<= :: BlinkSpeed -> BlinkSpeed -> Bool
< :: BlinkSpeed -> BlinkSpeed -> Bool
$c< :: BlinkSpeed -> BlinkSpeed -> Bool
compare :: BlinkSpeed -> BlinkSpeed -> Ordering
$ccompare :: BlinkSpeed -> BlinkSpeed -> Ordering
Ord, ReadPrec [BlinkSpeed]
ReadPrec BlinkSpeed
Int -> ReadS BlinkSpeed
ReadS [BlinkSpeed]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BlinkSpeed]
$creadListPrec :: ReadPrec [BlinkSpeed]
readPrec :: ReadPrec BlinkSpeed
$creadPrec :: ReadPrec BlinkSpeed
readList :: ReadS [BlinkSpeed]
$creadList :: ReadS [BlinkSpeed]
readsPrec :: Int -> ReadS BlinkSpeed
$creadsPrec :: Int -> ReadS BlinkSpeed
Read, Int -> BlinkSpeed -> ShowS
[BlinkSpeed] -> ShowS
BlinkSpeed -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlinkSpeed] -> ShowS
$cshowList :: [BlinkSpeed] -> ShowS
show :: BlinkSpeed -> String
$cshow :: BlinkSpeed -> String
showsPrec :: Int -> BlinkSpeed -> ShowS
$cshowsPrec :: Int -> BlinkSpeed -> ShowS
Show)

-- | ANSI text underlining

data Underlining
  = SingleUnderline
  -- | Not widely supported. Not supported natively on Windows 10

  | DoubleUnderline
  | NoUnderline
  deriving (Underlining
forall a. a -> a -> Bounded a
maxBound :: Underlining
$cmaxBound :: Underlining
minBound :: Underlining
$cminBound :: Underlining
Bounded, Underlining -> Underlining -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Underlining -> Underlining -> Bool
$c/= :: Underlining -> Underlining -> Bool
== :: Underlining -> Underlining -> Bool
$c== :: Underlining -> Underlining -> Bool
Eq, Int -> Underlining
Underlining -> Int
Underlining -> [Underlining]
Underlining -> Underlining
Underlining -> Underlining -> [Underlining]
Underlining -> Underlining -> Underlining -> [Underlining]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Underlining -> Underlining -> Underlining -> [Underlining]
$cenumFromThenTo :: Underlining -> Underlining -> Underlining -> [Underlining]
enumFromTo :: Underlining -> Underlining -> [Underlining]
$cenumFromTo :: Underlining -> Underlining -> [Underlining]
enumFromThen :: Underlining -> Underlining -> [Underlining]
$cenumFromThen :: Underlining -> Underlining -> [Underlining]
enumFrom :: Underlining -> [Underlining]
$cenumFrom :: Underlining -> [Underlining]
fromEnum :: Underlining -> Int
$cfromEnum :: Underlining -> Int
toEnum :: Int -> Underlining
$ctoEnum :: Int -> Underlining
pred :: Underlining -> Underlining
$cpred :: Underlining -> Underlining
succ :: Underlining -> Underlining
$csucc :: Underlining -> Underlining
Enum, Ord Underlining
(Underlining, Underlining) -> Int
(Underlining, Underlining) -> [Underlining]
(Underlining, Underlining) -> Underlining -> Bool
(Underlining, Underlining) -> Underlining -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (Underlining, Underlining) -> Int
$cunsafeRangeSize :: (Underlining, Underlining) -> Int
rangeSize :: (Underlining, Underlining) -> Int
$crangeSize :: (Underlining, Underlining) -> Int
inRange :: (Underlining, Underlining) -> Underlining -> Bool
$cinRange :: (Underlining, Underlining) -> Underlining -> Bool
unsafeIndex :: (Underlining, Underlining) -> Underlining -> Int
$cunsafeIndex :: (Underlining, Underlining) -> Underlining -> Int
index :: (Underlining, Underlining) -> Underlining -> Int
$cindex :: (Underlining, Underlining) -> Underlining -> Int
range :: (Underlining, Underlining) -> [Underlining]
$crange :: (Underlining, Underlining) -> [Underlining]
Ix, Eq Underlining
Underlining -> Underlining -> Bool
Underlining -> Underlining -> Ordering
Underlining -> Underlining -> Underlining
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Underlining -> Underlining -> Underlining
$cmin :: Underlining -> Underlining -> Underlining
max :: Underlining -> Underlining -> Underlining
$cmax :: Underlining -> Underlining -> Underlining
>= :: Underlining -> Underlining -> Bool
$c>= :: Underlining -> Underlining -> Bool
> :: Underlining -> Underlining -> Bool
$c> :: Underlining -> Underlining -> Bool
<= :: Underlining -> Underlining -> Bool
$c<= :: Underlining -> Underlining -> Bool
< :: Underlining -> Underlining -> Bool
$c< :: Underlining -> Underlining -> Bool
compare :: Underlining -> Underlining -> Ordering
$ccompare :: Underlining -> Underlining -> Ordering
Ord, ReadPrec [Underlining]
ReadPrec Underlining
Int -> ReadS Underlining
ReadS [Underlining]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Underlining]
$creadListPrec :: ReadPrec [Underlining]
readPrec :: ReadPrec Underlining
$creadPrec :: ReadPrec Underlining
readList :: ReadS [Underlining]
$creadList :: ReadS [Underlining]
readsPrec :: Int -> ReadS Underlining
$creadsPrec :: Int -> ReadS Underlining
Read, Int -> Underlining -> ShowS
[Underlining] -> ShowS
Underlining -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Underlining] -> ShowS
$cshowList :: [Underlining] -> ShowS
show :: Underlining -> String
$cshow :: Underlining -> String
showsPrec :: Int -> Underlining -> ShowS
$cshowsPrec :: Int -> Underlining -> ShowS
Show)

-- | ANSI general console intensity: usually treated as setting the font style

-- (e.g. 'BoldIntensity' causes text to be bold)

data ConsoleIntensity
  = BoldIntensity
  -- | Not widely supported: sometimes treated as concealing text. Not supported

  -- natively on Windows 10

  | FaintIntensity
  | NormalIntensity
  deriving (ConsoleIntensity
forall a. a -> a -> Bounded a
maxBound :: ConsoleIntensity
$cmaxBound :: ConsoleIntensity
minBound :: ConsoleIntensity
$cminBound :: ConsoleIntensity
Bounded, ConsoleIntensity -> ConsoleIntensity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConsoleIntensity -> ConsoleIntensity -> Bool
$c/= :: ConsoleIntensity -> ConsoleIntensity -> Bool
== :: ConsoleIntensity -> ConsoleIntensity -> Bool
$c== :: ConsoleIntensity -> ConsoleIntensity -> Bool
Eq, Int -> ConsoleIntensity
ConsoleIntensity -> Int
ConsoleIntensity -> [ConsoleIntensity]
ConsoleIntensity -> ConsoleIntensity
ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
ConsoleIntensity
-> ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ConsoleIntensity
-> ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
$cenumFromThenTo :: ConsoleIntensity
-> ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
enumFromTo :: ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
$cenumFromTo :: ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
enumFromThen :: ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
$cenumFromThen :: ConsoleIntensity -> ConsoleIntensity -> [ConsoleIntensity]
enumFrom :: ConsoleIntensity -> [ConsoleIntensity]
$cenumFrom :: ConsoleIntensity -> [ConsoleIntensity]
fromEnum :: ConsoleIntensity -> Int
$cfromEnum :: ConsoleIntensity -> Int
toEnum :: Int -> ConsoleIntensity
$ctoEnum :: Int -> ConsoleIntensity
pred :: ConsoleIntensity -> ConsoleIntensity
$cpred :: ConsoleIntensity -> ConsoleIntensity
succ :: ConsoleIntensity -> ConsoleIntensity
$csucc :: ConsoleIntensity -> ConsoleIntensity
Enum, Ord ConsoleIntensity
(ConsoleIntensity, ConsoleIntensity) -> Int
(ConsoleIntensity, ConsoleIntensity) -> [ConsoleIntensity]
(ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Bool
(ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (ConsoleIntensity, ConsoleIntensity) -> Int
$cunsafeRangeSize :: (ConsoleIntensity, ConsoleIntensity) -> Int
rangeSize :: (ConsoleIntensity, ConsoleIntensity) -> Int
$crangeSize :: (ConsoleIntensity, ConsoleIntensity) -> Int
inRange :: (ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Bool
$cinRange :: (ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Bool
unsafeIndex :: (ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Int
$cunsafeIndex :: (ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Int
index :: (ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Int
$cindex :: (ConsoleIntensity, ConsoleIntensity) -> ConsoleIntensity -> Int
range :: (ConsoleIntensity, ConsoleIntensity) -> [ConsoleIntensity]
$crange :: (ConsoleIntensity, ConsoleIntensity) -> [ConsoleIntensity]
Ix, Eq ConsoleIntensity
ConsoleIntensity -> ConsoleIntensity -> Bool
ConsoleIntensity -> ConsoleIntensity -> Ordering
ConsoleIntensity -> ConsoleIntensity -> ConsoleIntensity
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConsoleIntensity -> ConsoleIntensity -> ConsoleIntensity
$cmin :: ConsoleIntensity -> ConsoleIntensity -> ConsoleIntensity
max :: ConsoleIntensity -> ConsoleIntensity -> ConsoleIntensity
$cmax :: ConsoleIntensity -> ConsoleIntensity -> ConsoleIntensity
>= :: ConsoleIntensity -> ConsoleIntensity -> Bool
$c>= :: ConsoleIntensity -> ConsoleIntensity -> Bool
> :: ConsoleIntensity -> ConsoleIntensity -> Bool
$c> :: ConsoleIntensity -> ConsoleIntensity -> Bool
<= :: ConsoleIntensity -> ConsoleIntensity -> Bool
$c<= :: ConsoleIntensity -> ConsoleIntensity -> Bool
< :: ConsoleIntensity -> ConsoleIntensity -> Bool
$c< :: ConsoleIntensity -> ConsoleIntensity -> Bool
compare :: ConsoleIntensity -> ConsoleIntensity -> Ordering
$ccompare :: ConsoleIntensity -> ConsoleIntensity -> Ordering
Ord, ReadPrec [ConsoleIntensity]
ReadPrec ConsoleIntensity
Int -> ReadS ConsoleIntensity
ReadS [ConsoleIntensity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConsoleIntensity]
$creadListPrec :: ReadPrec [ConsoleIntensity]
readPrec :: ReadPrec ConsoleIntensity
$creadPrec :: ReadPrec ConsoleIntensity
readList :: ReadS [ConsoleIntensity]
$creadList :: ReadS [ConsoleIntensity]
readsPrec :: Int -> ReadS ConsoleIntensity
$creadsPrec :: Int -> ReadS ConsoleIntensity
Read, Int -> ConsoleIntensity -> ShowS
[ConsoleIntensity] -> ShowS
ConsoleIntensity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConsoleIntensity] -> ShowS
$cshowList :: [ConsoleIntensity] -> ShowS
show :: ConsoleIntensity -> String
$cshow :: ConsoleIntensity -> String
showsPrec :: Int -> ConsoleIntensity -> ShowS
$cshowsPrec :: Int -> ConsoleIntensity -> ShowS
Show)

-- | ANSI Select Graphic Rendition (SGR) command

--

-- In respect of colors, there are three alternative commands:

--

-- (1) the \'ANSI\' standards allow for eight standard colors (with two

-- intensities). Windows and many other terminals (including xterm) allow the

-- user to redefine the standard colors (so, for example 'Vivid' 'Green' may not

-- correspond to bright green;

--

-- (2) an extension of the standard that allows true colors (24 bit color depth)

-- in RGB space. This is usually the best alternative for more colors; and

--

-- (3) another extension that allows a palette of 256 colors, each color

-- specified by an index. Xterm provides a protocol for a palette of 256 colors

-- that many other terminals, including Windows 10, follow. Some terminals

-- (including xterm) allow the user to redefine some or all of the palette

-- colors.

data SGR
  -- | Default rendition, cancels the effect of any preceding occurrence of SGR

  -- (implementation-defined)

  = Reset
  -- | Set the character intensity. Partially supported natively on Windows 10

  | SetConsoleIntensity !ConsoleIntensity
  -- | Set italicized. Not widely supported: sometimes treated as swapping

  -- foreground and background. Not supported natively on Windows 10

  | SetItalicized !Bool
  -- | Set or clear underlining. Partially supported natively on Windows 10

  | SetUnderlining !Underlining
  -- | Set or clear character blinking. Not supported natively on Windows 10

  | SetBlinkSpeed !BlinkSpeed
  -- | Set revealed or concealed. Not widely supported. Not supported natively

  -- on Windows 10

  | SetVisible !Bool
  -- | Set negative or positive image. Supported natively on Windows 10

  | SetSwapForegroundBackground !Bool
  -- | Set a color from the standard palette of 16 colors (8 colors by 2

  -- color intensities). Many terminals allow the palette colors to be

  -- customised

  | SetColor !ConsoleLayer !ColorIntensity !Color
  -- | Set a true color (24 bit color depth). Supported natively on Windows 10

  -- from the Creators Update (April 2017)

  --

  -- @since 0.7

  | SetRGBColor !ConsoleLayer !(Colour Float)
  -- | Set a color from a palette of 256 colors using a numerical index

  -- (0-based). Supported natively on Windows 10 from the Creators Update (April

  -- 2017) but not on legacy Windows native terminals. See 'xtermSystem',

  -- 'xterm6LevelRGB' and 'xterm24LevelGray' to construct indices based on

  -- xterm's standard protocol for a 256-color palette.

  --

  -- @since 0.9

  | SetPaletteColor !ConsoleLayer !Word8
  -- | Set a color to the default (implementation-defined)

  --

  -- @since 0.10

  | SetDefaultColor !ConsoleLayer
  deriving (SGR -> SGR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SGR -> SGR -> Bool
$c/= :: SGR -> SGR -> Bool
== :: SGR -> SGR -> Bool
$c== :: SGR -> SGR -> Bool
Eq, ReadPrec [SGR]
ReadPrec SGR
Int -> ReadS SGR
ReadS [SGR]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SGR]
$creadListPrec :: ReadPrec [SGR]
readPrec :: ReadPrec SGR
$creadPrec :: ReadPrec SGR
readList :: ReadS [SGR]
$creadList :: ReadS [SGR]
readsPrec :: Int -> ReadS SGR
$creadsPrec :: Int -> ReadS SGR
Read, Int -> SGR -> ShowS
[SGR] -> ShowS
SGR -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SGR] -> ShowS
$cshowList :: [SGR] -> ShowS
show :: SGR -> String
$cshow :: SGR -> String
showsPrec :: Int -> SGR -> ShowS
$cshowsPrec :: Int -> SGR -> ShowS
Show)

-- | Given xterm's standard protocol for a 256-color palette, returns the index

-- to that part of the palette which is a 6 level (6x6x6) color cube of 216 RGB

-- colors. Throws an error if any of the red, green or blue channels is outside

-- the range 0 to 5. An example of use is:

--

-- >>> setSGR [ SetPaletteColor $ xterm6LevelRGB 5 2 0 ] -- Dark Orange

--

-- @since 0.9

xterm6LevelRGB :: Int -> Int -> Int -> Word8
xterm6LevelRGB :: Int -> Int -> Int -> Word8
xterm6LevelRGB Int
r Int
g Int
b
  -- RGB colors are represented by index:

  -- 16 + 36 × r + 6 × g + b (0 ≤ r, g, b ≤ 5)

  | Int
r forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
r forall a. Ord a => a -> a -> Bool
< Int
6 Bool -> Bool -> Bool
&& Int
g forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
g forall a. Ord a => a -> a -> Bool
< Int
6 Bool -> Bool -> Bool
&& Int
b forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
b forall a. Ord a => a -> a -> Bool
< Int
6
  =  forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
16 forall a. Num a => a -> a -> a
+ Int
36 forall a. Num a => a -> a -> a
* Int
r forall a. Num a => a -> a -> a
+ Int
6 forall a. Num a => a -> a -> a
* Int
g forall a. Num a => a -> a -> a
+ Int
b
  | Bool
otherwise
  = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Int
r forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
g forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
b forall a. [a] -> [a] -> [a]
++ String
" (r g b) is " forall a. [a] -> [a] -> [a]
++
            String
"outside of a 6 level (6x6x6) color cube."

-- | Given xterm's standard protocol for a 256-color palette, returns the index

-- to that part of the palette which is a spectrum of 24 grays, from dark

-- gray (0) to near white (23) (black and white are themselves excluded). Throws

-- an error if the gray is outside of the range 0 to 23. An example of use is:

--

-- >>> setSGR [ SetPaletteColor $ xterm24LevelGray 12 ] -- Gray50

--

-- @since 0.9

xterm24LevelGray :: Int -> Word8
xterm24LevelGray :: Int -> Word8
xterm24LevelGray Int
y
  -- Grayscale colors are represented by index:

  -- 232 + g (0 ≤ g ≤ 23)

  | Int
y forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
y forall a. Ord a => a -> a -> Bool
< Int
24 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
232 forall a. Num a => a -> a -> a
+ Int
y
  | Bool
otherwise
  = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Int
y forall a. [a] -> [a] -> [a]
++ String
" (gray) is outside of the range 0 to 23."

-- | Given xterm's standard protocol for a 256-color palette, returns the index

-- to that part of the palette which corresponds to the \'ANSI\' standards' 16

-- standard, or \'system\', colors (eight colors in two intensities). An example

-- of use is:

--

-- >>> setSGR [ SetPaletteColor $ xtermSystem Vivid Green ]

--

-- @since 0.9

xtermSystem :: ColorIntensity -> Color -> Word8
xtermSystem :: ColorIntensity -> Color -> Word8
xtermSystem ColorIntensity
intensity Color
color
  | ColorIntensity
intensity forall a. Eq a => a -> a -> Bool
== ColorIntensity
Dull  = Word8
index
  | Bool
otherwise          = Word8
index forall a. Num a => a -> a -> a
+ Word8
8
 where
  index :: Word8
index = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum Color
color