aboutsummaryrefslogtreecommitdiff
path: root/.config/XMonad/lib/Defaults.hs
blob: 15c278c7772667a34ada60c743717e1aee5bf3b6 (plain)
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
module Defaults where

import XMonad
import XMonad.Layout.Spacing
import XMonad.Layout.Tabbed
import XMonad.Actions.GridSelect


myBorder          = "#120F23"
myBorder'         = "#C44CF2"

myBorderWidth     :: Dimension
myBorderWidth     = 2

myFont            = "xft:Sauce Code Pro:style=Regular:size=14"

myModMask         = mod4Mask
myModMask'        = mod1Mask
myModShiftMask    = myModMask  .|. shiftMask
myModShiftMask'   = myModMask' .|. shiftMask

myLockscreen      = "notify-send 'to be set up!' 'to be set up!'"
myColorPicker     = "colorpicker --short --one-shot --preview | xsel -b"

myTerminal        = "open_terminal"
myTerminal'       = "alacritty"
myLauncher        = "dmenu_run"

volUp             = "pamixer -i 5"
volDown           = "pamixer -d 5"
volMute           = "pamixer -t"

backlightUp       = "brightnessctl s +5"
backlightDown     = "brightnessctl s 5-"

wifiOn            = "nmcli radio wifi on"
wifiOff :: String
wifiOff           = "nmcli radio wifi off"

screenshot        = "flameshot screen"
fullScreenshot    = "flameshot full"
customScreenshot  = "flameshot gui"

myBrowser         = "librewolf"
myBrowser'        = "brave"

myTorrentClient   = "qbittorrent"

myFileManager     = "pcmanfm"
myFileManager'    = "lf"

myTextEditor      = "emacs"
myTextEditor'     = "nvim"

-- workspaces
myExtraWorkspaces = [(xK_0, "十")]
myWorkspaces      = ["一", "二", "三", "四", "五", "六", "七", "八", "九"] ++ map snd myExtraWorkspaces

-- screen gaps
sGap = 4
wGap = 6

myGap  = spacingRaw True  (Border sGap sGap sGap sGap) True (Border wGap wGap wGap wGap) True

myTabTheme = def {
    fontName              = myFont
    , activeColor         = "#755999"
    , inactiveColor       = "#282c35"
    , activeBorderColor   = "#755999"
    , inactiveBorderColor = "#313846"
    , activeTextColor     = "#FFFFFF"
    , inactiveTextColor   = "#d0d0d0"
    , decoHeight          = 20
  }
myGSColorizer :: Window -> Bool -> X (String, String)
myGSColorizer = colorRangeFromClassName
  (0x28,0x2c,0x34) -- lowest inactive bg
  (0x28,0x2c,0x34) -- highest inactive bg
  -- (0xff,0xff,0xff) -- lowest inactive bg
  -- (0xff,0xff,0xff) -- highest inactive bg
  (0xc4,0x4c,0xf2) -- active bg
  (0xff,0xff,0xff) -- inactive fg
  (0xff,0xff,0xff) -- active fg

myGSConfig colorizer = (buildDefaultGSConfig myGSColorizer)
  { gs_cellheight   = 36
  , gs_cellwidth    = 180
  , gs_cellpadding  = 6
  , gs_originFractX = 0.5
  , gs_originFractY = 0.5
  , gs_font         = myFont
  }

myGridSelect = myGSConfig myGSColorizer

-- bar config

bottomBar  = "-b"
barDimensions = "1920x28+0+0"
barBackground = "#1E2120"
barForeground = "#FFFFFF"
barFont = "-f 'SauceCodePro:style=Regular:size=12' -f 'Source Han Sans JP:size=11'"

myLemonbar = "lemonbar " ++ bottomBar ++ " -g " ++ barDimensions ++ " -B '" ++ barBackground ++ "' -F '" ++ barForeground ++ "'" ++ barFont
-- myLemonbar = "cat > ~/lemonb/ffx"

-- wsVisibleBG = "#ffffff"
-- wsVisibleFG = "#FFFFFF"

wsVisibleOccupiedBG = "#ff0aa3"
wsVisibleOccupiedFG = "#FFFFFF"

-- multi monitor only
-- wsVisibleInactiveBG = "#ff0aa3"
-- wsVisibleInactiveFG = "#FFFFFF"

wsOccupiedBG = "#9b1bed"
wsOccupiedFG = "#FFFFFF"

wsEmptyBG = "#272526"
wsEmptyFG = "#9d00ff"

titleBG = "#272526"
titleFG = "#9d00ff"