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