{-# LANGUAGE TupleSections #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
module Brick.Themes
( CustomAttr(..)
, customFgL
, customBgL
, customStyleL
, Theme(..)
, newTheme
, themeDefaultAttrL
, themeDefaultMappingL
, themeCustomMappingL
, themeCustomDefaultAttrL
, ThemeDocumentation(..)
, themeDescriptionsL
, themeToAttrMap
, applyCustomizations
, loadCustomizations
, saveCustomizations
, saveTheme
)
where
import GHC.Generics (Generic)
import Graphics.Vty hiding ((<|>))
import Control.Monad (forM, join)
import Control.Applicative ((<|>))
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Map as M
import qualified Data.Semigroup as Sem
import Data.Tuple (swap)
import Data.List (intercalate)
import Data.Bits ((.|.), (.&.))
import Data.Maybe (fromMaybe, isNothing, catMaybes)
import Data.Monoid ((<>))
import qualified Data.Foldable as F
import Data.Ini.Config
import Brick.AttrMap (AttrMap, AttrName, attrMap, attrNameComponents)
import Brick.Types.TH (suffixLenses)
data CustomAttr =
CustomAttr { customFg :: Maybe (MaybeDefault Color)
, customBg :: Maybe (MaybeDefault Color)
, customStyle :: Maybe Style
}
deriving (Eq, Read, Show, Generic)
instance Sem.Semigroup CustomAttr where
a <> b =
CustomAttr { customFg = customFg a <|> customFg b
, customBg = customBg a <|> customBg b
, customStyle = customStyle a <|> customStyle b
}
instance Monoid CustomAttr where
mempty = CustomAttr Nothing Nothing Nothing
mappend = (Sem.<>)
data ThemeDocumentation =
ThemeDocumentation { themeDescriptions :: M.Map AttrName T.Text
}
deriving (Eq, Read, Show, Generic)
data Theme =
Theme { themeDefaultAttr :: Attr
, themeDefaultMapping :: M.Map AttrName Attr
, themeCustomDefaultAttr :: Maybe CustomAttr
, themeCustomMapping :: M.Map AttrName CustomAttr
}
deriving (Eq, Read, Show, Generic)
suffixLenses ''CustomAttr
suffixLenses ''Theme
suffixLenses ''ThemeDocumentation
defaultSectionName :: T.Text
defaultSectionName = "default"
otherSectionName :: T.Text
otherSectionName = "other"
newTheme :: Attr -> [(AttrName, Attr)] -> Theme
newTheme def mapping =
Theme { themeDefaultAttr = def
, themeDefaultMapping = M.fromList mapping
, themeCustomDefaultAttr = Nothing
, themeCustomMapping = mempty
}
themeToAttrMap :: Theme -> AttrMap
themeToAttrMap t =
attrMap (customizeAttr (themeCustomDefaultAttr t) (themeDefaultAttr t)) customMap
where
customMap = F.foldr f [] (M.toList $ themeDefaultMapping t)
f (aName, attr) mapping =
let a' = customizeAttr (M.lookup aName (themeCustomMapping t)) attr
in (aName, a'):mapping
customizeAttr :: Maybe CustomAttr -> Attr -> Attr
customizeAttr Nothing a = a
customizeAttr (Just c) a =
let fg = fromMaybe (attrForeColor a) (customFg c)
bg = fromMaybe (attrBackColor a) (customBg c)
sty = maybe (attrStyle a) SetTo (customStyle c)
in a { attrForeColor = fg
, attrBackColor = bg
, attrStyle = sty
}
isNullCustomization :: CustomAttr -> Bool
isNullCustomization c =
isNothing (customFg c) &&
isNothing (customBg c) &&
isNothing (customStyle c)
parseColor :: T.Text -> Either String (MaybeDefault Color)
parseColor s =
let stripped = T.strip $ T.toLower s
normalize (t, c) = (T.toLower t, c)
in if stripped == "default"
then Right Default
else maybe (Left $ "Invalid color: " <> show stripped) (Right . SetTo) $
lookup stripped (normalize <$> swap <$> allColors)
allColors :: [(Color, T.Text)]
allColors =
[ (black, "black")
, (red, "red")
, (green, "green")
, (yellow, "yellow")
, (blue, "blue")
, (magenta, "magenta")
, (cyan, "cyan")
, (white, "white")
, (brightBlack, "brightBlack")
, (brightRed, "brightRed")
, (brightGreen, "brightGreen")
, (brightYellow, "brightYellow")
, (brightBlue, "brightBlue")
, (brightMagenta, "brightMagenta")
, (brightCyan, "brightCyan")
, (brightWhite, "brightWhite")
]
allStyles :: [(T.Text, Style)]
allStyles =
[ ("standout", standout)
, ("underline", underline)
, ("reversevideo", reverseVideo)
, ("blink", blink)
, ("dim", dim)
, ("bold", bold)
]
parseStyle :: T.Text -> Either String Style
parseStyle s =
let lookupStyle "" = Right Nothing
lookupStyle n = case lookup n normalizedStyles of
Just sty -> Right $ Just sty
Nothing -> Left $ T.unpack $ "Invalid style: " <> n
stripped = T.strip $ T.toLower s
normalize (n, a) = (T.toLower n, a)
normalizedStyles = normalize <$> allStyles
bracketed = "[" `T.isPrefixOf` stripped &&
"]" `T.isSuffixOf` stripped
unbracketed = T.tail $ T.init stripped
parseStyleList = do
ss <- mapM lookupStyle $ T.strip <$> T.splitOn "," unbracketed
return $ foldr (.|.) 0 $ catMaybes ss
in if bracketed
then parseStyleList
else do
result <- lookupStyle stripped
case result of
Nothing -> Left $ "Invalid style: " <> show stripped
Just sty -> Right sty
themeParser :: Theme -> IniParser (Maybe CustomAttr, M.Map AttrName CustomAttr)
themeParser t = do
let parseCustomAttr basename = do
c <- CustomAttr <$> fieldMbOf (basename <> ".fg") parseColor
<*> fieldMbOf (basename <> ".bg") parseColor
<*> fieldMbOf (basename <> ".style") parseStyle
return $ if isNullCustomization c then Nothing else Just c
defCustom <- sectionMb defaultSectionName $ do
parseCustomAttr "default"
customMap <- sectionMb otherSectionName $ do
catMaybes <$> (forM (M.keys $ themeDefaultMapping t) $ \an ->
(fmap (an,)) <$> parseCustomAttr (makeFieldName $ attrNameComponents an)
)
return (join defCustom, M.fromList $ fromMaybe [] customMap)
applyCustomizations :: Maybe CustomAttr
-> (AttrName -> Maybe CustomAttr)
-> Theme
-> Theme
applyCustomizations customDefAttr lookupAttr t =
let customMap = foldr nextAttr mempty (M.keys $ themeDefaultMapping t)
nextAttr an m = case lookupAttr an of
Nothing -> m
Just custom -> M.insert an custom m
in t { themeCustomDefaultAttr = customDefAttr
, themeCustomMapping = customMap
}
loadCustomizations :: FilePath -> Theme -> IO (Either String Theme)
loadCustomizations path t = do
content <- T.readFile path
case parseIniFile content (themeParser t) of
Left e -> return $ Left e
Right (customDef, customMap) ->
return $ Right $ applyCustomizations customDef (flip M.lookup customMap) t
vtyColorName :: Color -> T.Text
vtyColorName (Color240 _) = error "Color240 space not supported yet"
vtyColorName c =
fromMaybe (error $ "Invalid color: " <> show c)
(lookup c allColors)
makeFieldName :: [String] -> T.Text
makeFieldName cs = T.pack $ intercalate "." cs
serializeCustomColor :: [String] -> MaybeDefault Color -> T.Text
serializeCustomColor cs cc =
let cName = case cc of
Default -> "default"
SetTo c -> vtyColorName c
KeepCurrent -> error "serializeCustomColor does not support KeepCurrent"
in makeFieldName cs <> " = " <> cName
serializeCustomStyle :: [String] -> Style -> T.Text
serializeCustomStyle cs s =
let activeStyles = filter (\(_, a) -> a .&. s == a) allStyles
styleStr = case activeStyles of
[(single, _)] -> single
many -> "[" <> (T.intercalate ", " $ fst <$> many) <> "]"
in makeFieldName cs <> " = " <> styleStr
serializeCustomAttr :: [String] -> CustomAttr -> [T.Text]
serializeCustomAttr cs c =
catMaybes [ serializeCustomColor (cs <> ["fg"]) <$> customFg c
, serializeCustomColor (cs <> ["bg"]) <$> customBg c
, serializeCustomStyle (cs <> ["style"]) <$> customStyle c
]
emitSection :: T.Text -> [T.Text] -> [T.Text]
emitSection _ [] = []
emitSection secName ls = ("[" <> secName <> "]") : ls
saveCustomizations :: FilePath -> Theme -> IO ()
saveCustomizations path t = do
let defSection = fromMaybe [] $
serializeCustomAttr ["default"] <$> themeCustomDefaultAttr t
mapSection = concat $ flip map (M.keys $ themeDefaultMapping t) $ \an ->
maybe [] (serializeCustomAttr (attrNameComponents an)) $
M.lookup an $ themeCustomMapping t
content = T.unlines $ (emitSection defaultSectionName defSection) <>
(emitSection otherSectionName mapSection)
T.writeFile path content
saveTheme :: FilePath -> Theme -> IO ()
saveTheme path t = do
let defSection = serializeCustomAttr ["default"] $
fromMaybe (attrToCustom $ themeDefaultAttr t) (themeCustomDefaultAttr t)
mapSection = concat $ flip map (M.toList $ themeDefaultMapping t) $ \(an, def) ->
serializeCustomAttr (attrNameComponents an) $
fromMaybe (attrToCustom def) (M.lookup an $ themeCustomMapping t)
content = T.unlines $ (emitSection defaultSectionName defSection) <>
(emitSection otherSectionName mapSection)
T.writeFile path content
attrToCustom :: Attr -> CustomAttr
attrToCustom a =
CustomAttr { customFg = Just $ attrForeColor a
, customBg = Just $ attrForeColor a
, customStyle = case attrStyle a of
SetTo s -> Just s
_ -> Nothing
}