xmonad-config/lib/XMonad/Internal/Theme.hs

179 lines
4.3 KiB
Haskell
Raw Normal View History

2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Theme for XMonad and Xmobar
2020-04-01 20:17:47 -04:00
module XMonad.Internal.Theme
( baseColor
, bgColor
, fgColor
, bordersColor
, warningColor
, errorColor
, selectedFgColor
, selectedBgColor
, selectedBordersColor
, backdropBaseColor
, backdropFgColor
, backdropTextColor
, blend'
, darken'
, Slant(..)
, Weight(..)
, ThemeFont(..)
, fmtFontXFT
, font
, tabbedTheme
, promptTheme
) where
2020-04-01 21:03:00 -04:00
import Data.Char
2020-04-01 20:17:47 -04:00
import Data.Colour
import Data.Colour.SRGB
import Data.List
2020-03-16 13:50:08 -04:00
import qualified XMonad.Layout.Decoration as D
2020-03-22 17:59:49 -04:00
import qualified XMonad.Prompt as P
2020-03-16 13:50:08 -04:00
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Colors - vocabulary roughly based on GTK themes
2020-03-16 13:50:08 -04:00
baseColor :: String
baseColor = "#f7f7f7"
bgColor :: String
bgColor = "#d6d6d6"
fgColor :: String
2020-03-16 14:48:38 -04:00
fgColor = "#2c2c2c"
2020-03-16 13:50:08 -04:00
bordersColor :: String
2020-03-22 17:59:49 -04:00
bordersColor = darken' 0.3 bgColor
2020-03-16 13:50:08 -04:00
warningColor :: String
warningColor = "#ffca28"
errorColor :: String
errorColor = "#e53935"
selectedFgColor :: String
selectedFgColor = "#ffffff"
selectedBgColor :: String
2021-07-04 16:45:53 -04:00
selectedBgColor = "#7f66ff"
2020-03-16 13:50:08 -04:00
2020-03-22 17:59:49 -04:00
selectedBordersColor :: String
2021-07-04 16:45:53 -04:00
selectedBordersColor = "#5948B3"
2020-03-22 17:59:49 -04:00
2020-03-16 13:50:08 -04:00
backdropBaseColor :: String
backdropBaseColor = baseColor
backdropTextColor :: String
backdropTextColor = blend' 0.95 fgColor backdropBaseColor
backdropFgColor :: String
backdropFgColor = blend' 0.75 fgColor bgColor
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Color functions
2020-03-16 13:50:08 -04:00
blend' :: Float -> String -> String -> String
blend' wt c0 c1 = sRGB24show $ blend wt (sRGB24read c0) (sRGB24read c1)
darken' :: Float -> String -> String
darken' wt = sRGB24show . darken wt . sRGB24read
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Fonts
2020-03-16 13:50:08 -04:00
2020-03-22 17:59:49 -04:00
data Slant = Roman
| Italic
| Oblique
deriving (Eq, Show)
data Weight = Light
| Medium
| Demibold
| Bold
| Black
deriving (Eq, Show)
data ThemeFont = ThemeFont
{ family :: String
, weight :: Maybe Weight
, slant :: Maybe Slant
, size :: Maybe Int
, pixelsize :: Maybe Int
, antialias :: Maybe Bool
}
2020-03-16 13:50:08 -04:00
fmtFontXFT :: ThemeFont -> String
fmtFontXFT ThemeFont
{ family = f
, weight = w
, slant = l
, size = s
2020-04-01 21:03:00 -04:00
, pixelsize = p
2020-03-16 13:50:08 -04:00
, antialias = a
2020-04-01 21:03:00 -04:00
} = intercalate ":" $ ["xft", f] ++ elems
2020-03-16 13:50:08 -04:00
where
2020-04-01 21:03:00 -04:00
elems = [ k ++ "=" ++ v | (k, Just v) <- [ ("weight", showLower w)
, ("slant", showLower l)
, ("size", showLower s)
, ("pixelsize", showLower p)
, ("antialias", showLower a)
]
]
showLower :: Show a => Maybe a -> Maybe String
showLower = fmap (fmap toLower . show)
2020-03-16 13:50:08 -04:00
2020-04-01 20:17:47 -04:00
font :: ThemeFont
2020-03-16 13:50:08 -04:00
font = ThemeFont
{ family = "DejaVu Sans"
2020-03-16 14:48:38 -04:00
, size = Just 10
2020-03-16 13:50:08 -04:00
, antialias = Just True
, weight = Nothing
, slant = Nothing
, pixelsize = Nothing
}
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Complete themes
2020-03-16 13:50:08 -04:00
2020-04-01 20:17:47 -04:00
tabbedTheme :: D.Theme
2020-03-16 13:50:08 -04:00
tabbedTheme = D.def
2020-03-16 14:48:38 -04:00
{ D.fontName = fmtFontXFT font { weight = Just Bold }
2020-03-16 13:50:08 -04:00
, D.activeTextColor = fgColor
, D.activeColor = bgColor
, D.activeBorderColor = bgColor
, D.inactiveTextColor = backdropTextColor
, D.inactiveColor = backdropFgColor
, D.inactiveBorderColor = backdropFgColor
, D.urgentTextColor = darken' 0.5 errorColor
, D.urgentColor = errorColor
, D.urgentBorderColor = errorColor
-- this is in a newer version
-- , D.activeBorderWidth = 0
-- , D.inactiveBorderWidth = 0
-- , D.urgentBorderWidth = 0
, D.decoHeight = 20
, D.windowTitleAddons = []
, D.windowTitleIcons = []
}
2020-04-01 20:17:47 -04:00
promptTheme :: P.XPConfig
2020-03-16 13:50:08 -04:00
promptTheme = P.def
2020-04-01 22:49:36 -04:00
{ P.font = fmtFontXFT font { size = Just 12 }
2020-03-16 13:50:08 -04:00
, P.bgColor = bgColor
, P.fgColor = fgColor
, P.fgHLight = selectedFgColor
, P.bgHLight = selectedBgColor
, P.borderColor = bordersColor
, P.promptBorderWidth = 1
2020-04-01 22:49:36 -04:00
, P.height = 35
2020-03-16 13:50:08 -04:00
, P.position = P.CenteredAt 0.5 0.5
}