module Yi.Style where
import Data.Word (Word8)
import Data.Char (chr, ord)
import Data.Monoid
data Attributes = Attributes
{ Attributes -> Color
foreground :: !Color
, Attributes -> Color
background :: !Color
, Attributes -> Bool
reverseAttr :: !Bool
, Attributes -> Bool
bold :: !Bool
, Attributes -> Bool
italic :: !Bool
, Attributes -> Bool
underline :: !Bool
} deriving (Attributes -> Attributes -> Bool
(Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool) -> Eq Attributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attributes -> Attributes -> Bool
== :: Attributes -> Attributes -> Bool
$c/= :: Attributes -> Attributes -> Bool
/= :: Attributes -> Attributes -> Bool
Eq, Eq Attributes
Eq Attributes =>
(Attributes -> Attributes -> Ordering)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Attributes)
-> (Attributes -> Attributes -> Attributes)
-> Ord Attributes
Attributes -> Attributes -> Bool
Attributes -> Attributes -> Ordering
Attributes -> Attributes -> Attributes
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
$ccompare :: Attributes -> Attributes -> Ordering
compare :: Attributes -> Attributes -> Ordering
$c< :: Attributes -> Attributes -> Bool
< :: Attributes -> Attributes -> Bool
$c<= :: Attributes -> Attributes -> Bool
<= :: Attributes -> Attributes -> Bool
$c> :: Attributes -> Attributes -> Bool
> :: Attributes -> Attributes -> Bool
$c>= :: Attributes -> Attributes -> Bool
>= :: Attributes -> Attributes -> Bool
$cmax :: Attributes -> Attributes -> Attributes
max :: Attributes -> Attributes -> Attributes
$cmin :: Attributes -> Attributes -> Attributes
min :: Attributes -> Attributes -> Attributes
Ord, Int -> Attributes -> ShowS
[Attributes] -> ShowS
Attributes -> String
(Int -> Attributes -> ShowS)
-> (Attributes -> String)
-> ([Attributes] -> ShowS)
-> Show Attributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attributes -> ShowS
showsPrec :: Int -> Attributes -> ShowS
$cshow :: Attributes -> String
show :: Attributes -> String
$cshowList :: [Attributes] -> ShowS
showList :: [Attributes] -> ShowS
Show)
emptyAttributes :: Attributes
emptyAttributes :: Attributes
emptyAttributes = Attributes { foreground :: Color
foreground = Color
Default, background :: Color
background = Color
Default, reverseAttr :: Bool
reverseAttr = Bool
False, bold :: Bool
bold = Bool
False, italic :: Bool
italic = Bool
False, underline :: Bool
underline = Bool
False }
type Style = Endo Attributes
data UIStyle = UIStyle
{ UIStyle -> Attributes
modelineAttributes :: Attributes
, StyleName
modelineFocusStyle :: Style
, UIStyle -> Attributes
tabBarAttributes :: Attributes
, StyleName
tabInFocusStyle :: Style
, StyleName
tabNotFocusedStyle :: Style
, UIStyle -> Attributes
baseAttributes :: Attributes
, StyleName
selectedStyle :: Style
, StyleName
eofStyle :: Style
, StyleName
errorStyle :: Style
, StyleName
hintStyle :: Style
, StyleName
strongHintStyle :: Style
, :: Style
, :: Style
, StyleName
keywordStyle :: Style
, StyleName
numberStyle :: Style
, StyleName
preprocessorStyle :: Style
, StyleName
stringStyle :: Style
, StyleName
longStringStyle :: Style
, StyleName
typeStyle :: Style
, StyleName
dataConstructorStyle
:: Style
, StyleName
importStyle :: Style
, StyleName
builtinStyle :: Style
, StyleName
regexStyle :: Style
, StyleName
variableStyle :: Style
, StyleName
operatorStyle :: Style
, StyleName
quoteStyle :: Style
, StyleName
makeFileAction :: Style
, StyleName
makeFileRuleHead :: Style
}
type StyleName = UIStyle -> Style
withFg, withBg :: Color -> Style
withFg :: Color -> Endo Attributes
withFg Color
c = (Attributes -> Attributes) -> Endo Attributes
forall a. (a -> a) -> Endo a
Endo ((Attributes -> Attributes) -> Endo Attributes)
-> (Attributes -> Attributes) -> Endo Attributes
forall a b. (a -> b) -> a -> b
$ \Attributes
s -> Attributes
s { foreground = c }
withBg :: Color -> Endo Attributes
withBg Color
c = (Attributes -> Attributes) -> Endo Attributes
forall a. (a -> a) -> Endo a
Endo ((Attributes -> Attributes) -> Endo Attributes)
-> (Attributes -> Attributes) -> Endo Attributes
forall a b. (a -> b) -> a -> b
$ \Attributes
s -> Attributes
s { background = c }
withBd, withItlc, withUnderline, withReverse :: Bool -> Style
withBd :: Bool -> Endo Attributes
withBd Bool
c = (Attributes -> Attributes) -> Endo Attributes
forall a. (a -> a) -> Endo a
Endo ((Attributes -> Attributes) -> Endo Attributes)
-> (Attributes -> Attributes) -> Endo Attributes
forall a b. (a -> b) -> a -> b
$ \Attributes
s -> Attributes
s { bold = c }
withItlc :: Bool -> Endo Attributes
withItlc Bool
c = (Attributes -> Attributes) -> Endo Attributes
forall a. (a -> a) -> Endo a
Endo ((Attributes -> Attributes) -> Endo Attributes)
-> (Attributes -> Attributes) -> Endo Attributes
forall a b. (a -> b) -> a -> b
$ \Attributes
s -> Attributes
s { italic = c }
withUnderline :: Bool -> Endo Attributes
withUnderline Bool
c = (Attributes -> Attributes) -> Endo Attributes
forall a. (a -> a) -> Endo a
Endo ((Attributes -> Attributes) -> Endo Attributes)
-> (Attributes -> Attributes) -> Endo Attributes
forall a b. (a -> b) -> a -> b
$ \Attributes
s -> Attributes
s { underline = c }
withReverse :: Bool -> Endo Attributes
withReverse Bool
c = (Attributes -> Attributes) -> Endo Attributes
forall a. (a -> a) -> Endo a
Endo ((Attributes -> Attributes) -> Endo Attributes)
-> (Attributes -> Attributes) -> Endo Attributes
forall a b. (a -> b) -> a -> b
$ \Attributes
s -> Attributes
s { reverseAttr = c }
defaultStyle :: StyleName
defaultStyle :: StyleName
defaultStyle = StyleName
forall a. Monoid a => a
mempty
data Color
= RGB {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8
| Default
deriving (Color -> Color -> Bool
(Color -> Color -> Bool) -> (Color -> Color -> Bool) -> Eq Color
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
/= :: Color -> Color -> Bool
Eq,Eq Color
Eq Color =>
(Color -> Color -> Ordering)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Color)
-> (Color -> Color -> Color)
-> Ord 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
$ccompare :: Color -> Color -> Ordering
compare :: Color -> Color -> Ordering
$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
>= :: Color -> Color -> Bool
$cmax :: Color -> Color -> Color
max :: Color -> Color -> Color
$cmin :: Color -> Color -> Color
min :: Color -> Color -> Color
Ord,Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
(Int -> Color -> ShowS)
-> (Color -> String) -> ([Color] -> ShowS) -> Show Color
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Color -> ShowS
showsPrec :: Int -> Color -> ShowS
$cshow :: Color -> String
show :: Color -> String
$cshowList :: [Color] -> ShowS
showList :: [Color] -> ShowS
Show)
colorToText :: Color -> String
colorToText :: Color -> String
colorToText Color
Default = String
"default"
colorToText (RGB Word8
r Word8
g Word8
b) = (Char
'#'Char -> ShowS
forall a. a -> [a] -> [a]
:) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> ShowS
forall {a}. Integral a => a -> ShowS
showsHex Word8
r ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> ShowS
forall {a}. Integral a => a -> ShowS
showsHex Word8
g ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> ShowS
forall {a}. Integral a => a -> ShowS
showsHex Word8
b ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ []
where showsHex :: a -> ShowS
showsHex a
x String
s = a -> Char
forall {a}. Integral a => a -> Char
showHex1 (a
x a -> a -> a
forall a. Integral a => a -> a -> a
`div` a
16) Char -> ShowS
forall a. a -> [a] -> [a]
: a -> Char
forall {a}. Integral a => a -> Char
showHex1 (a
x a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
16) Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
showHex1 :: a -> Char
showHex1 a
x | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
10 = Int -> Char
chr (Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x)
| Bool
otherwise = Int -> Char
chr (Char -> Int
ord Char
'A' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
10)
black, grey, lightGrey, darkred, red, darkgreen, green, brown, yellow :: Color
darkblue, blue, purple, magenta, darkcyan, cyan, white, brightwhite :: Color
black :: Color
black = Word8 -> Word8 -> Word8 -> Color
RGB Word8
0 Word8
0 Word8
0
grey :: Color
grey = Word8 -> Word8 -> Word8 -> Color
RGB Word8
128 Word8
128 Word8
128
lightGrey :: Color
lightGrey = Word8 -> Word8 -> Word8 -> Color
RGB Word8
100 Word8
100 Word8
100
darkred :: Color
darkred = Word8 -> Word8 -> Word8 -> Color
RGB Word8
139 Word8
0 Word8
0
red :: Color
red = Word8 -> Word8 -> Word8 -> Color
RGB Word8
255 Word8
0 Word8
0
darkgreen :: Color
darkgreen = Word8 -> Word8 -> Word8 -> Color
RGB Word8
0 Word8
100 Word8
0
green :: Color
green = Word8 -> Word8 -> Word8 -> Color
RGB Word8
0 Word8
128 Word8
0
brown :: Color
brown = Word8 -> Word8 -> Word8 -> Color
RGB Word8
165 Word8
42 Word8
42
yellow :: Color
yellow = Word8 -> Word8 -> Word8 -> Color
RGB Word8
255 Word8
255 Word8
0
darkblue :: Color
darkblue = Word8 -> Word8 -> Word8 -> Color
RGB Word8
0 Word8
0 Word8
139
blue :: Color
blue = Word8 -> Word8 -> Word8 -> Color
RGB Word8
0 Word8
0 Word8
255
purple :: Color
purple = Word8 -> Word8 -> Word8 -> Color
RGB Word8
128 Word8
0 Word8
128
magenta :: Color
magenta = Word8 -> Word8 -> Word8 -> Color
RGB Word8
255 Word8
0 Word8
255
darkcyan :: Color
darkcyan = Word8 -> Word8 -> Word8 -> Color
RGB Word8
0 Word8
139 Word8
139
cyan :: Color
cyan = Word8 -> Word8 -> Word8 -> Color
RGB Word8
0 Word8
255 Word8
255
white :: Color
white = Word8 -> Word8 -> Word8 -> Color
RGB Word8
165 Word8
165 Word8
165
brightwhite :: Color
brightwhite = Word8 -> Word8 -> Word8 -> Color
RGB Word8
255 Word8
255 Word8
255