summaryrefslogtreecommitdiff
path: root/accounts/gkleen@sif/xmonad
diff options
context:
space:
mode:
Diffstat (limited to 'accounts/gkleen@sif/xmonad')
-rw-r--r--accounts/gkleen@sif/xmonad/.gitignore4
-rw-r--r--accounts/gkleen@sif/xmonad/default.nix7
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Mpv.hs127
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs94
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyShell.hs105
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs243
-rw-r--r--accounts/gkleen@sif/xmonad/package.yaml30
-rw-r--r--accounts/gkleen@sif/xmonad/stack.nix17
-rw-r--r--accounts/gkleen@sif/xmonad/stack.yaml10
-rw-r--r--accounts/gkleen@sif/xmonad/xmonad-yggdrasil.nix21
-rw-r--r--accounts/gkleen@sif/xmonad/xmonad.hs902
11 files changed, 1560 insertions, 0 deletions
diff --git a/accounts/gkleen@sif/xmonad/.gitignore b/accounts/gkleen@sif/xmonad/.gitignore
new file mode 100644
index 00000000..c11891cd
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/.gitignore
@@ -0,0 +1,4 @@
1**/#*#
2**/.stack-work/
3/stack.yaml.lock
4/*.cabal
diff --git a/accounts/gkleen@sif/xmonad/default.nix b/accounts/gkleen@sif/xmonad/default.nix
new file mode 100644
index 00000000..8790c12f
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/default.nix
@@ -0,0 +1,7 @@
1argumentPackages@{ ... }:
2
3let
4 # defaultPackages = (import ./stackage.nix {});
5 # haskellPackages = defaultPackages // argumentPackages;
6 haskellPackages = argumentPackages;
7in haskellPackages.callPackage ./xmonad-yggdrasil.nix {}
diff --git a/accounts/gkleen@sif/xmonad/lib/XMonad/Mpv.hs b/accounts/gkleen@sif/xmonad/lib/XMonad/Mpv.hs
new file mode 100644
index 00000000..e6accdcc
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/lib/XMonad/Mpv.hs
@@ -0,0 +1,127 @@
1{-# LANGUAGE DeriveGeneric, OverloadedLists, OverloadedStrings, ViewPatterns, ExistentialQuantification, MultiWayIf #-}
2
3module XMonad.Mpv
4 ( MpvCommand(..), MpvResponse(..), MpvException(..)
5 , mpv
6 , mpvDir
7 , mpvAll, mpvOne
8 , mpvResponse
9 ) where
10
11import Data.Aeson
12
13import Data.Monoid
14
15import Network.Socket hiding (recv)
16import Network.Socket.ByteString
17
18import qualified Data.ByteString as BS
19import qualified Data.ByteString.Char8 as CBS
20import qualified Data.ByteString.Lazy as LBS
21
22import GHC.Generics (Generic)
23import Data.Typeable (Typeable)
24import Data.String (IsString(..))
25
26import Control.Exception
27
28import System.IO.Temp (getCanonicalTemporaryDirectory)
29
30import Control.Monad
31import Control.Exception (bracket)
32import Control.Monad.IO.Class (MonadIO(..))
33
34import System.FilePath
35import System.Directory (getDirectoryContents)
36
37import Data.List
38import Data.Either
39import Data.Maybe
40
41import Debug.Trace
42
43
44data MpvCommand
45 = forall a. ToJSON a => MpvSetProperty String a
46 | MpvGetProperty String
47data MpvResponse
48 = MpvError String
49 | MpvSuccess (Maybe Value)
50 deriving (Read, Show, Generic, Eq)
51data MpvException = MpvException String
52 | MpvNoValue
53 | MpvNoParse String
54 deriving (Generic, Typeable, Read, Show)
55instance Exception MpvException
56
57
58instance ToJSON MpvCommand where
59 toJSON (MpvSetProperty name val) = Array ["set_property", fromString name, toJSON val]
60 toJSON (MpvGetProperty name) = Array ["get_property", fromString name]
61
62instance FromJSON MpvResponse where
63 parseJSON = withObject "response object" $ \obj -> do
64 mval <- obj .:? "data"
65 err <- obj .: "error"
66
67 let ret
68 | err == "success" = MpvSuccess mval
69 | otherwise = MpvError err
70
71 return ret
72
73mpvSocket :: FilePath -> (Socket -> IO a) -> IO a
74mpvSocket sockPath = withSocketsDo . bracket mkSock close
75 where
76 mkSock = do
77 sock <- socket AF_UNIX Stream defaultProtocol
78 connect sock $ SockAddrUnix (traceId sockPath)
79 return sock
80
81mpvResponse :: FromJSON v => MpvResponse -> IO v
82mpvResponse (MpvError str) = throwIO $ MpvException str
83mpvResponse (MpvSuccess Nothing) = throwIO MpvNoValue
84mpvResponse (MpvSuccess (Just v)) = case fromJSON v of
85 Success v' -> return v'
86 Error str -> throwIO $ MpvNoParse str
87
88mpv :: FilePath -> MpvCommand -> IO MpvResponse
89mpv sockPath cmd = mpvSocket sockPath $ \sock -> do
90 let message = (`BS.append` "\n") . LBS.toStrict . encode $ Object [("command", toJSON cmd)]
91 traceIO $ show message
92 sendAll sock message
93 let recvAll = do
94 prefix <- recv sock 4096
95 if
96 | (prefix', rest) <- CBS.break (== '\n') prefix
97 , not (BS.null rest) -> return prefix'
98 | BS.null prefix -> return prefix
99 | otherwise -> BS.append prefix <$> recvAll
100 response <- recvAll
101 traceIO $ show response
102 either (ioError . userError) return . traceShowId $ eitherDecodeStrict' response
103
104mpvDir :: Exception e => FilePath -> (FilePath -> [(FilePath, Either e MpvResponse)] -> Maybe MpvCommand) -> IO [(FilePath, Either e MpvResponse)]
105mpvDir dir step = do
106 socks <- filter (".sock" `isSuffixOf`) <$> getDirectoryContents dir
107 go [] socks
108 where
109 go acc [] = return acc
110 go acc (sock:socks)
111 | Just cmd <- step sock acc = do
112 res <- try $ mpv (dir </> sock) cmd
113 go ((sock, res) : acc) socks
114 | otherwise =
115 go acc socks
116
117mpvAll :: FilePath -> MpvCommand -> IO [MpvResponse]
118mpvAll dir cmd = do
119 results <- map snd <$> (mpvDir dir (\_ _ -> Just cmd) :: IO [(FilePath, Either SomeException MpvResponse)])
120 mapM (either throwIO return) results
121
122mpvOne :: FilePath -> MpvCommand -> IO (Maybe MpvResponse)
123mpvOne dir cmd = listToMaybe . snd . partitionEithers . map snd <$> (mpvDir dir step :: IO [(FilePath, Either SomeException MpvResponse)])
124 where
125 step _ results
126 | any (isRight . snd) results = Nothing
127 | otherwise = Just cmd
diff --git a/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs
new file mode 100644
index 00000000..1caefae5
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs
@@ -0,0 +1,94 @@
1module XMonad.Prompt.MyPass
2 (
3 -- * Usages
4 -- $usages
5 mkPassPrompt
6 ) where
7
8import Control.Monad (liftM)
9import XMonad.Core
10import XMonad.Prompt ( XPrompt
11 , showXPrompt
12 , commandToComplete
13 , nextCompletion
14 , getNextCompletion
15 , XPConfig
16 , mkXPrompt
17 , searchPredicate)
18import System.Directory (getHomeDirectory)
19import System.FilePath (takeExtension, dropExtension, combine)
20import System.Posix.Env (getEnv)
21import XMonad.Util.Run (runProcessWithInput)
22
23-- $usages
24-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
25--
26-- > import XMonad.Prompt.Pass
27--
28-- Then add a keybinding for 'passPrompt', 'passGeneratePrompt' or 'passRemovePrompt':
29--
30-- > , ((modMask x , xK_p) , passPrompt xpconfig)
31-- > , ((modMask x .|. controlMask, xK_p) , passGeneratePrompt xpconfig)
32-- > , ((modMask x .|. controlMask .|. shiftMask, xK_p), passRemovePrompt xpconfig)
33--
34-- For detailed instructions on:
35--
36-- - editing your key bindings, see "XMonad.Doc.Extending#Editing_key_bindings".
37--
38-- - how to setup the password storage, see <http://git.zx2c4.com/password-store/about/>
39--
40
41type Predicate = String -> String -> Bool
42
43getPassCompl :: [String] -> Predicate -> String -> IO [String]
44getPassCompl compls p s
45 | length s <= minL
46 , all ((> minL) . length) compls = return []
47 | otherwise = do return $ filter (p s) compls
48 where
49 minL = 3
50
51type PromptLabel = String
52
53data Pass = Pass PromptLabel
54
55instance XPrompt Pass where
56 showXPrompt (Pass prompt) = prompt ++ ": "
57 commandToComplete _ c = c
58 nextCompletion _ = getNextCompletion
59
60-- | Default password store folder in $HOME/.password-store
61--
62passwordStoreFolderDefault :: String -> String
63passwordStoreFolderDefault home = combine home ".password-store"
64
65-- | Compute the password store's location.
66-- Use the PASSWORD_STORE_DIR environment variable to set the password store.
67-- If empty, return the password store located in user's home.
68--
69passwordStoreFolder :: IO String
70passwordStoreFolder =
71 getEnv "PASSWORD_STORE_DIR" >>= computePasswordStoreDir
72 where computePasswordStoreDir Nothing = liftM passwordStoreFolderDefault getHomeDirectory
73 computePasswordStoreDir (Just storeDir) = return storeDir
74
75-- | A pass prompt factory
76--
77mkPassPrompt :: PromptLabel -> (String -> X ()) -> XPConfig -> X ()
78mkPassPrompt promptLabel passwordFunction xpconfig = do
79 passwords <- io (passwordStoreFolder >>= getPasswords)
80 mkXPrompt (Pass promptLabel) xpconfig (getPassCompl passwords $ searchPredicate xpconfig) passwordFunction
81
82-- | Retrieve the list of passwords from the password storage 'passwordStoreDir
83getPasswords :: FilePath -> IO [String]
84getPasswords passwordStoreDir = do
85 files <- runProcessWithInput "find" [
86 passwordStoreDir,
87 "-type", "f",
88 "-name", "*.gpg",
89 "-printf", "%P\n"] []
90 return $ map removeGpgExtension $ lines files
91
92removeGpgExtension :: String -> String
93removeGpgExtension file | takeExtension file == ".gpg" = dropExtension file
94 | otherwise = file
diff --git a/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyShell.hs b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyShell.hs
new file mode 100644
index 00000000..c268f87d
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyShell.hs
@@ -0,0 +1,105 @@
1module XMonad.Prompt.MyShell
2 ( Shell (..)
3 , shellPrompt
4 , prompt
5 , safePrompt
6 , unsafePrompt
7 , getCommands
8 , getShellCompl
9 , split
10 ) where
11
12import Codec.Binary.UTF8.String (encodeString)
13import Control.Exception as E
14import Control.Monad (forM)
15import Data.List (isPrefixOf)
16import System.Directory (doesDirectoryExist, getDirectoryContents)
17import System.Environment (getEnv)
18import System.Posix.Files (getFileStatus, isDirectory)
19
20import XMonad hiding (config)
21import XMonad.Prompt
22import XMonad.Util.Run
23
24econst :: Monad m => a -> IOException -> m a
25econst = const . return
26
27data Shell = Shell String
28
29instance XPrompt Shell where
30 showXPrompt (Shell q) = q
31 completionToCommand _ = escape
32
33shellPrompt :: String -> XPConfig -> X ()
34shellPrompt q c = do
35 cmds <- io getCommands
36 mkXPrompt (Shell q) c (getShellCompl cmds) spawn
37
38{- $spawns
39 See safe and unsafeSpawn in "XMonad.Util.Run".
40 prompt is an alias for safePrompt;
41 safePrompt and unsafePrompt work on the same principles, but will use
42 XPrompt to interactively query the user for input; the appearance is
43 set by passing an XPConfig as the second argument. The first argument
44 is the program to be run with the interactive input.
45 You would use these like this:
46
47 > , ((modm, xK_b), safePrompt "firefox" greenXPConfig)
48 > , ((modm .|. shiftMask, xK_c), prompt ("xterm" ++ " -e") greenXPConfig)
49
50 Note that you want to use safePrompt for Firefox input, as Firefox
51 wants URLs, and unsafePrompt for the XTerm example because this allows
52 you to easily start a terminal executing an arbitrary command, like
53 'top'. -}
54
55prompt, unsafePrompt, safePrompt :: String -> FilePath -> XPConfig -> X ()
56prompt = unsafePrompt
57safePrompt q c config = mkXPrompt (Shell q) config (getShellCompl [c]) run
58 where run = safeSpawn c . return
59unsafePrompt q c config = mkXPrompt (Shell q) config (getShellCompl [c]) run
60 where run a = unsafeSpawn $ c ++ " " ++ a
61
62getShellCompl :: [String] -> String -> IO [String]
63getShellCompl cmds s | s == "" || last s == ' ' = return []
64 | otherwise = do
65 f <- fmap lines $ runProcessWithInput "bash" [] ("compgen -A file -- "
66 ++ s ++ "\n")
67 files <- case f of
68 [x] -> do fs <- getFileStatus (encodeString x)
69 if isDirectory fs then return [x ++ "/"]
70 else return [x]
71 _ -> return f
72 return . uniqSort $ files ++ commandCompletionFunction cmds s
73
74commandCompletionFunction :: [String] -> String -> [String]
75commandCompletionFunction cmds str | '/' `elem` str = []
76 | otherwise = filter (isPrefixOf str) cmds
77
78getCommands :: IO [String]
79getCommands = do
80 p <- getEnv "PATH" `E.catch` econst []
81 let ds = filter (/= "") $ split ':' p
82 es <- forM ds $ \d -> do
83 exists <- doesDirectoryExist d
84 if exists
85 then getDirectoryContents d
86 else return []
87 return . uniqSort . filter ((/= '.') . head) . concat $ es
88
89split :: Eq a => a -> [a] -> [[a]]
90split _ [] = []
91split e l =
92 f : split e (rest ls)
93 where
94 (f,ls) = span (/=e) l
95 rest s | s == [] = []
96 | otherwise = tail s
97
98escape :: String -> String
99escape [] = ""
100escape (x:xs)
101 | isSpecialChar x = '\\' : x : escape xs
102 | otherwise = x : escape xs
103
104isSpecialChar :: Char -> Bool
105isSpecialChar = flip elem " &\\@\"'#?$*()[]{};"
diff --git a/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs
new file mode 100644
index 00000000..c85d0f92
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs
@@ -0,0 +1,243 @@
1module XMonad.Prompt.MySsh
2 ( -- * Usage
3 -- $usage
4 sshPrompt,
5 Ssh,
6 Override (..),
7 mkOverride,
8 Conn (..),
9 moshCmd,
10 moshCmd',
11 sshCmd,
12 inTmux,
13 withEnv
14 ) where
15
16import XMonad
17import XMonad.Util.Run
18import XMonad.Prompt
19
20import System.Directory
21import System.Environment
22import qualified Control.Exception as E
23
24import Control.Monad
25import Data.Maybe
26
27import Text.Parsec.String
28import Text.Parsec
29import Data.Char (isSpace)
30
31econst :: Monad m => a -> E.IOException -> m a
32econst = const . return
33
34-- $usage
35-- 1. In your @~\/.xmonad\/xmonad.hs@:
36--
37-- > import XMonad.Prompt
38-- > import XMonad.Prompt.Ssh
39--
40-- 2. In your keybindings add something like:
41--
42-- > , ((modm .|. controlMask, xK_s), sshPrompt defaultXPConfig)
43--
44-- Keep in mind, that if you want to use the completion you have to
45-- disable the "HashKnownHosts" option in your ssh_config
46--
47-- For detailed instruction on editing the key binding see
48-- "XMonad.Doc.Extending#Editing_key_bindings".
49
50data Override = Override
51 { oUser :: Maybe String
52 , oHost :: String
53 , oPort :: Maybe Int
54 , oCommand :: Conn -> String
55 }
56
57mkOverride = Override { oUser = Nothing, oHost = "", oPort = Nothing, oCommand = sshCmd }
58sshCmd c = concat
59 [ "ssh -t "
60 , if isJust $ cUser c then (fromJust $ cUser c) ++ "@" else ""
61 , cHost c
62 , if isJust $ cPort c then " -p " ++ (show $ fromJust $ cPort c) else ""
63 , " -- "
64 , cCommand c
65 ]
66moshCmd c = concat
67 [ "mosh "
68 , if isJust $ cUser c then (fromJust $ cUser c) ++ "@" else ""
69 , cHost c
70 , if isJust $ cPort c then " --ssh=\"ssh -p " ++ (show $ fromJust $ cPort c) ++ "\"" else ""
71 , " -- "
72 , cCommand c
73 ]
74moshCmd' p c = concat
75 [ "mosh "
76 , "--server=" ++ p ++ " "
77 , if isJust $ cUser c then (fromJust $ cUser c) ++ "@" else ""
78 , cHost c
79 , if isJust $ cPort c then " --ssh=\"ssh -p " ++ (show $ fromJust $ cPort c) ++ "\"" else ""
80 , " -- "
81 , cCommand c
82 ]
83inTmux c
84 | null $ cCommand c = c { cCommand = "tmux new-session" }
85 | otherwise = c { cCommand = "tmux new-session \"" ++ (cCommand c) ++ "\"" }
86withEnv :: [(String, String)] -> Conn -> Conn
87withEnv envs c = c { cCommand = "env" ++ (concat $ map (\(n, v) -> ' ' : (n ++ "=" ++ v)) envs) ++ " " ++ (cCommand c) }
88
89data Conn = Conn
90 { cUser :: Maybe String
91 , cHost :: String
92 , cPort :: Maybe Int
93 , cCommand :: String
94 } deriving (Eq, Show, Read)
95
96data Ssh = Ssh
97
98instance XPrompt Ssh where
99 showXPrompt Ssh = "SSH to: "
100 commandToComplete _ c = c
101 nextCompletion _ = getNextCompletion
102
103toConn :: String -> Maybe Conn
104toConn = toConn' . parse connParser "(unknown)"
105toConn' :: Either ParseError Conn -> Maybe Conn
106toConn' (Left _) = Nothing
107toConn' (Right a) = Just a
108
109connParser :: Parser Conn
110connParser = do
111 spaces
112 user' <- optionMaybe $ try $ do
113 str <- many1 $ satisfy (\c -> (not $ isSpace c) && (c /= '@'))
114 char '@'
115 return str
116 host' <- many1 $ satisfy (not . isSpace)
117 port' <- optionMaybe $ try $ do
118 space
119 string "-p"
120 spaces
121 int <- many1 digit
122 (space >> return ()) <|> eof
123 return $ (read int :: Int)
124 spaces
125 command' <- many anyChar
126 eof
127 return $ Conn
128 { cHost = host'
129 , cUser = user'
130 , cPort = port'
131 , cCommand = command'
132 }
133
134sshPrompt :: [Override] -> XPConfig -> X ()
135sshPrompt o c = do
136 sc <- io sshComplList
137 mkXPrompt Ssh c (mkComplFunFromList sc) $ ssh o
138
139ssh :: [Override] -> String -> X ()
140ssh overrides str = do
141 let cmd = applyOverrides overrides str
142 liftIO $ putStr "SSH Command: "
143 liftIO $ putStrLn cmd
144 runInTerm "" cmd
145
146applyOverrides :: [Override] -> String -> String
147applyOverrides [] str = "ssh " ++ str
148applyOverrides (o:os) str = case (applyOverride o str) of
149 Just str -> str
150 Nothing -> applyOverrides os str
151
152applyOverride :: Override -> String -> Maybe String
153applyOverride o str = let
154 conn = toConn str
155 in
156 if isNothing conn then Nothing else
157 case (fromJust conn) `matches` o of
158 True -> Just $ (oCommand o) (fromJust conn)
159 False -> Nothing
160
161matches :: Conn -> Override -> Bool
162a `matches` b = and
163 [ justBool (cUser a) (oUser b) (==)
164 , (cHost a) == (oHost b)
165 , justBool (cPort a) (oPort b) (==)
166 ]
167
168justBool :: Eq a => Maybe a -> Maybe a -> (a -> a -> Bool) -> Bool
169justBool Nothing _ _ = True
170justBool _ Nothing _ = True
171justBool (Just a) (Just b) match = a `match` b
172
173sshComplList :: IO [String]
174sshComplList = uniqSort `fmap` liftM2 (++) sshComplListLocal sshComplListGlobal
175
176sshComplListLocal :: IO [String]
177sshComplListLocal = do
178 h <- getEnv "HOME"
179 s1 <- sshComplListFile $ h ++ "/.ssh/known_hosts"
180 s2 <- sshComplListConf $ h ++ "/.ssh/config"
181 return $ s1 ++ s2
182
183sshComplListGlobal :: IO [String]
184sshComplListGlobal = do
185 env <- getEnv "SSH_KNOWN_HOSTS" `E.catch` econst "/nonexistent"
186 fs <- mapM fileExists [ env
187 , "/usr/local/etc/ssh/ssh_known_hosts"
188 , "/usr/local/etc/ssh_known_hosts"
189 , "/etc/ssh/ssh_known_hosts"
190 , "/etc/ssh_known_hosts"
191 ]
192 case catMaybes fs of
193 [] -> return []
194 (f:_) -> sshComplListFile' f
195
196sshComplListFile :: String -> IO [String]
197sshComplListFile kh = do
198 f <- doesFileExist kh
199 if f then sshComplListFile' kh
200 else return []
201
202sshComplListFile' :: String -> IO [String]
203sshComplListFile' kh = do
204 l <- readFile kh
205 return $ map (getWithPort . takeWhile (/= ',') . concat . take 1 . words)
206 $ filter nonComment
207 $ lines l
208
209sshComplListConf :: String -> IO [String]
210sshComplListConf kh = do
211 f <- doesFileExist kh
212 if f then sshComplListConf' kh
213 else return []
214
215sshComplListConf' :: String -> IO [String]
216sshComplListConf' kh = do
217 l <- readFile kh
218 return $ map (!!1)
219 $ filter isHost
220 $ map words
221 $ lines l
222 where
223 isHost ws = take 1 ws == ["Host"] && length ws > 1
224
225fileExists :: String -> IO (Maybe String)
226fileExists kh = do
227 f <- doesFileExist kh
228 if f then return $ Just kh
229 else return Nothing
230
231nonComment :: String -> Bool
232nonComment [] = False
233nonComment ('#':_) = False
234nonComment ('|':_) = False -- hashed, undecodeable
235nonComment _ = True
236
237getWithPort :: String -> String
238getWithPort ('[':str) = host ++ " -p " ++ port
239 where (host,p) = break (==']') str
240 port = case p of
241 ']':':':x -> x
242 _ -> "22"
243getWithPort str = str
diff --git a/accounts/gkleen@sif/xmonad/package.yaml b/accounts/gkleen@sif/xmonad/package.yaml
new file mode 100644
index 00000000..48de1a53
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/package.yaml
@@ -0,0 +1,30 @@
1name: xmonad-yggdrasil
2
3executables:
4 xmonad:
5 dependencies:
6 - base
7 - xmonad
8 - xmonad-contrib
9 - aeson
10 - bytestring
11 - text
12 - temporary
13 - filepath
14 - directory
15 - network
16 - unix
17 - utf8-string
18 - parsec
19 - process
20 - mtl
21 - X11
22 - transformers
23 - containers
24 - hostname
25 - libnotify
26
27 main: xmonad.hs
28 source-dirs:
29 - .
30 - lib
diff --git a/accounts/gkleen@sif/xmonad/stack.nix b/accounts/gkleen@sif/xmonad/stack.nix
new file mode 100644
index 00000000..17a49e04
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/stack.nix
@@ -0,0 +1,17 @@
1{ ghc, nixpkgs ? import ./nixpkgs.nix {} }:
2
3let
4 haskellPackages = import ./stackage.nix { inherit nixpkgs; };
5 inherit (nixpkgs {}) pkgs;
6in pkgs.haskell.lib.buildStackProject {
7 inherit ghc;
8 inherit (haskellPackages) stack;
9 name = "stackenv";
10 buildInputs = (with pkgs;
11 [ xorg.libX11 xorg.libXrandr xorg.libXinerama xorg.libXScrnSaver xorg.libXext xorg.libXft
12 cairo
13 glib
14 ]) ++ (with haskellPackages;
15 [
16 ]);
17}
diff --git a/accounts/gkleen@sif/xmonad/stack.yaml b/accounts/gkleen@sif/xmonad/stack.yaml
new file mode 100644
index 00000000..b8ed1147
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/stack.yaml
@@ -0,0 +1,10 @@
1nix:
2 enable: true
3 shell-file: stack.nix
4
5resolver: lts-13.21
6
7packages:
8 - .
9
10extra-deps: []
diff --git a/accounts/gkleen@sif/xmonad/xmonad-yggdrasil.nix b/accounts/gkleen@sif/xmonad/xmonad-yggdrasil.nix
new file mode 100644
index 00000000..d3d72310
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/xmonad-yggdrasil.nix
@@ -0,0 +1,21 @@
1{ mkDerivation, aeson, base, bytestring, containers, directory
2, filepath, hostname, hpack, mtl, network, parsec, process, lib
3, temporary, transformers, unix, utf8-string, X11, xmonad
4, xmonad-contrib, libnotify
5}:
6mkDerivation {
7 pname = "xmonad-yggdrasil";
8 version = "0.0.0";
9 src = ./.;
10 isLibrary = false;
11 isExecutable = true;
12 libraryToolDepends = [ hpack ];
13 executableHaskellDepends = [
14 aeson base bytestring containers directory filepath hostname mtl
15 network parsec process temporary transformers unix utf8-string X11
16 xmonad xmonad-contrib libnotify
17 ];
18 preConfigure = "hpack";
19 license = "unknown";
20 hydraPlatforms = lib.platforms.none;
21}
diff --git a/accounts/gkleen@sif/xmonad/xmonad.hs b/accounts/gkleen@sif/xmonad/xmonad.hs
new file mode 100644
index 00000000..8282ed3f
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/xmonad.hs
@@ -0,0 +1,902 @@
1{-# LANGUAGE TupleSections, ViewPatterns, OverloadedStrings, FlexibleInstances, UndecidableInstances, MultiWayIf #-}
2
3import XMonad
4import XMonad.Hooks.DynamicLog
5import XMonad.Hooks.ManageDocks
6import XMonad.Util.Run
7import XMonad.Util.Loggers
8import XMonad.Util.EZConfig(additionalKeys)
9import System.IO
10import System.IO.Error
11import System.Environment
12import Data.Map (Map)
13import qualified Data.Map as Map
14import qualified XMonad.StackSet as W
15import System.Exit
16import Control.Monad.State (get)
17-- import XMonad.Layout.Spiral
18import Data.Ratio
19import Data.List
20import Data.Char
21import Data.Maybe (fromMaybe, listToMaybe, maybeToList, catMaybes, isJust)
22import XMonad.Layout.Tabbed
23import XMonad.Prompt
24import XMonad.Prompt.Input
25import XMonad.Util.Scratchpad
26import XMonad.Util.NamedScratchpad
27import Control.Monad (sequence, liftM, liftM2, join, void)
28import XMonad.Util.WorkspaceCompare
29import XMonad.Layout.NoBorders
30import XMonad.Layout.PerWorkspace
31import XMonad.Layout.SimplestFloat
32import XMonad.Layout.Renamed
33import XMonad.Layout.Reflect
34import XMonad.Layout.OnHost
35import XMonad.Layout.Combo
36import XMonad.Layout.ComboP
37import XMonad.Layout.Column
38import XMonad.Layout.TwoPane
39import XMonad.Layout.IfMax
40import XMonad.Layout.LayoutBuilder
41import XMonad.Layout.WindowNavigation
42import XMonad.Layout.Dwindle
43import XMonad.Layout.TrackFloating
44import System.Process
45import System.Directory (removeFile)
46import System.Posix.Files
47import System.FilePath ((</>))
48import Control.Concurrent
49import System.Posix.Process (getProcessID)
50import System.IO.Error
51import System.IO
52import XMonad.Hooks.ManageHelpers hiding (CW)
53import XMonad.Hooks.UrgencyHook as U
54import XMonad.Hooks.EwmhDesktops
55import XMonad.StackSet (RationalRect (..))
56import Control.Monad (when, filterM, (<=<))
57import Graphics.X11.ExtraTypes.XF86
58import XMonad.Util.Cursor
59import XMonad.Actions.Warp
60import XMonad.Actions.FloatKeys
61import XMonad.Util.SpawnOnce
62import System.Directory
63import System.FilePath
64import XMonad.Actions.CopyWindow
65import XMonad.Hooks.ServerMode
66import XMonad.Actions.Commands
67import XMonad.Actions.CycleWS
68import XMonad.Actions.RotSlaves
69import XMonad.Actions.UpdatePointer
70import XMonad.Prompt.Window
71import Data.IORef
72import Data.Monoid
73import Data.String
74import qualified XMonad.Actions.PhysicalScreens as P
75
76import XMonad.Layout.IM
77
78import XMonad.Prompt.MyShell
79import XMonad.Prompt.MyPass
80import XMonad.Prompt.MySsh
81
82import XMonad.Mpv
83
84import Network.HostName
85
86import Control.Applicative ((<$>))
87
88import Libnotify as Notify hiding (appName)
89import qualified Libnotify as Notify (appName)
90import Libnotify (Notification)
91-- import System.Information.Battery
92
93import Data.Int (Int32)
94
95import System.Posix.Process
96import System.Posix.Signals
97import System.Posix.IO as Posix
98import Control.Exception
99
100import System.IO.Unsafe
101
102import Control.Monad.Trans.Class
103import Control.Monad.Trans.Maybe
104
105import Data.Fixed (Micro)
106
107import qualified Data.Text as Text
108import Data.Ord (comparing)
109import Debug.Trace
110
111instance MonadIO m => IsString (m ()) where
112 fromString = spawn
113
114type KeyMap = Map (ButtonMask, KeySym) (X ())
115
116data Host = Host
117 { hName :: HostName
118 , hManageHook :: ManageHook
119 , hWsp :: Integer -> WorkspaceId
120 , hCoWsp :: String -> Maybe WorkspaceId
121 , hKeysMod :: XConfig Layout -> (KeyMap -> KeyMap)
122 , hScreens :: [P.PhysicalScreen]
123 , hKbLayouts :: [(String, Maybe String)]
124 , hCmds :: X [(String, X ())]
125 , hKeyUpKeys :: XConfig Layout -> KeyMap
126 }
127
128defaultHost = Host { hName = "unkown"
129 , hManageHook = composeOne [manageScratchTerm]
130 , hWsp = show
131 , hCoWsp = const Nothing
132 , hKeysMod = const id
133 , hScreens = [0,1..]
134 , hKbLayouts = [ ("us", Just "dvp")
135 , ("us", Nothing)
136 , ("de", Nothing)
137 ]
138 , hCmds = return []
139 , hKeyUpKeys = const Map.empty
140 }
141
142browser :: String
143browser = "env MOZ_USE_XINPUT2=1 firefox"
144
145hostFromName :: HostName -> Host
146hostFromName h@("vali") = defaultHost { hName = h
147 , hManageHook = composeOne $ catMaybes [ Just manageScratchTerm
148 , assign "web" $ className =? ".dwb-wrapped"
149 , assign "web" $ className =? "Chromium"
150 , assign "work" $ className =? "Emacs"
151 , assign "media" $ className =? "mpv"
152 ]
153 , hWsp = hWsp
154 , hCoWsp = hCoWsp
155 , hKeysMod = \conf -> Map.union $ (Map.fromList $ join $ map (spawnBindings conf) [ (xK_d, ["chromium", "chromium $(xclip -o)"])
156 , (xK_e, ["emacsclient -c"])
157 ])
158 `Map.union`
159 ( Map.fromList [ ((XMonad.modMask conf .|. controlMask, xK_Return), scratchpadSpawnActionCustom $ (XMonad.terminal conf) ++ " -name scratchpad -title scratchpad -e tmux new-session -D -s scratch")
160 ] )
161 , hScreens = hScreens defaultHost
162 }
163 where
164 workspaceNames = Map.fromList [ (2, "web")
165 , (3, "work")
166 , (10, "media")
167 ]
168 hWsp = wspFromMap workspaceNames
169 hCoWsp = coWspFromMap workspaceNames
170 assign wsp test = (\wsp -> test -?> doShift wsp) <$> hCoWsp wsp
171hostFromName h
172 | h `elem` ["hel", "sif"] = defaultHost { hName = h
173 , hManageHook = namedScratchpadManageHook scratchpads <+> composeOne (catMaybes
174 [ assign "mpv" $ className =? "mpv"
175 , assign "mpv" $ (className =? "URxvt" <&&> title =? "irssi")
176 , assign "mpv" $ (className =? "URxvt" <&&> resource =? "presentation")
177 , assign "mpv" $ stringProperty "WM_WINDOW_ROLE" =? "presentation"
178 , assign "read" $ stringProperty "WM_WINDOW_ROLE" =? "presenter"
179 , assign "mpv" $ className =? "factorio"
180 , assign "web" $ className =? "chromium-browser"
181 , assign "web" $ className =? "Google-chrome"
182 , assign "work" $ (appName =? "Devtools" <&&> className =? "Firefox")
183 , assign "work" $ className =? "Postman"
184 , assign "web" $ className =? "Firefox"
185 , assign "comm" $ (className =? "URxvt" <&&> resource =? "comm")
186 , assign "comm" $ (className =? "Emacs" <&&> title =? "Mail")
187 , assign "comm" $ className =? "Zulip"
188 , assign "comm" $ className =? "Discord"
189 , assign "media" $ (className =? "URxvt" <&&> resource =? "media")
190 , assign "media" $ (className =? "URxvt" <&&> title =? "streamlink")
191 , assign "media" $ (className =? "URxvt" <&&> title =? "mpv")
192 , assign "monitor" $ (className =? "URxvt" <&&> fmap ("monitor" `isInfixOf`) title)
193 , assign "monitor" $ className =? "Grafana"
194 , Just $ (className =? "URxvt" <&&> resource =? "htop") -?> centerFloat
195 , Just $ (className =? "Scp-dbus-service.py") -?> centerFloat
196 , Just $ (className =? "URxvt" <&&> resource =? "log") -?> centerFloat
197 , assign "work" $ className =? "URxvt"
198 , assign' ["work", "uni"] $ (className =? "Emacs" <&&> appName /=? "Edit_with_Emacs_FRAME")
199 , assign' ["work", "uni"] $ className =? "jetbrains-idea-ce"
200 , assign "read" $ className =? "llpp"
201 , assign "read" $ className =? "Evince"
202 , assign "read" $ className =? "Zathura"
203 , assign "read" $ className =? "MuPDF"
204 , assign "read" $ className =? "Xournal"
205 , assign "read" $ appName =? "com-trollworks-gcs-app-GCS"
206 , assign "read" $ appName =? "Tux.py"
207 , assign "read" $ className =? "Gnucash"
208 , assign "comm" $ className =? "Skype"
209 , assign "comm" $ className =? "Daily"
210 , assign "comm" $ className =? "Pidgin"
211 , assign "comm" $ className =? "Slack"
212 , Just $ (resource =? "xvkbd") -?> doRectFloat $ RationalRect (1 % 8) (3 % 8) (6 % 8) (4 % 8)
213 , Just $ (stringProperty "_NET_WM_WINDOW_TYPE" =? "_NET_WM_WINDOW_TYPE_DIALOG") -?> doFloat
214 , Just $ (className =? "Dunst") -?> doFloat
215 , Just $ (className =? "Xmessage") -?> doCenterFloat
216 , Just $ (className =? "Nm-openconnect-auth-dialog") -?> centerFloat
217 , Just $ (className =? "Pinentry") -?> doCenterFloat
218 , Just $ (className =? "pinentry") -?> doCenterFloat
219 , Just $ (appName =? "Edit_with_Emacs_FRAME") -?> centerFloat
220 , Just $ (stringProperty "WM_WINDOW_ROLE" =? "GtkFileChooseDialog") -?> centerFloatSmall
221 , Just $ (className =? "Nvidia-settings") -?> doCenterFloat
222 , Just $ fmap ("Minetest" `isInfixOf`) title -?> doIgnore
223 , Just $ fmap ("Automachef" `isInfixOf`) title -?> doIgnore
224 , assign "call" $ className =? "zoom"
225 ])
226 , hWsp = hWsp
227 , hCoWsp = hCoWsp
228 , hKeysMod = \conf -> Map.union $ (Map.fromList $ join $ map (spawnBindings conf) [ (xK_e, ["emacsclient -c"])
229 , (xK_d, [fromString browser, fromString $ browser ++ " $(xclip -o)", fromString $ "notmuch-links"])
230 , (xK_f, ["urxvtc -name comm -title Feeds -e mosh odin -- tmux new-session -ADs comm"])
231 , (xK_c, [ inputPrompt xPConfig "dc" ?+ dc ])
232 , (xK_g, ["pidgin"])
233 , (xK_s, ["skype"])
234 -- , (xK_p, [mkPassPrompt "Type password" pwType xPConfig, mkPassPrompt "Show password" pwShow xPConfig, mkPassPrompt "Copy password" pwClip xPConfig])
235 , (xK_w, ["sudo rewacom"])
236 , (xK_y, [ "tmux new-window -dt media /var/media/link.hs $(xclip -o)"
237 , "tmux new-window -dt media /var/media/download.hs $(xclip -o)"
238 , "urxvtc -name media -e tmuxp load /var/media"
239 ])
240 , (xK_l, [ "tmux new-window -dt media mpv $(xclip -o)"
241 , "tmux new-window -dt media streamlink --retry-open 10 $(xclip -o)"
242 ])
243 , (xK_m, [ "emacsclient -c -F \"'(title . \\\"Mail\\\")\" -e '(notmuch)'"
244 , "emacsclient -c -F \"'(title . \\\"Mail\\\")\" -e '(notmuch-mua-new-mail)'"
245 , "emacsclient -c -F \"'(title . \\\"Mail\\\")\" -e \"(browse-url-mail \"$(xclip -o)\")\""
246 ])
247 , (xK_Return, ["keynav start,windowzoom", "keynav start"])
248 , (xK_t, [inputPrompt xPConfig "fuzzytime timer" ?+ fuzzytime, fuzzytime "unset", work_fuzzytime])
249 , (xK_a, [inputPrompt xPConfig "adjmix" ?+ adjmix])
250 , (xK_s, [ inputPromptWithCompl xPConfig "start synergy" synergyCompl ?+ synergyStart
251 , inputPromptWithCompl xPConfig "stop synergy" synergyCompl ?+ synergyStop
252 ])
253 , (xK_h, [ "urxvtc -name htop -e htop"
254 , "urxvtc -name log -e journalctl -xef"
255 ])
256 , (xK_x, [ "autorandr -c"
257 , "autorandr -fl def"
258 ])
259 , (xK_z, [ "zulip -- --force-device-scale-factor=2"
260 ])
261 ])
262 `Map.union`
263 ( Map.fromList [ ((XMonad.modMask conf .|. controlMask, xK_Return), namedScratchpadAction scratchpads "term")
264 , ((XMonad.modMask conf .|. controlMask, xK_a), namedScratchpadAction scratchpads "pavucontrol")
265 , ((XMonad.modMask conf .|. controlMask, xK_w), namedScratchpadAction scratchpads "alarms")
266 , ((XMonad.modMask conf .|. controlMask, xK_b), namedScratchpadAction scratchpads "blueman")
267 , ((XMonad.modMask conf .|. controlMask, xK_p), namedScratchpadAction scratchpads "keepassxc")
268 , ((XMonad.modMask conf .|. controlMask, xK_t), namedScratchpadAction scratchpads "toggl")
269 , ((XMonad.modMask conf .|. controlMask, xK_e), namedScratchpadAction scratchpads "emacs")
270 , ((XMonad.modMask conf .|. controlMask, xK_m), namedScratchpadAction scratchpads "calendar")
271 , ((XMonad.modMask conf .|. controlMask, xK_f), namedScratchpadAction scratchpads "music")
272 , ((XMonad.modMask conf .|. mod1Mask, xK_Up), rotate U)
273 , ((XMonad.modMask conf .|. mod1Mask, xK_Down), rotate D)
274 , ((XMonad.modMask conf .|. mod1Mask, xK_Left), rotate L)
275 , ((XMonad.modMask conf .|. mod1Mask, xK_Right), rotate R)
276 -- , ((XMonad.modMask conf .|. shiftMask, xK_a), startMute "hel")
277 ] )
278 , hKeyUpKeys = \conf -> Map.fromList [ -- ((XMonad.modMask conf .|. shiftMask, xK_a), stopMute "hel")
279 ]
280 , hScreens = hScreens defaultHost
281 , hCmds = return [ ("prev-workspace", prevWS)
282 , ("next-workspace", nextWS)
283 , ("prev-window", rotAllDown)
284 , ("next-window", rotAllUp)
285 , ("banish", banishScreen LowerRight)
286 , ("update-gpg-tty", safeSpawn "gpg-connect-agent" ["UPDATESTARTUPTTY", "/bye"])
287 , ("rescreen", rescreen)
288 , ("repanel", do
289 spawn "nm-applet"
290 spawn "blueman-applet"
291 spawn "pasystray"
292 spawn "kdeconnect-indicator"
293 spawn "dunst -print"
294 spawn "udiskie"
295 spawn "autocutsel -s PRIMARY"
296 spawn "autocutsel -s CLIPBOARD"
297 )
298 , ("pause", mediaMpv $ MpvSetProperty "pause" True)
299 , ("unpause", mediaMpv $ MpvSetProperty "pause" False)
300 , ("exit", io $ exitWith ExitSuccess)
301 ]
302 }
303 where
304 withGdkScale act = void . xfork $ setEnv "GDK_SCALE" "2" >> act
305 workspaceNames = Map.fromList [ (1, "comm")
306 , (2, "web")
307 , (3, "work")
308 , (4, "read")
309 , (5, "monitor")
310 , (6, "uni")
311 , (8, "call")
312 , (9, "media")
313 , (10, "mpv")
314 ]
315 scratchpads = [ NS "term" "urxvtc -name scratchpad -title scratchpad -e tmux new-session -AD -s scratch" (resource =? "scratchpad") centerFloat
316 , NS "pavucontrol" "pavucontrol" (resource =? "pavucontrol") centerFloat
317 , NS "alarms" "alarm-clock-applet" (className =? "Alarm-clock-applet" <&&> title =? "Alarms") centerFloat
318 , NS "blueman" "blueman-manager" (className =? ".blueman-manager-wrapped") centerFloat
319 , NS "keepassxc" "keepassxc" (className =? "KeePassXC") centerFloat
320 , NS "toggl" "toggldesktop" (className =? "Toggl Desktop") centerFloat
321 , NS "calendar" "minetime -- --force-device-scale-factor=1.6" (className =? "MineTime") centerFloat
322 , NS "emacs" "emacsclient -c -F \"'(title . \\\"Scratchpad\\\")\"" (className =? "Emacs" <&&> title =? "Scratchpad") centerFloat
323 , NS "music" "google-play-music-desktop-player --force-device-scale-factor=1.6" (className =? "Google Play Music Desktop Player") centerFloat
324 ]
325 centerFloat = customFloating $ RationalRect (1 % 16) (1 % 16) (7 % 8) (7 % 8)
326 centerFloatSmall = customFloating $ RationalRect (1 % 4) (1 % 4) (1 % 2) (1 % 2)
327 hWsp = wspFromMap workspaceNames
328 hCoWsp = coWspFromMap workspaceNames
329 assign wsp test = (\wsp -> test -?> doShift wsp) <$> hCoWsp wsp
330 assign' :: [String] -> Query Bool -> Maybe MaybeManageHook
331 assign' wsps test = do
332 wsIds <- mapM hCoWsp wsps
333 return $ test -?> go wsIds
334 where
335 go :: [WorkspaceId] -> ManageHook
336 go wsps = do
337 visWsps <- liftX $ (\wset -> W.tag . W.workspace <$> W.current wset : W.visible wset) <$> gets windowset
338 case (filter (`elem` visWsps) wsps, wsps) of
339 (wsp : _, _) -> doShift wsp
340 (_, wsp : _) -> doShift wsp
341 ([], []) -> return mempty
342 rotate rot = do
343 safeSpawn "xrandr" ["--output", "eDP-1", "--rotate", xrandrDir]
344 mapM_ rotTouch touchscreens
345 where
346 xrandrDir = case rot of
347 U -> "normal"
348 L -> "left"
349 R -> "right"
350 D -> "inverted"
351 matrix = case rot of
352 U -> [ [ 1, 0, 0]
353 , [ 0, 1, 0]
354 , [ 0, 0, 1]
355 ]
356 L -> [ [ 0, -1, 1]
357 , [ 1, 0, 0]
358 , [ 0, 0, 1]
359 ]
360 R -> [ [ 0, 1, 0]
361 , [-1, 0, 1]
362 , [ 0, 0, 1]
363 ]
364 D -> [ [-1, 0, 1]
365 , [ 0, -1, 1]
366 , [ 0, 0, 1]
367 ]
368 touchscreens = [ "Wacom Co.,Ltd. Pen and multitouch sensor Finger touch"
369 , "Wacom Co.,Ltd. Pen and multitouch sensor Pen stylus"
370 , "Wacom Co.,Ltd. Pen and multitouch sensor Pen eraser"
371 ]
372 rotTouch screen = do
373 safeSpawn "xinput" $ ["set-prop", screen, "Coordinate Transformation Matrix"] ++ map (\n -> show n ++ ",") (concat matrix)
374 safeSpawn "xinput" ["map-to-output", screen, "eDP-1"]
375 withPw f label = io . void . forkProcess $ do
376 uninstallSignalHandlers
377 void $ createSession
378 (dropWhileEnd isSpace -> pw) <- readCreateProcess (proc "pass" ["show", label]) ""
379 void $ f pw
380 pwType :: String -> X ()
381 pwType = withPw $ readCreateProcess (proc "xdotool" ["type", "--clearmodifiers", "--file", "-"])
382 pwClip label = safeSpawn "pass" ["show", "--clip", label]
383 pwShow :: String -> X ()
384 pwShow = withPw $ \pw -> do
385 xmessage <- fromMaybe "xmessage" <$> liftIO (lookupEnv "XMONAD_XMESSAGE")
386 readCreateProcess (proc xmessage ["-file", "-"]) pw
387 fuzzytime str = safeSpawn "fuzzytime" $ "timer" : words str
388 work_fuzzytime = io . void . forkProcess $ do
389 readCreateProcess (proc "worktime" []) "" >>= safeSpawn "fuzzytime" . ("timer" : ) . pure
390 adjmix str = safeSpawn "adjmix" $ words str
391 dc expr = void . xfork $ do
392 result <- readProcess "dc" [] $ expr ++ "f"
393 let
394 (first : rest) = filter (not . null) $ lines result
395 notification = Notify.summary first <> Notify.body (unlines rest) <> Notify.timeout Infinite <> Notify.urgency Normal <> Notify.appName "dc"
396 void $ Notify.display notification
397 synergyCompl = mkComplFunFromList' ["mathw86"]
398 synergyStart host = safeSpawn "systemctl" ["--user", "start", "synergy-rtunnel@" ++ host ++ ".service"]
399 synergyStop host = safeSpawn "systemctl" ["--user", "stop", "synergy-rtunnel@" ++ host ++ ".service"]
400
401hostFromName _ = defaultHost
402
403-- muteRef :: IORef (Maybe (String, Notification))
404-- {-# NOINLINE muteRef #-}
405-- muteRef = unsafePerformIO $ newIORef Nothing
406
407-- startMute, stopMute :: String -> X ()
408-- startMute sink = liftIO $ do
409-- muted <- isJust <$> readIORef muteRef
410-- when (not muted) $ do
411-- let
412-- notification = Notify.summary "Muted" <> Notify.timeout Infinite <> Notify.urgency Normal
413-- level = "0.0dB"
414-- -- level <- runProcessWithInput "ssh" ["bragi", "cat", "/dev/shm/mix/" ++ sink ++ "/level"] ""
415-- -- callProcess "ssh" ["bragi", "adjmix", "-t", sink, "-o", "0"]
416-- hPutStrLn stderr "Mute"
417-- writeIORef muteRef . Just . (level, ) =<< Notify.display notification
418-- stopMute sink = liftIO $ do
419-- let
420-- unmute (Just (level, notification)) = do
421-- hPutStrLn stderr "Unmute"
422-- -- callProcess "ssh" ["bragi", "adjmix", "-t", sink, "-o", level]
423-- Notify.close notification
424-- unmute Nothing = return ()
425-- muted <- isJust <$> readIORef muteRef
426-- when muted . join . atomicModifyIORef muteRef $ (Nothing, ) . unmute
427
428wspFromMap workspaceNames = \i -> case Map.lookup i workspaceNames of
429 Just str -> show i ++ " " ++ str
430 Nothing -> show i
431
432coWspFromMap workspaceNames = \str -> case filter ((== str) . snd) $ Map.toList workspaceNames of
433 [] -> Nothing
434 [(i, _)] -> Just $ wspFromMap workspaceNames i
435 _ -> Nothing
436
437spawnModifiers = [0, controlMask, shiftMask .|. controlMask]
438spawnBindings :: XConfig layout -> (KeySym, [X ()]) -> [((KeyMask, KeySym), X ())]
439spawnBindings conf (k, cmds) = zipWith (\m cmd -> ((modm .|. mod1Mask .|. m, k), cmd)) spawnModifiers cmds
440 where
441 modm = XMonad.modMask conf
442
443manageScratchTerm = (resource =? "scratchpad" <||> resource =? "keysetup") -?> doRectFloat $ RationalRect (1 % 16) (1 % 16) (7 % 8) (7 % 8)
444
445tabbedLayout t = renamed [Replace "Tabbed"] $ reflectHoriz $ t CustomShrink $ tabbedTheme
446tabbedLayoutHoriz t = renamed [Replace "Tabbed Horiz"] $ reflectVert $ t CustomShrink $ tabbedTheme
447tabbedTheme = def
448 { activeColor = "black"
449 , inactiveColor = "black"
450 , urgentColor = "black"
451 , activeBorderColor = "grey"
452 , inactiveBorderColor = "#202020"
453 , urgentBorderColor = "#bb0000"
454 , activeTextColor = "grey"
455 , inactiveTextColor = "grey"
456 , urgentTextColor = "grey"
457 , decoHeight = 32
458 , fontName = "xft:Fira Mono for Powerline:style=Medium:pixelsize=22.5"
459 }
460
461main :: IO ()
462main = do
463 arguments <- either (const []) id <$> tryIOError getArgs
464 case arguments of
465 ["--command", s] -> do
466 d <- openDisplay ""
467 rw <- rootWindow d $ defaultScreen d
468 a <- internAtom d "XMONAD_COMMAND" False
469 m <- internAtom d s False
470 allocaXEvent $ \e -> do
471 setEventType e clientMessage
472 setClientMessageEvent e rw a 32 m currentTime
473 sendEvent d rw False structureNotifyMask e
474 sync d False
475 _ -> do
476 -- batteryMon <- xfork $ monitorBattery Nothing Nothing
477 hostname <- getHostName
478 let
479 host = hostFromName hostname
480 setEnv "HOST" hostname
481 let myConfig = withHostUrgency . ewmh $ docks def
482 { manageHook = hManageHook host
483 , terminal = "urxvtc"
484 , layoutHook = smartBorders . avoidStruts $ windowNavigation layout'
485 , logHook = do
486 dynamicLogString xmobarPP' >>= writeProps
487 updatePointer (99 % 100, 98 % 100) (0, 0)
488 , modMask = mod4Mask
489 , keys = \conf -> hKeysMod host conf $ myKeys' conf host
490 , workspaces = take (length numKeys) $ map wsp [1..]
491 , startupHook = setDefaultCursor xC_left_ptr
492 , normalBorderColor = "#202020"
493 , focusedBorderColor = "grey"
494 , handleEventHook = fullscreenEventHook <+> (serverModeEventHookCmd' $ hCmds host) <+> keyUpEventHook
495 }
496 writeProps str = do
497 let encodeCChar = map $ fromIntegral . fromEnum
498 atoms = [ "_XMONAD_WORKSPACES"
499 , "_XMONAD_LAYOUT"
500 , "_XMONAD_TITLE"
501 ]
502 (flip mapM_) (zip atoms (lines str)) $ \(atom', content) -> do
503 ustring <- getAtom "UTF8_STRING"
504 atom <- getAtom atom'
505 withDisplay $ \dpy -> io $ do
506 root <- rootWindow dpy $ defaultScreen dpy
507 changeProperty8 dpy root atom ustring propModeReplace $ encodeCChar content
508 sync dpy True
509 wsp = hWsp host
510 -- We can´t define per-host layout modifiers because we lack dependent types
511 layout' = onHost "skadhi" ( onWorkspace (wsp 1) (Full ||| withIM (1%5) (Title "Buddy List") tabbedLayout') $
512 onWorkspace (wsp 10) Full $
513 onWorkspace (wsp 2) (Full ||| tabbedLayout') $
514 onWorkspace (wsp 5) tabbedLayout' $
515 onWorkspace (wsp 8) (withIM (1%5) (Title "Friends") tabbedLayout') $
516 defaultLayouts
517 ) $
518 onHost "vali" ( onWorkspace (wsp 2) (Full ||| tabbedLayout' ||| combineTwo (TwoPane 0.01 0.57) Full tabbedLayout') $
519 onWorkspace (wsp 3) workLayouts $
520 defaultLayouts
521 ) $
522 onHost "hel" ( onWorkspace (wsp 1) (withIM (1 % 8) (Title "Buddy List") $ trackFloating tabbedLayout') $
523 onWorkspace (wsp 2) (tabbedLayout''' ||| Dwindle R CW 1 (5 % 100)) $
524 onWorkspace (wsp 3) workLayouts $
525 onWorkspace (wsp 6) workLayouts $
526 onWorkspace (wsp 4) (tabbedLayout' ||| tabbedLayoutHoriz' ||| Dwindle R CW 1 (5 % 100)) $
527 onWorkspace (wsp 5) (tabbedLayout''' ||| Dwindle R CW 1 (5 % 100)) $
528 onWorkspace (wsp 10) (tabbedLayout''' ||| combineTwoP (TwoPane (1 % 100) (3 % 4)) tabbedLayout''' tabbedLayout''' (ClassName "mpv") ||| Dwindle R CW 1 (5 % 100)) $
529 defaultLayouts
530 ) $
531 onHost "sif" ( onWorkspace (wsp 1) (withIM (1 % 8) (Title "Buddy List") $ trackFloating tabbedLayout') $
532 onWorkspace (wsp 2) (tabbedLayout''' ||| Dwindle R CW 1 (5 % 100)) $
533 onWorkspace (wsp 3) workLayouts $
534 onWorkspace (wsp 6) workLayouts $
535 onWorkspace (wsp 4) (tabbedLayout' ||| tabbedLayoutHoriz' ||| Dwindle R CW 1 (5 % 100)) $
536 onWorkspace (wsp 5) (tabbedLayout''' ||| Dwindle R CW 1 (5 % 100)) $
537 onWorkspace (wsp 8) tabbedLayout''' $
538 onWorkspace (wsp 10) (tabbedLayout''' ||| combineTwoP (TwoPane (1 % 100) (3 % 4)) tabbedLayout''' tabbedLayout''' (ClassName "mpv") ||| Dwindle R CW 1 (5 % 100)) $
539 defaultLayouts
540 ) $
541 defaultLayouts
542 -- tabbedLayout''' = renamed [Replace "Tabbed'"] $ IfMax 1 (noBorders Full) (tabbedLayout tabbedBottomAlways)
543 tabbedLayout''' = tabbedLayout tabbedBottom
544 tabbedLayout' = tabbedLayout tabbedBottomAlways
545 tabbedLayoutHoriz' = tabbedLayoutHoriz tabbedLeftAlways
546 defaultLayouts = {- spiralWithDir East CW (1 % 2) -} Dwindle R CW 1 (5 % 100) ||| tabbedLayout' ||| Full
547 -- workLayouts = {- spiralWithDir East CW (1 % 2) -} Dwindle R CW (2 % 1) (5 % 100) ||| tabbedLayout' ||| Full
548 workLayouts = tabbedLayout' ||| (renamed [Replace "Combined"] $ combineTwoP (TwoPane (1 % 100) (1891 % 2560)) tabbedLayout''' (Column 1.6) (ClassName "Postman" `Or` ClassName "Emacs" `Or` ClassName "jetbrains-idea-ce" `Or` (Resource "Devtools" `And` ClassName "Firefox"))) ||| Full ||| Dwindle R CW 1 (5 % 100)
549 sqrtTwo = approxRational (sqrt 2) (1 / 2560)
550 xmobarPP' = xmobarPP { ppTitle = shorten 80
551 , ppSort = (liftM2 (.)) getSortByIndex $ return scratchpadFilterOutWorkspace
552 , ppUrgent = wrap "(" ")" . xmobarColor "#800000" ""
553 , ppHiddenNoWindows = xmobarColor "#202020" "" . wrap "(" ")"
554 , ppVisible = wrap "(" ")" . xmobarColor "#808000" ""
555 , ppCurrent = wrap "(" ")" . xmobarColor "#008000" ""
556 , ppHidden = wrap "(" ")"
557 , ppWsSep = " "
558 , ppSep = "\n"
559 }
560 withHostUrgency = case hostname of
561 "hel" -> withUrgencyHookC urgencyHook' $ urgencyConfig { suppressWhen = U.Never, remindWhen = Dont }
562 "sif" -> withUrgencyHookC urgencyHook' $ urgencyConfig { suppressWhen = U.Never, remindWhen = Dont }
563 _ -> id
564 urgencyHook' window = do
565 runQuery ((resource =? "comm" <||> resource =? "Pidgin" <||> className =? "Gajim" <||> className =? "Skype") --> safeSpawn "thinklight" ["Blink", "100"]) window
566 urgencyHook (BorderUrgencyHook { urgencyBorderColor = "#bb0000" }) window
567 shutdown :: SomeException -> IO a
568 shutdown e = do
569 let pids = [ -- batteryMon
570 ]
571 mapM_ (signalProcess sigTERM) pids
572 mapM_ (getProcessStatus False False) pids
573 throw e
574 keyUpEventHook :: Event -> X All
575 keyUpEventHook event = handle event >> return (All True)
576 where
577 handle (KeyEvent { ev_event_type = t, ev_state = m, ev_keycode = code })
578 | t == keyRelease = withDisplay $ \dpy -> do
579 s <- io $ keycodeToKeysym dpy code 0
580 mClean <- cleanMask m
581 ks <- asks $ hKeyUpKeys host . config
582 userCodeDef () $ whenJust (Map.lookup (mClean, s) ks) id
583 | otherwise = return ()
584 handle _ = return ()
585 handle shutdown $ launch myConfig
586
587secs :: Int -> Int
588secs = (* 1000000)
589
590-- monitorBattery :: Maybe BatteryContext -> Maybe Notification -> IO ()
591-- monitorBattery Nothing n = do
592-- ctx <- batteryContextNew
593-- case ctx of
594-- Nothing -> threadDelay (secs 10) >> monitorBattery Nothing n
595-- Just _ -> monitorBattery ctx n
596-- monitorBattery ctx@(Just ctx') n = do
597-- batInfo <- getBatteryInfo ctx'
598-- case batInfo of
599-- Nothing -> threadDelay (secs 1) >> monitorBattery ctx n
600-- Just batInfo -> do
601-- let n'
602-- | batteryState batInfo == BatteryStateDischarging
603-- , timeLeft <= 1200
604-- , timeLeft > 0 = Just $ summary "Discharging" <> hint "value" percentage <> urgency u <> body (duz timeLeft ++ "left")
605-- | otherwise = Nothing
606-- u
607-- | timeLeft <= 600 = Critical
608-- | timeLeft <= 1800 = Normal
609-- | otherwise = Low
610-- timeLeft = batteryTimeToEmpty batInfo
611-- percentage :: Int32
612-- percentage = round $ batteryPercentage batInfo
613-- ts = [("s", 60), ("m", 60), ("h", 24), ("d", 365), ("y", 1)]
614-- duz ms = ss
615-- where (ss, _) = foldl (\(ss, x) (s, y) -> ((if rem x y > 0 then show (rem x y) ++ s ++ " " else "") ++ ss , quot x y)) ("", ms) ts
616-- case n' of
617-- Just n' -> Notify.display (maybe mempty reuse n <> Notify.appName "monitorBattery" <> n') >>= (\n -> threadDelay (secs 2) >> monitorBattery ctx (Just n))
618-- Nothing -> threadDelay (secs 30) >> monitorBattery ctx n
619
620disableTouchpad, disableTrackpoint, enableTrackpoint, enableTouchpad :: X ()
621enableTouchpad = safeSpawn "xinput" ["enable", "SynPS/2 Synaptics TouchPad"]
622disableTouchpad = safeSpawn "xinput" ["disable", "SynPS/2 Synaptics TouchPad"]
623enableTrackpoint = safeSpawn "xinput" ["enable", "TPPS/2 IBM TrackPoint"]
624disableTrackpoint = safeSpawn "xinput" ["disable", "TPPS/2 IBM TrackPoint"]
625
626isDisabled :: String -> X Bool
627isDisabled str = do
628 out <- runProcessWithInput "xinput" ["list", str] ""
629 return $ "disabled" `isInfixOf` out
630
631
632spawnKeychain :: X ()
633spawnKeychain = do
634 home <- liftIO getHomeDirectory
635 let keys = (map ((home </>) . (".ssh/" ++)) ["id", "id-rsa"]) ++ ["6B13AA67"]
636 liftIO (maybe (return ()) (setEnv "SSH_ASKPASS") =<< findAskpass)
637 safeSpawn "keychain" . (["--agents", "gpg,ssh"] ++)=<< liftIO (filterM doesFileExist keys)
638 where
639 findAskpass = filter `liftM` readFile "/etc/zshrc"
640 filter = listToMaybe . catMaybes . map (stripPrefix "export SSH_ASKPASS=") . lines
641
642assimilateKeychain :: X ()
643assimilateKeychain = liftIO $ assimilateKeychain' >> return ()
644assimilateKeychain' = tryIOError $ do
645 -- pid <- getProcessID
646 -- tmpDir <- lookupEnv "TMPDIR"
647 -- let tmpDir' = fromMaybe "/tmp" tmpDir
648 -- tmpFile = tmpDir' </> "xmonad-keychain" ++ (show pid) ++ ".env"
649 env <- runProcessWithInput "sh" ["-c", "eval $(keychain --eval --noask --agents gpg,ssh); env"] "" -- > " ++ tmpFile] ""
650 -- env <- readFile tmpFile
651 let envVars = Map.fromList $ map (\(k, v) -> (k, tail' v)) $ map (span (/= '=')) $ envLines
652 envVars' = Map.filterWithKey (\k _ -> k `elem` transfer) envVars
653 transfer = ["SSH_AUTH_SOCK", "SSH_AGENT_PID", "GPG_AGENT_INFO"]
654 envLines = filter (elem '=') $ lines env :: [String]
655 sequence $ map (\(k, c) -> setEnv k c) $ Map.toList envVars'
656 -- removeFile tmpFile
657 where
658 tail' [] = []
659 tail' (x:xs) = xs
660
661
662numKeys = [xK_parenleft, xK_parenright, xK_braceright, xK_plus, xK_braceleft, xK_bracketright, xK_bracketleft, xK_exclam, xK_equal, xK_asterisk]
663
664instance Shrinker CustomShrink where
665 shrinkIt _ "" = [""]
666 shrinkIt s cs
667 | length cs >= 4 = cs : shrinkIt s ((reverse . drop 4 . reverse $ cs) ++ "...")
668 | otherwise = cs : shrinkIt s (init cs)
669
670xPConfig :: XPConfig
671xPConfig = def
672 { font = "xft:Fira Mono for Powerline:style=Medium:pixelsize=22.5"
673 , height = 32
674 , bgColor = "black"
675 , fgColor = "grey"
676 , fgHLight = "green"
677 , bgHLight = "black"
678 , borderColor = "grey"
679 , searchPredicate = (\needle haystack -> all (`isInfixOf` map toLower haystack) . map (map toLower) $ words needle)
680 , position = Top
681 }
682
683sshOverrides = map (\h -> mkOverride { oHost = h, oCommand = moshCmd . inTmux } )
684 [
685 "odin", "odin.asgard.yggdrasil"
686 , "ymir", "ymir.yggdrasil.li", "ymir.niflheim.yggdrasil"
687 , "surtr", "yggdrasil.li", "surtr.yggdrasil.li", "praseodym.org", "surtr.praseodym.org", "surtr.141.li", "141.li"
688 , "vindler", "vindler.alfheim.yggdrasil"
689 , "ullr"
690 , "heimdallr", "heimdallr.asgard.yggdrasil"
691 , "testworx"
692 ]
693 ++
694 map (\h -> mkOverride { oHost = h, oCommand = moshCmd' "/run/current-system/sw/bin/mosh-server" . withEnv [("TERM", "xterm")] . inTmux} )
695 [ "bragi", "bragi.asgard.yggdrasil"
696 ]
697 ++
698 map (\h -> mkOverride { oHost = h, oCommand = sshCmd . withEnv [("TERM", "xterm")] . inTmux } )
699 [ "remote.cip.ifi.lmu.de"
700 , "uniworx3", "uniworx4", "uniworxdb"
701 ]
702
703backlight :: (Rational -> Rational) -> X ()
704backlight f = void . xfork . liftIO $ do
705 [ _device
706 , _class
707 , read . Text.unpack -> currentBright
708 , _currentPercentage
709 , read . Text.unpack -> maximumBright
710 ] <- Text.splitOn "," . Text.pack <$> readProcess "brightnessctl" ["-m"] ""
711 let current = currentBright % maximumBright
712 new' = f current * fromIntegral maximumBright
713 new :: Integer
714 new | floor new' < 0 = 0
715 | ceiling new' > maximumBright = maximumBright
716 | new' >= maximumBright % 2 = ceiling new'
717 | otherwise = floor new'
718 callProcess "brightnessctl" ["-m", "s", show new]
719
720cycleThrough :: [Rational] -> (Rational -> Rational)
721cycleThrough opts current = fromMaybe currentOpt $ listToMaybe next'
722 where currentOpt = minimumBy (comparing $ abs . subtract current) opts
723 (_, _ : next') = break (== currentOpt) opts
724
725cycleKbLayout :: [(String, Maybe String)] -> X ()
726cycleKbLayout [] = return ()
727cycleKbLayout layouts = liftIO $ do
728 next <- (getNext . extract) `liftM` runProcessWithInput "setxkbmap" ["-query"] ""
729 let
730 args = case next of
731 (l, Just v) -> [l, v]
732 (l, Nothing) -> [l]
733 safeSpawn "setxkbmap" args
734 where
735 extract :: String -> Maybe (String, Maybe String)
736 extract str = listToMaybe $ do
737 ["layout:", l] <- str'
738 [(l, Just v) | ["variant:", v] <- str'] ++ pure (l, Nothing)
739 where
740 str' = map words $ lines str
741 getNext :: Maybe (String, Maybe String) -> (String, Maybe String)
742 getNext = maybe (head layouts) getNext'
743 getNext' x = case elemIndex x layouts of
744 Nothing -> getNext Nothing
745 Just i -> layouts !! ((i + 1) `mod` length layouts)
746
747mpvAll' :: MpvCommand -> IO [MpvResponse]
748mpvAll' = mpvAll "/var/media/.mpv-ipc"
749
750mpvOne' :: MpvCommand -> IO (Maybe MpvResponse)
751mpvOne' = mpvOne "/var/media/.mpv-ipc"
752
753mediaMpv :: MpvCommand -> X ()
754mediaMpv cmd = void . xfork $ print =<< mpvAll' cmd
755
756mediaMpvTogglePause :: X ()
757mediaMpvTogglePause = void . xfork $ do
758 paused <- mapM mpvResponse <=< mpvAll' $ MpvGetProperty "pause"
759 if
760 | and paused -> print <=< mpvAll' $ MpvSetProperty "pause" False
761 | otherwise -> print <=< mpvOne' $ MpvSetProperty "pause" True
762
763myKeys' conf host = Map.fromList $
764 -- launch a terminal
765 [ ((modm, xK_Return), spawn $ (XMonad.terminal conf) ++ " -e tmux")
766 , ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
767
768 -- launch dmenu
769 --, ((modm, xK_d ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
770 , ((modm, xK_d ), shellPrompt "Run: " xPConfig)
771 , ((modm .|. shiftMask, xK_d ), prompt "Run in Terminal: " ("urxvtc" ++ " -e") xPConfig)
772 , ((modm, xK_at ), sshPrompt sshOverrides xPConfig)
773
774 -- close focused window
775 , ((modm .|. shiftMask, xK_q ), kill)
776 , ((modm .|. controlMask .|. shiftMask, xK_q ), spawn "xkill")
777
778 -- Rotate through the available layout algorithms
779 , ((modm, xK_space ), sendMessage NextLayout)
780
781 -- Reset the layouts on the current workspace to default
782 , ((modm .|. controlMask, xK_r ), (setLayout $ XMonad.layoutHook conf) >> refresh)
783
784 -- Resize viewed windows to the correct size
785 , ((modm, xK_r ), refresh)
786
787 -- Move focus to the next window
788 , ((modm, xK_t ), windows W.focusDown)
789
790 -- Move focus to the previous window
791 , ((modm, xK_n ), windows W.focusUp )
792
793 -- Move focus to the master window
794 , ((modm, xK_m ), windows W.focusMaster )
795
796 -- Swap the focused window and the master window
797 , ((modm .|. shiftMask, xK_m ), windows W.swapMaster)
798
799 -- Swap the focused window with the next window
800 , ((modm .|. shiftMask, xK_t ), windows W.swapDown )
801
802 -- Swap the focused window with the previous window
803 , ((modm .|. shiftMask, xK_n ), windows W.swapUp )
804
805 -- Swap the focused window with the previous window
806 , ((modm .|. shiftMask .|. controlMask, xK_m), sendMessage SwapWindow)
807
808 , ((modm, xK_Right), sendMessage $ Go R)
809 , ((modm, xK_Left ), sendMessage $ Go L)
810 , ((modm, xK_Up ), sendMessage $ Go U)
811 , ((modm, xK_Down ), sendMessage $ Go D)
812 , ((modm .|. shiftMask , xK_Right), sendMessage $ Move R)
813 , ((modm .|. shiftMask , xK_Left ), sendMessage $ Move L)
814 , ((modm .|. shiftMask , xK_Up ), sendMessage $ Move U)
815 , ((modm .|. shiftMask , xK_Down ), sendMessage $ Move D)
816 -- , ((modm .|. controlMask, xK_Right), withFocused $ keysMoveWindow (10, 0))
817 -- , ((modm .|. controlMask, xK_Left ), withFocused $ keysMoveWindow (-10, 0))
818 -- , ((modm .|. controlMask, xK_Up ), withFocused $ keysMoveWindow (0, -10))
819 -- , ((modm .|. controlMask, xK_Down ), withFocused $ keysMoveWindow (0, 10))
820 -- Shrink the master area
821 , ((modm, xK_h ), sendMessage Shrink)
822
823 -- Expand the master area
824 , ((modm, xK_s ), sendMessage Expand)
825
826 -- Push window back into tiling
827 , ((modm .|. shiftMask, xK_space ), withFocused $ windows . W.sink)
828 , ((modm, xK_BackSpace), focusUrgent)
829 , ((modm .|. shiftMask, xK_BackSpace), clearUrgents)
830
831 -- Increment the number of windows in the master area
832 , ((modm , xK_comma ), sendMessage (IncMasterN 1))
833
834 -- Deincrement the number of windows in the master area
835 , ((modm , xK_period), sendMessage (IncMasterN (-1)))
836
837 , ((0, xF86XK_AudioRaiseVolume), safeSpawn "pulseaudio-ctl" ["up", "2"])
838 , ((0, xF86XK_AudioLowerVolume), safeSpawn "pulseaudio-ctl" ["down", "2"])
839 , ((0, xF86XK_AudioMute), safeSpawn "pulseaudio-ctl" ["mute"])
840 , ((0, xF86XK_AudioPause), mediaMpv $ MpvSetProperty "pause" False)
841 , ((0, {-xF86XK_AudioMicMute-} 269025202), safeSpawn "pulseaudio-ctl" ["mute-input"])
842 , ((0, xF86XK_AudioPlay), mediaMpvTogglePause)
843 , ((modm .|. mod1Mask, xK_space), mediaMpvTogglePause)
844
845 , ((0, xF86XK_MonBrightnessDown), backlight (subtract 5))
846 , ((0, xF86XK_MonBrightnessUp), backlight (+ 5))
847
848 , ((modm , xK_Escape), cycleKbLayout (hKbLayouts host))
849 , ((modm .|. controlMask, xK_Escape), safeSpawn "setxkbmap" $ fst (head $ hKbLayouts host) : maybeToList (snd . head $ hKbLayouts host))
850
851 -- Toggle the status bar gap
852 -- Use this binding with avoidStruts from Hooks.ManageDocks.
853 -- See also the statusBar function from Hooks.DynamicLog.
854 --
855 , ((modm , xK_b ), sendMessage ToggleStruts)
856
857 , ((modm .|. shiftMask, xK_p ), safeSpawn "playerctl" ["-a", "pause"])
858
859 -- Quit xmonad
860 , ((modm .|. shiftMask, xK_e ), io (exitWith ExitSuccess))
861
862 -- Restart xmonad
863 -- , ((modm .|. shiftMask .|. controlMask, xK_r ), void . xfork $ recompile False >>= flip when (safeSpawn "xmonad" ["--restart"]))
864 , ((modm .|. shiftMask, xK_r ), void . liftIO $ executeFile "xmonad" True [] Nothing)
865 , ((modm .|. shiftMask, xK_l ), void . xfork $ do
866 sessId <- getEnv "XDG_SESSION_ID"
867 safeSpawn "loginctl" ["lock-session", sessId]
868 )
869 , ((modm .|. shiftMask, xK_s ), safeSpawn "systemctl" ["suspend"])
870 , ((modm .|. shiftMask, xK_h ), safeSpawn "systemctl" ["hibernate"])
871 , ((modm .|. shiftMask, xK_b ), backlight $ cycleThrough [1, 3 % 4, 1 % 2, 1 % 4, 1 % 10, 1 % 100, 0]
872 )
873 , ((modm .|. shiftMask .|. controlMask, xK_b), backlight $ cycleThrough [0, 1 % 100, 1 % 10, 1 % 4, 1 % 2, 3 % 4, 1]
874 )
875 , ((modm, xK_v ), windows copyToAll) -- @@ Make focused window always visible
876 , ((modm .|. shiftMask, xK_v ), killAllOtherCopies) -- @@ Toggle window state back
877 , ((modm .|. shiftMask, xK_g ), windowPrompt xPConfig Goto wsWindows)
878 , ((modm .|. shiftMask .|. controlMask, xK_g ), windowPrompt xPConfig Bring allWindows)
879 ]
880 ++
881
882 --
883 -- mod-[1..9], Switch to workspace N
884 --
885 -- mod-[1..9], Switch to workspace N
886 -- mod-shift-[1..9], Move client to workspace N
887 --
888 [((m .|. modm, k), windows $ f i)
889 | (i, k) <- zip (XMonad.workspaces conf) $ numKeys
890 , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]
891 ]
892 ++
893 [((m .|. modm .|. controlMask, k), void . runMaybeT $
894 MaybeT (P.getScreen def i) >>= MaybeT . screenWorkspace >>= lift . windows . f
895 )
896 | (i, k) <- zip (hScreens host) [xK_g, xK_c, xK_r, xK_l]
897 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
898 ]
899 where
900 modm = XMonad.modMask conf
901
902