{-# LANGUAGE NoImplicitPrelude #-}
module RIO.PrettyPrint.Types
(
Style (..)
, Styles
, StyleSpec
) where
import Data.Array.IArray (Array)
import Data.Ix (Ix)
import Data.Text (Text)
import RIO
import System.Console.ANSI.Types (SGR)
data Style
= Error
| Warning
| Info
| Debug
| OtherLevel
| Good
| Shell
| File
| Url
| Dir
| Recommendation
| Current
| Target
| Module
| PkgComponent
| Secondary
| Highlight
deriving (Style
forall a. a -> a -> Bounded a
maxBound :: Style
$cmaxBound :: Style
minBound :: Style
$cminBound :: Style
Bounded, Int -> Style
Style -> Int
Style -> [Style]
Style -> Style
Style -> Style -> [Style]
Style -> Style -> Style -> [Style]
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 :: Style -> Style -> Style -> [Style]
$cenumFromThenTo :: Style -> Style -> Style -> [Style]
enumFromTo :: Style -> Style -> [Style]
$cenumFromTo :: Style -> Style -> [Style]
enumFromThen :: Style -> Style -> [Style]
$cenumFromThen :: Style -> Style -> [Style]
enumFrom :: Style -> [Style]
$cenumFrom :: Style -> [Style]
fromEnum :: Style -> Int
$cfromEnum :: Style -> Int
toEnum :: Int -> Style
$ctoEnum :: Int -> Style
pred :: Style -> Style
$cpred :: Style -> Style
succ :: Style -> Style
$csucc :: Style -> Style
Enum, Style -> Style -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c== :: Style -> Style -> Bool
Eq, Ord Style
(Style, Style) -> Int
(Style, Style) -> [Style]
(Style, Style) -> Style -> Bool
(Style, Style) -> Style -> 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 :: (Style, Style) -> Int
$cunsafeRangeSize :: (Style, Style) -> Int
rangeSize :: (Style, Style) -> Int
$crangeSize :: (Style, Style) -> Int
inRange :: (Style, Style) -> Style -> Bool
$cinRange :: (Style, Style) -> Style -> Bool
unsafeIndex :: (Style, Style) -> Style -> Int
$cunsafeIndex :: (Style, Style) -> Style -> Int
index :: (Style, Style) -> Style -> Int
$cindex :: (Style, Style) -> Style -> Int
range :: (Style, Style) -> [Style]
$crange :: (Style, Style) -> [Style]
Ix, Eq Style
Style -> Style -> Bool
Style -> Style -> Ordering
Style -> Style -> Style
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 :: Style -> Style -> Style
$cmin :: Style -> Style -> Style
max :: Style -> Style -> Style
$cmax :: Style -> Style -> Style
>= :: Style -> Style -> Bool
$c>= :: Style -> Style -> Bool
> :: Style -> Style -> Bool
$c> :: Style -> Style -> Bool
<= :: Style -> Style -> Bool
$c<= :: Style -> Style -> Bool
< :: Style -> Style -> Bool
$c< :: Style -> Style -> Bool
compare :: Style -> Style -> Ordering
$ccompare :: Style -> Style -> Ordering
Ord, Int -> Style -> ShowS
[Style] -> ShowS
Style -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Style] -> ShowS
$cshowList :: [Style] -> ShowS
show :: Style -> String
$cshow :: Style -> String
showsPrec :: Int -> Style -> ShowS
$cshowsPrec :: Int -> Style -> ShowS
Show)
instance Semigroup Style where
Style
s <> :: Style -> Style -> Style
<> Style
_ = Style
s
type StyleSpec = (Text, [SGR])
type Styles = Array Style StyleSpec