about summary refs log tree commit diff
path: root/src/lib/XMonad/Custom/Theme.hs
blob: cfcd176b73d8b58c6ab5a4a1bb1d60f92f2148d2 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
-- |
-- Module                  : XMonad.Custom.Theme
-- Description             : Theming and styles
-- Copyright               : (c) Azat Bahawi 2018-2021
-- SPDX-License-Identifier : GPL-3.0-or-later
-- Maintainer              : azahi@teknik.io
-- Stability               : experimental
-- Portability             : non-portable
--

module XMonad.Custom.Theme
  ( font
  , black1
  , black2
  , red1
  , red2
  , green1
  , green2
  , yellow1
  , yellow2
  , blue1
  , blue2
  , magenta1
  , magenta2
  , cyan1
  , cyan2
  , white1
  , white2
  , colorN
  , colorF
  , gapBase
  , gapFull
  , border
  , tabTheme
  , promptTheme
  , hotPromptTheme
  ) where

import           Data.Char
import           Data.Function
import           Data.List                      ( isInfixOf )
import           Data.Ratio
import           Graphics.X11.Xlib.Types
import           XMonad.Layout.Decoration
import qualified XMonad.Prompt                 as P

font :: String
font = "xft:tewi:style=Regular:size=8" -- TODO CJKのフォールバックフォントを追加する

black1, black2 :: String -- TODO get variables from Xresources
(black1, black2) = ("#0b0806", "#2f2b2a")

-- | Red
red1, red2 :: String
(red1, red2) = ("#844d2c", "#a64848")

-- | Green
green1, green2 :: String
(green1, green2) = ("#57553a", "#897f5a")

-- | Yellow
yellow1, yellow2 :: String
(yellow1, yellow2) = ("#a17c38", "#c8b38d")

-- | Blue
blue1, blue2 :: String
(blue1, blue2) = ("#41434f", "#526274")

-- | Magenta
magenta1, magenta2 :: String
(magenta1, magenta2) = ("#6b4444", "#755c47")

-- | Cyan
cyan1, cyan2 :: String
(cyan1, cyan2) = ("#59664c", "#718062")

-- | White
white1, white2 :: String
(white1, white2) = ("#a19782", "#c1ab83")

colorN, colorF :: String
colorN = black2
colorF = white2

gapBase, gapFull :: Int
gapBase = 6
gapFull = gapBase * 2

height, border :: Dimension
height = 12 * 2
border = 1

tabTheme :: Theme
tabTheme = def { activeColor         = black1
               , inactiveColor       = black2
               , urgentColor         = red1
               , activeBorderColor   = white1
               , inactiveBorderColor = white2
               , urgentBorderColor   = red2
               , activeTextColor     = white1
               , inactiveTextColor   = white2
               , urgentTextColor     = red2
               , fontName            = font
               , decoHeight          = height
               }

promptTheme, hotPromptTheme :: P.XPConfig
promptTheme = def
  { P.font              = font
  , P.bgColor           = black1
  , P.fgColor           = white1
  , P.fgHLight          = white2
  , P.bgHLight          = black2
  , P.borderColor       = white2
  , P.promptBorderWidth = border
  , P.position = P.CenteredAt { P.xpCenterY = 3 % 10, P.xpWidth = 9 % 10 }
  , P.height            = height
  , P.maxComplRows      = Just 5
  , P.searchPredicate   = isInfixOf `on` map toLower
  , P.alwaysHighlight   = True
  }
hotPromptTheme = promptTheme { P.bgColor  = black2
                             , P.fgColor  = white2
                             , P.fgHLight = white1
                             , P.bgHLight = black1
                             }

Consider giving Nix/NixOS a try! <3