diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Main.hs | 12 | ||||
-rw-r--r-- | src/XMonad/Actions/FloatSnapSpaced.hs | 12 | ||||
-rw-r--r-- | src/XMonad/Actions/PerConditionKeys.hs | 12 | ||||
-rw-r--r-- | src/XMonad/Custom/Bindings.hs | 118 | ||||
-rw-r--r-- | src/XMonad/Custom/Event.hs | 14 | ||||
-rw-r--r-- | src/XMonad/Custom/Layout.hs | 23 | ||||
-rw-r--r-- | src/XMonad/Custom/Log.hs | 36 | ||||
-rw-r--r-- | src/XMonad/Custom/Manage.hs | 16 | ||||
-rw-r--r-- | src/XMonad/Custom/Misc.hs | 42 | ||||
-rw-r--r-- | src/XMonad/Custom/Navigation.hs | 16 | ||||
-rw-r--r-- | src/XMonad/Custom/Projects.hs | 14 | ||||
-rw-r--r-- | src/XMonad/Custom/Scratchpads.hs | 12 | ||||
-rw-r--r-- | src/XMonad/Custom/Startup.hs | 42 | ||||
-rw-r--r-- | src/XMonad/Custom/Theme.hs | 12 | ||||
-rw-r--r-- | src/XMonad/Custom/Workspaces.hs | 14 |
15 files changed, 296 insertions, 99 deletions
diff --git a/src/Main.hs b/src/Main.hs index 74117e4..159cfaa 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,3 +1,15 @@ +----------------------------------------------------------------------------- +-- | +-- Module : Main +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +------------------------------------------------------------------------ + module Main where import XMonad diff --git a/src/XMonad/Actions/FloatSnapSpaced.hs b/src/XMonad/Actions/FloatSnapSpaced.hs index 9a66643..4113a13 100644 --- a/src/XMonad/Actions/FloatSnapSpaced.hs +++ b/src/XMonad/Actions/FloatSnapSpaced.hs @@ -1,3 +1,15 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Actions.FloatSnapSpaced +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +------------------------------------------------------------------------ + module XMonad.Actions.FloatSnapSpaced ( snapSpacedMagicMove ) where diff --git a/src/XMonad/Actions/PerConditionKeys.hs b/src/XMonad/Actions/PerConditionKeys.hs index 85469d6..faa33c1 100644 --- a/src/XMonad/Actions/PerConditionKeys.hs +++ b/src/XMonad/Actions/PerConditionKeys.hs @@ -1,3 +1,15 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Actions.PerConditionKeys +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +------------------------------------------------------------------------ + module XMonad.Actions.PerConditionKeys ( XCond(..) , chooseAction diff --git a/src/XMonad/Custom/Bindings.hs b/src/XMonad/Custom/Bindings.hs index fd59e88..fa7cb17 100644 --- a/src/XMonad/Custom/Bindings.hs +++ b/src/XMonad/Custom/Bindings.hs @@ -1,3 +1,17 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Bindings +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +-- Custom target for keyboard/mouse bindings. +-- +------------------------------------------------------------------------ + module XMonad.Custom.Bindings ( showKeyBindings , modMask' @@ -10,13 +24,13 @@ import qualified Data.Map as M import System.Exit import System.IO import XMonad +import qualified XMonad.Actions.ConstrainedResize as C import XMonad.Actions.CopyWindow -import qualified XMonad.Actions.ConstrainedResize as C import XMonad.Actions.CycleWS -import qualified XMonad.Actions.FlexibleManipulate as F import XMonad.Actions.DynamicProjects -import XMonad.Actions.FloatSnap import XMonad.Actions.DynamicWorkspaces +import qualified XMonad.Actions.FlexibleManipulate as F +import XMonad.Actions.FloatSnap import XMonad.Actions.FloatSnapSpaced import XMonad.Actions.MessageFeedback import XMonad.Actions.Navigation2D @@ -66,7 +80,7 @@ directions = [D, U, L, R] arrowKeys, directionKeys, wsKeys :: [String] arrowKeys = [ "<D>" , "<U>" , "<L>" , "<R>" ] directionKeys = [ "j" , "k" , "h" , "l" ] -wsKeys = map show [1 .. 9 :: Int] +wsKeys = map show [1..9 :: Int] zipM :: [a] -> String -> [[a]] -> [t] -> (t -> X ()) -> [([a], NamedAction)] zipM m nm ks as f = zipWith (\k d -> (m ++ k, addName nm $ f d)) ks as @@ -77,15 +91,13 @@ tryMessageR_ :: (Message a, Message b) => a -> b -> X () tryMessageR_ x y = sequence_ [tryMessage_ x y, refresh] xSelectionNotify :: MonadIO m => m () -xSelectionNotify = join - $ io - $ (unsafeSpawn . (\x -> CM.notify CM.customApplications ++ " Clipboard " ++ wrap "\"\\\"" "\"\\\"" x)) - <$> getSelection +xSelectionNotify = join $ io + $ (unsafeSpawn . (\x -> CM.notify CM.customApplications ++ " Clipboard " ++ wrap "\"\\\"" "\"\\\"" x)) <$> getSelection toggleCopyToAll :: X () toggleCopyToAll = wsContainingCopies >>= \x -> case x of - [] -> windows copyToAll - _ -> killAllOtherCopies + [] -> windows copyToAll + _ -> killAllOtherCopies getSortByIndexNonSP :: X ([WindowSpace] -> [WindowSpace]) getSortByIndexNonSP = (. namedScratchpadFilterOutWorkspace) <$> getSortByIndex @@ -96,20 +108,21 @@ prevNonEmptyWS = findWorkspace getSortByIndexNonSP Prev HiddenNonEmptyWS 1 >>= \ toggleFloat :: Window -> X () toggleFloat w = windows (\s -> if M.member w (S.floating s) - then S.sink w s + then S.sink w s else S.float w (S.RationalRect (1/2 - 1/4) (1/2 - 1/4) (1/2) (1/2)) s) keyBindings :: XConfig Layout -> [((KeyMask, KeySym), NamedAction)] -keyBindings c = let subKeys s ks = subtitle s:mkNamedKeymap c ks in +keyBindings c = + let subKeys s ks = subtitle s:mkNamedKeymap c ks + in subKeys "System" - [ ("M-q" , addName "Restart XMonad" $ spawn "/usr/bin/xmonad --restart") - , ("M-C-q" , addName "Recompile & restart XMonad" $ spawn "/usr/bin/xmonad --recompile && /usr/bin/xmonad --restart") - , ("M-S-q" , addName "Quit XMonad" $ confirmPrompt hotPromptTheme "Quit XMonad?" $ io exitSuccess) - , ("M-x" , addName "Shell prompt" $ shellPrompt promptTheme) - , ("M-o" , addName "Goto W prompt" $ windowPrompt promptTheme Goto allWindows) - , ("M-S-o" , addName "Bring W prompt" $ windowPrompt promptTheme Bring allWindows) + [ ("M-q" , addName "Restart XMonad" $ spawn "/usr/bin/xmonad --restart") + , ("M-C-q" , addName "Recompile & restart XMonad" $ spawn "/usr/bin/xmonad --recompile && /usr/bin/xmonad --restart") + , ("M-S-q" , addName "Quit XMonad" $ confirmPrompt hotPromptTheme "Quit XMonad?" $ io exitSuccess) + , ("M-x" , addName "Shell prompt" $ shellPrompt promptTheme) + , ("M-o" , addName "Goto W prompt" $ windowPrompt promptTheme Goto allWindows) + , ("M-S-o" , addName "Bring W prompt" $ windowPrompt promptTheme Bring allWindows) ] - ^++^ subKeys "Actions" [ ("M-C-g" , addName "Cancel" $ return ()) @@ -136,9 +149,8 @@ keyBindings c = let subKeys s ks = subtitle s:mkNamedKeymap c ks in , ("M-C-t" , addName "Toggle trackpoint on/off" $ spawn "~/.xmonad/bin/\ \toggle-trackpoint.sh") ] - ^++^ - subKeys "Volume & Music" -- TODO replace play/pause script with Haskell implementation + subKeys "Volume & Music" [ ("<XF86AudioMute>" , addName "ALSA: Mute" $ void toggleMute) , ("<XF86AudioLowerVolume>" , addName "ALSA: Lower volume" $ void $ lowerVolume 5) , ("<XF86AudioRaiseVolume>" , addName "ALSA: Raise volume" $ void $ raiseVolume 5) @@ -147,7 +159,6 @@ keyBindings c = let subKeys s ks = subtitle s:mkNamedKeymap c ks in , ("<XF86AudioPrev>" , addName "MPD: Previos track" $ spawn "/usr/bin/mpc --no-status prev") , ("<XF86AudioNext>" , addName "MPD: Next track" $ spawn "/usr/bin/mpc --no-status next") ] - ^++^ subKeys "Spawnables" [ ("M-<Return>" , addName "Terminal" $ spawn (CM.term CM.customApplications)) @@ -158,38 +169,34 @@ keyBindings c = let subKeys s ks = subtitle s:mkNamedKeymap c ks in , ("M-t" , addName "NSP Top" $ namedScratchpadAction scratchpads "top") , ("M-v" , addName "NSP Volume" $ namedScratchpadAction scratchpads "volume") ] - ^++^ subKeys "Windows" - ( [ ("M-d" , addName "Kill W" kill) - , ("M-S-d" , addName "Kill all W on WS" $ confirmPrompt hotPromptTheme "Kill all" killAll) - , ("M-C-d" , addName "Duplicate W to all WS" toggleCopyToAll) - , ("M-a" , addName "Hide W" $ withFocused hideWindow) -- FIXME This is so broken - , ("M-S-a" , addName "Restore hidden W" popOldestHiddenWindow) - , ("M-p" , addName "Promote W" promote) - , ("M-s" , addName "Merge W from sublayout" $ withFocused $ sendMessage . MergeAll) - , ("M-S-s" , addName "Unmerge W from sublayout" $ withFocused $ sendMessage . UnMerge) - , ("M-u" , addName "Focus urgent W" focusUrgent) - , ("M-e" , addName "Focus master W" $ windows S.focusMaster) - , ("M-'" , addName "Navigate tabbed W -> D" $ bindOn LD [ ("Tabs" , windows S.focusDown) + ( [ ("M-d" , addName "Kill W" kill) + , ("M-S-d" , addName "Kill all W on WS" $ confirmPrompt hotPromptTheme "Kill all" killAll) + , ("M-C-d" , addName "Duplicate W to all WS" toggleCopyToAll) + , ("M-a" , addName "Hide W" $ withFocused hideWindow) -- FIXME This is so broken + , ("M-S-a" , addName "Restore hidden W" popOldestHiddenWindow) + , ("M-p" , addName "Promote W" promote) + , ("M-s" , addName "Merge W from sublayout" $ withFocused $ sendMessage . MergeAll) + , ("M-S-s" , addName "Unmerge W from sublayout" $ withFocused $ sendMessage . UnMerge) + , ("M-u" , addName "Focus urgent W" focusUrgent) + , ("M-e" , addName "Focus master W" $ windows S.focusMaster) + , ("M-'" , addName "Navigate tabbed W -> D" $ bindOn LD [ ("Tabs" , windows S.focusDown) , ("" , onGroup S.focusDown') ]) - , ("M-;" , addName "Navigate tabbed W -> U" $ bindOn LD [ ("Tabs" , windows S.focusUp) + , ("M-;" , addName "Navigate tabbed W -> U" $ bindOn LD [ ("Tabs" , windows S.focusUp) , ("" , onGroup S.focusUp') ]) - , ("M-S-'" , addName "Swap tabbed W -> D" $ windows S.swapDown) - , ("M-S-;" , addName "Swap tabbed W -> U" $ windows S.swapUp) + , ("M-S-'" , addName "Swap tabbed W -> D" $ windows S.swapDown) + , ("M-S-;" , addName "Swap tabbed W -> U" $ windows S.swapUp) ] - ++ zipM' "M-" "Navigate W" directionKeys directions windowGo True -- TODO W moving ++ zipM' "M-S-" "Swap W" directionKeys directions windowSwap True ++ zipM "M-C-" "Merge W with sublayout" directionKeys directions (sendMessage . pullGroup) - ++ zipM' "M-" "Navigate screen" arrowKeys directions screenGo True ++ zipM' "M-S-" "Move W to screen" arrowKeys directions windowToScreen True ++ zipM' "M-C-" "Swap W to screen" arrowKeys directions screenSwap True ) - ^++^ subKeys "Workspaces & Projects" ( [ ("M-w" , addName "Switch to project" $ switchProjectPrompt promptTheme) @@ -199,12 +206,10 @@ keyBindings c = let subKeys s ks = subtitle s:mkNamedKeymap c ks in , ("M-i" , addName "Toggle last WS" $ toggleWS' ["NSP"]) , ("M-`" , addName "WS prompt" $ workspacePrompt promptTheme $ windows . S.shift) ] - ++ zipM "M-" "View WS" wsKeys [0 ..] (withNthWorkspace S.greedyView) ++ zipM "M-S-" "Move W to WS" wsKeys [0 ..] (withNthWorkspace S.shift) ++ zipM "M-C-S-" "Copy W to WS" wsKeys [0 ..] (withNthWorkspace copy) ) - ^++^ subKeys "Layout Management" [ ("M-<Tab>" , addName "Cycle layouts" $ sendMessage NextLayout) @@ -221,7 +226,6 @@ keyBindings c = let subKeys s ks = subtitle s:mkNamedKeymap c ks in ]) , ("M-S-g" , addName "Toggle gapped layout" $ sendMessage $ Toggle GAPS) -- FIXME Breaks merged tabbed layout ] - ^++^ subKeys "Resize" [ ("M-[" , addName "Expand L" $ tryMessageR_ (ExpandTowards L) Shrink) @@ -236,20 +240,24 @@ keyBindings c = let subKeys s ks = subtitle s:mkNamedKeymap c ks in mouseBindings' :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ()) mouseBindings' XConfig {XMonad.modMask = m} = M.fromList - [ ((m, button1), \w -> focus w >> F.mouseWindow F.position w - >> ifClick (snapSpacedMagicMove gapBase (Just 50) (Just 50) w) - >> windows S.shiftMaster + [ ((m, button1), \w -> focus w + >> F.mouseWindow F.position w + >> ifClick (snapSpacedMagicMove gapBase (Just 50) (Just 50) w) + >> windows S.shiftMaster ) - , ((m .|. shiftMask, button1), \w -> focus w >> C.mouseResizeWindow w True - >> ifClick (snapMagicResize [L, R, U, D] (Just 50) (Just 50) w) - >> windows S.shiftMaster + , ((m .|. shiftMask, button1), \w -> focus w + >> C.mouseResizeWindow w True + >> ifClick (snapMagicResize [L, R, U, D] (Just 50) (Just 50) w) + >> windows S.shiftMaster ) - , ((m, button3), \w -> focus w >> F.mouseWindow F.linear w - >> ifClick (snapMagicResize [L, R] (Just 50) (Just 50) w) - >> windows S.shiftMaster + , ((m, button3), \w -> focus w + >> F.mouseWindow F.linear w + >> ifClick (snapMagicResize [L, R] (Just 50) (Just 50) w) + >> windows S.shiftMaster ) - , ((m .|. shiftMask, button3), \w -> focus w >> C.mouseResizeWindow w True - >> ifClick (snapMagicResize [U, D] (Just 50) (Just 50) w) - >> windows S.shiftMaster + , ((m .|. shiftMask, button3), \w -> focus w + >> C.mouseResizeWindow w True + >> ifClick (snapMagicResize [U, D] (Just 50) (Just 50) w) + >> windows S.shiftMaster ) ] diff --git a/src/XMonad/Custom/Event.hs b/src/XMonad/Custom/Event.hs index 032efd1..926614b 100644 --- a/src/XMonad/Custom/Event.hs +++ b/src/XMonad/Custom/Event.hs @@ -1,3 +1,17 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Event +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +-- Custom target for layouts, sublayouts and everything in between. +-- +------------------------------------------------------------------------ + module XMonad.Custom.Event ( handleEventHook' ) where diff --git a/src/XMonad/Custom/Layout.hs b/src/XMonad/Custom/Layout.hs index 8f14926..0ad0de2 100644 --- a/src/XMonad/Custom/Layout.hs +++ b/src/XMonad/Custom/Layout.hs @@ -1,10 +1,25 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeSynonymInstances #-} +{-# OPTIONS_GHC -Wno-missing-signatures #-} + +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Layout +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +-- Custom target for layouts, sublayouts and layout transformers. +-- +------------------------------------------------------------------------ module XMonad.Custom.Layout ( layoutHook' - , Transformers (..) + , CustomTransformers (..) ) where import XMonad @@ -36,10 +51,10 @@ applyGaps = gaps [ (U, gapBase) , (L, gapBase) ] -data Transformers = GAPS - deriving (Read, Show, Eq, Typeable) +data CustomTransformers = GAPS + deriving (Read, Show, Eq, Typeable) -instance Transformer Transformers Window where +instance Transformer CustomTransformers Window where transform GAPS x k = k (avoidStruts $ applyGaps $ applySpacing x) (const x) layoutHook' = fullscreenFloat diff --git a/src/XMonad/Custom/Log.hs b/src/XMonad/Custom/Log.hs index 49b7334..1bf05f1 100644 --- a/src/XMonad/Custom/Log.hs +++ b/src/XMonad/Custom/Log.hs @@ -1,5 +1,21 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Log +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi <azahi@teknik.io> +-- Stability : unstable +-- Portability : unportable +-- +-- Provides configuration for logging to be used +-- with various status display applications +-- +----------------------------------------------------------------------------- + module XMonad.Custom.Log - ( logHook' ) where + ( logHook' + ) where import System.IO import XMonad @@ -13,7 +29,7 @@ import XMonad.Util.SpawnNamedPipe import XMonad.Util.WorkspaceCompare xmobarFont :: Int -> String -> String -xmobarFont fn = wrap (concat ["<fn=", show fn, ">"]) "</fn>" +xmobarFont f = wrap (concat ["<fn=", show f, ">"]) "</fn>" topBarPP :: PP topBarPP = def @@ -27,9 +43,9 @@ topBarPP = def , ppTitle = xmobarColor white1 "" . shorten 50 , ppTitleSanitize = xmobarStrip , ppLayout = xmobarColor white1 "" . \x -> case x of -- TODO Generalize string conversion - "Spacing 12 Tabbed Hidden BSP" -> "Omni.Gaps" - "Tabbed Hidden BSP" -> "Omni" - _ -> "Misc" + "Spacing 12 Tabbed Hidden BSP" -> "Omni.Gaps" + "Tabbed Hidden BSP" -> "Omni" + _ -> "Misc" , ppOrder = id , ppSort = (namedScratchpadFilterOutWorkspace .) <$> getSortByIndex , ppExtras = [] @@ -53,9 +69,9 @@ logHook' :: X () logHook' = do currentWorkspaceOnTop ewmhDesktopsLogHook - b1 <- getNamedPipe "xmobarTop" - b2 <- getNamedPipe "xmobarBot" - c <- wsContainingCopies + t <- getNamedPipe "xmobarTop" + b <- getNamedPipe "xmobarBot" + c <- wsContainingCopies let copiesCurrent ws | ws `elem` c = xmobarColor yellow2 "" . xmobarFont 2 . wrap "*" "=" $ ws | otherwise = xmobarColor white2 "" . xmobarFont 2 . wrap "=" "=" $ ws let copiesHidden ws | ws `elem` c = xmobarColor yellow1 "" . wrap "*" "-" $ ws @@ -66,8 +82,8 @@ logHook' = do { ppCurrent = copiesCurrent , ppHidden = copiesHidden , ppUrgent = copiesUrgent - , ppOutput = safePrintToPipe b1 + , ppOutput = safePrintToPipe t } dynamicLogWithPP $ botBarPP - { ppOutput = safePrintToPipe b2 + { ppOutput = safePrintToPipe b } diff --git a/src/XMonad/Custom/Manage.hs b/src/XMonad/Custom/Manage.hs index 09ee651..ce5efe2 100644 --- a/src/XMonad/Custom/Manage.hs +++ b/src/XMonad/Custom/Manage.hs @@ -1,3 +1,17 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Manage +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi <azahi@teknik.io> +-- Stability : unstable +-- Portability : unportable +-- +-- Custom target for container (window) management. +-- +----------------------------------------------------------------------------- + module XMonad.Custom.Manage ( manageHook' ) where @@ -16,12 +30,12 @@ composeActions = , appName =? "eterm" -?> tileBelow , className =? "Pinentry" -?> doCenterFloat , className =? "Steam" <&&> not <$> title =? "Steam" -?> doFloat - , className =? "URxvt" -?> tileBelow , className =? "Xmessage" -?> doCenterFloat , className =? "Zenity" -?> doCenterFloat , className =? "explorer.exe" -?> doFullFloat , className =? "qemu-system-x86" -?> doCenterFloat , className =? "qemu-system-x86_64" -?> doCenterFloat + , className =? "urxvt" -?> tileBelow , className =? "xterm" -?> tileBelow , isDialog -?> doCenterFloat , isFullscreen -?> doFullFloat diff --git a/src/XMonad/Custom/Misc.hs b/src/XMonad/Custom/Misc.hs index 41883b5..dbf7e2c 100644 --- a/src/XMonad/Custom/Misc.hs +++ b/src/XMonad/Custom/Misc.hs @@ -1,19 +1,37 @@ +{-# OPTIONS_GHC -funbox-strict-fields #-} + +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Misc +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +-- Miscellaneous functions, data types and declarations used for 'XMonad.Custom'. +-- +------------------------------------------------------------------------ + module XMonad.Custom.Misc ( Applications (..) , customApplications ) where -data Applications = Applications { term :: String - , browser :: String - , top :: String - , mixer :: String - , notify :: String - } deriving (Show) +data Applications = Applications + { term :: !String + , browser :: !String + , top :: !String + , mixer :: !String + , notify :: !String + } deriving (Eq, Show) customApplications :: Applications -customApplications = Applications { term = "/usr/bin/urxvtc" - , browser = "/usr/bin/qutebrowser" - , top = "/usr/bin/htop" - , mixer = "/usr/bin/alsamixer" - , notify = "/usr/bin/notify-send" - } +customApplications = Applications + { term = "/usr/bin/urxvtc" + , browser = "/usr/bin/qutebrowser" + , top = "/usr/bin/htop" + , mixer = "/usr/bin/alsamixer" + , notify = "/usr/bin/notify-send" + } diff --git a/src/XMonad/Custom/Navigation.hs b/src/XMonad/Custom/Navigation.hs index 112afd3..decc2de 100644 --- a/src/XMonad/Custom/Navigation.hs +++ b/src/XMonad/Custom/Navigation.hs @@ -1,8 +1,22 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Navigation +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +-- Custom target for window navigation. +-- +------------------------------------------------------------------------ + module XMonad.Custom.Navigation ( navigation2DConfig ) where -import XMonad.Actions.Navigation2D +import XMonad.Actions.Navigation2D navigation2DConfig :: Navigation2DConfig navigation2DConfig = def diff --git a/src/XMonad/Custom/Projects.hs b/src/XMonad/Custom/Projects.hs index fac181b..6b3951c 100644 --- a/src/XMonad/Custom/Projects.hs +++ b/src/XMonad/Custom/Projects.hs @@ -1,3 +1,17 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Projects +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +-- Custom target for projects. +-- +------------------------------------------------------------------------ + module XMonad.Custom.Projects ( projects ) where diff --git a/src/XMonad/Custom/Scratchpads.hs b/src/XMonad/Custom/Scratchpads.hs index 9d82ed5..b5296cc 100644 --- a/src/XMonad/Custom/Scratchpads.hs +++ b/src/XMonad/Custom/Scratchpads.hs @@ -1,3 +1,15 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Scratchpads +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +------------------------------------------------------------------------ + module XMonad.Custom.Scratchpads ( scratchpads ) where diff --git a/src/XMonad/Custom/Startup.hs b/src/XMonad/Custom/Startup.hs index b2765a0..f2c0af0 100644 --- a/src/XMonad/Custom/Startup.hs +++ b/src/XMonad/Custom/Startup.hs @@ -1,3 +1,15 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Startup +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +------------------------------------------------------------------------ + module XMonad.Custom.Startup ( startupHook' ) where @@ -12,25 +24,25 @@ import XMonad.Util.SpawnNamedPipe atomsToFullscreen :: [String] atomsToFullscreen = - [ "_NET_ACTIVE_WINDOW" - , "_NET_CLIENT_LIST" - , "_NET_CLIENT_LIST_STACKING" - , "_NET_DESKTOP_NAMES" - , "_NET_WM_DESKTOP" - , "_NET_WM_STATE" - , "_NET_WM_STATE_FULLSCREEN" - , "_NET_WM_STATE_HIDDEN" - , "_NET_WM_STRUT" - ] + [ "_NET_ACTIVE_WINDOW" + , "_NET_CLIENT_LIST" + , "_NET_CLIENT_LIST_STACKING" + , "_NET_DESKTOP_NAMES" + , "_NET_WM_DESKTOP" + , "_NET_WM_STATE" + , "_NET_WM_STATE_FULLSCREEN" + , "_NET_WM_STATE_HIDDEN" + , "_NET_WM_STRUT" + ] addNETSupported :: Atom -> X () addNETSupported x = withDisplay $ \d -> do - r <- asks theRoot - ns <- getAtom "_NET_SUPPORTED" - a <- getAtom "ATOM" + r <- asks theRoot + n <- getAtom "_NET_SUPPORTED" + a <- getAtom "ATOM" liftIO $ do - s <- (join . maybeToList) <$> getWindowProperty32 d ns r - when (fromIntegral x `notElem` s) $ changeProperty32 d r ns a propModeAppend [fromIntegral x] + p <- (join . maybeToList) <$> getWindowProperty32 d n r + when (fromIntegral x `notElem` p) $ changeProperty32 d r n a propModeAppend [fromIntegral x] addEWMHFullscreen :: X () addEWMHFullscreen = do diff --git a/src/XMonad/Custom/Theme.hs b/src/XMonad/Custom/Theme.hs index 50fa398..bad73e4 100644 --- a/src/XMonad/Custom/Theme.hs +++ b/src/XMonad/Custom/Theme.hs @@ -1,3 +1,15 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Theme +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +------------------------------------------------------------------------ + module XMonad.Custom.Theme ( font , black1 diff --git a/src/XMonad/Custom/Workspaces.hs b/src/XMonad/Custom/Workspaces.hs index beae415..a62b4af 100644 --- a/src/XMonad/Custom/Workspaces.hs +++ b/src/XMonad/Custom/Workspaces.hs @@ -1,3 +1,15 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Custom.Workspaces +-- Copyright : (c) azahi 2018 +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : azahi@teknik.io +-- Stability : unstable +-- Portability : unportable +-- +------------------------------------------------------------------------ + module XMonad.Custom.Workspaces ( workspaces' ) where @@ -5,4 +17,4 @@ module XMonad.Custom.Workspaces import XMonad.Core workspaces' :: [WorkspaceId] -workspaces' = map show [1 .. 9 :: Int] +workspaces' = map show [1..9 :: Int] |