stockholm/tv/5pkgs/haskell/xmonad-tv/src/main.hs

242 lines
8.1 KiB
Haskell
Raw Normal View History

{-# LANGUAGE LambdaCase #-}
2022-11-27 21:05:55 +00:00
{-# LANGUAGE PatternSynonyms #-}
2018-11-30 13:18:14 +00:00
module Main (main) where
import System.Exit (exitFailure)
2023-01-18 20:20:08 +00:00
import XMonad.Hooks.EwmhDesktops (ewmh)
2023-01-18 20:22:53 +00:00
import XMonad.Hooks.RefocusLast (refocusLastLayoutHook, toggleFocus)
import Control.Exception
2022-06-19 10:34:14 +00:00
import Control.Monad.Extra (whenJustM)
import qualified Data.Aeson
import qualified Data.ByteString.Char8
import qualified Data.List
import qualified Data.Maybe
import Graphics.X11.ExtraTypes.XF86
import Text.Read (readEither)
import XMonad
import XMonad.Extra (isFloatingX)
import System.IO (hPutStrLn, stderr)
2018-11-28 16:03:53 +00:00
import System.Environment (getArgs, getEnv, getEnvironment, lookupEnv)
import System.Posix.Process (executeFile)
import XMonad.Actions.DynamicWorkspaces ( addWorkspacePrompt, renameWorkspace
, removeEmptyWorkspace)
import XMonad.Actions.CycleWS (toggleWS)
import XMonad.Layout.NoBorders ( smartBorders )
2018-12-01 10:40:01 +00:00
import XMonad.Layout.ResizableTile (ResizableTall(ResizableTall))
import XMonad.Layout.ResizableTile (MirrorResize(MirrorExpand,MirrorShrink))
2022-11-27 21:05:55 +00:00
import XMonad.Layout.StateFull (pattern StateFull)
2020-06-03 18:41:10 +00:00
import qualified XMonad.Prompt
import qualified XMonad.StackSet as W
import Data.Map (Map)
import qualified Data.Map as Map
2022-03-31 21:12:39 +00:00
import XMonad.Hooks.UrgencyHook
( BorderUrgencyHook(BorderUrgencyHook,urgencyBorderColor)
, RemindWhen(Dont)
, SuppressWhen(Never)
, UrgencyConfig(UrgencyConfig,remindWhen,suppressWhen)
, withUrgencyHookC
)
2020-05-05 15:37:18 +00:00
import XMonad.Hooks.ManageHelpers (doCenterFloat,doRectFloat)
import Data.Ratio
import XMonad.Hooks.Place (placeHook, smart)
import XMonad.Actions.PerWorkspaceKeys (chooseAction)
2022-12-05 15:25:33 +00:00
import Shutdown (shutdown, newShutdownEventHandler)
2018-11-30 13:18:14 +00:00
main :: IO ()
main = getArgs >>= \case
[] -> mainNoArgs
2018-11-29 20:24:31 +00:00
["--shutdown"] -> shutdown
args -> hPutStrLn stderr ("bad arguments: " <> show args) >> exitFailure
2018-11-30 13:18:14 +00:00
2021-02-20 12:08:12 +00:00
(=??) :: Query a -> (a -> Bool) -> Query Bool
(=??) x p = fmap p x
readEnv :: Data.Aeson.FromJSON b => String -> IO b
readEnv name =
Data.Maybe.fromJust
. Data.Aeson.decodeStrict'
. Data.ByteString.Char8.pack
<$> getEnv name
mainNoArgs :: IO ()
mainNoArgs = do
myScreenWidth <- readEnv "XMONAD_SCREEN_WIDTH" :: IO Dimension
myTermFont <- getEnv "XMONAD_TERM_FONT"
myTermFontWidth <- readEnv "XMONAD_TERM_FONT_WIDTH" :: IO Dimension
myTermPadding <- readEnv "XMONAD_TERM_PADDING" :: IO Dimension
workspaces0 <- getWorkspaces0
2018-11-29 20:24:31 +00:00
handleShutdownEvent <- newShutdownEventHandler
2022-06-19 10:34:14 +00:00
let
config =
2023-01-18 20:20:08 +00:00
ewmh
2022-03-31 21:12:39 +00:00
$ withUrgencyHookC
BorderUrgencyHook
{ urgencyBorderColor = "#ff0000"
}
UrgencyConfig
{ remindWhen = Dont
, suppressWhen = Never
}
2016-02-12 13:20:51 +00:00
$ def
2023-01-11 16:20:34 +00:00
{ terminal = {-pkg:alacritty-tv-}"alacritty"
, modMask = mod4Mask
, keys = myKeys myTermFont
, workspaces = workspaces0
2018-12-01 10:40:01 +00:00
, layoutHook =
2023-01-18 20:22:53 +00:00
refocusLastLayoutHook $
2018-12-01 10:40:01 +00:00
smartBorders $
ResizableTall
1
(fromIntegral (10 * myTermFontWidth) / fromIntegral myScreenWidth)
(fromIntegral (80 * myTermFontWidth + 2 * (myTermPadding + borderWidth def)) / fromIntegral myScreenWidth)
[]
2018-12-01 10:40:01 +00:00
|||
2022-11-27 21:05:55 +00:00
StateFull
2018-11-28 08:55:38 +00:00
, manageHook =
composeAll
[ appName =? "fzmenu-urxvt" --> doCenterFloat
2021-02-20 12:08:12 +00:00
, appName =?? Data.List.isPrefixOf "pinentry" --> doCenterFloat
, appName =?? Data.List.isInfixOf "Float" --> doCenterFloat
2020-05-05 15:37:18 +00:00
, title =? "Upload to Imgur" -->
doRectFloat (W.RationalRect 0 0 (1 % 8) (1 % 8))
2018-11-28 08:55:38 +00:00
, placeHook (smart (1,0))
]
, startupHook =
2018-11-28 13:47:08 +00:00
whenJustM (io (lookupEnv "XMONAD_STARTUP_HOOK"))
(\path -> forkFile path [] Nothing)
, normalBorderColor = "#1c1c1c"
, focusedBorderColor = "#f000b0"
, handleEventHook = handleShutdownEvent
}
2022-06-19 10:34:14 +00:00
directories <- getDirectories
launch config directories
getWorkspaces0 :: IO [String]
getWorkspaces0 =
try (getEnv "XMONAD_WORKSPACES0_FILE") >>= \case
Left e -> warn (displaySomeException e)
Right p -> try (readFile p) >>= \case
Left e -> warn (displaySomeException e)
Right x -> case readEither x of
Left e -> warn e
Right y -> return y
where
warn msg = hPutStrLn stderr ("getWorkspaces0: " ++ msg) >> return []
2018-11-30 13:18:14 +00:00
displaySomeException :: SomeException -> String
displaySomeException = displayException
2016-05-24 23:26:25 +00:00
forkFile :: FilePath -> [String] -> Maybe [(String, String)] -> X ()
forkFile path args env =
2021-03-14 22:44:08 +00:00
xfork (executeFile path True args env) >> return ()
2016-05-24 23:26:25 +00:00
2018-11-30 13:18:14 +00:00
2016-05-24 23:26:25 +00:00
spawnRootTerm :: X ()
spawnRootTerm =
forkFile
2023-01-11 16:20:34 +00:00
{-pkg:alacritty-tv-}"alacritty"
["--profile=root", "-e", "/run/wrappers/bin/su", "-"]
2016-05-24 23:26:25 +00:00
Nothing
2018-11-30 13:18:14 +00:00
myKeys :: String -> XConfig Layout -> Map (KeyMask, KeySym) (X ())
myKeys font conf = Map.fromList $
2021-03-14 22:44:08 +00:00
[ ((_4 , xK_Escape ), forkFile {-pkg-}"slock" [] Nothing)
, ((_4S , xK_c ), kill)
2021-03-14 22:44:08 +00:00
, ((_4 , xK_o ), forkFile {-pkg:fzmenu-}"otpmenu" [] Nothing)
, ((_4 , xK_p ), forkFile {-pkg:fzmenu-}"passmenu" [] Nothing)
2018-03-26 11:00:23 +00:00
2023-01-11 16:20:34 +00:00
, ((_4 , xK_x ), forkFile {-pkg:alacritty-tv-}"alacritty" ["--singleton"] Nothing)
2016-05-24 23:26:25 +00:00
, ((_4C , xK_x ), spawnRootTerm)
, ((_C , xK_Menu ), toggleWS)
2018-11-30 13:18:14 +00:00
, ((_4 , xK_space ), withFocused $ \w -> ifM (isFloatingX w) xdeny $ sendMessage NextLayout)
, ((_4M , xK_space ), withFocused $ \w -> ifM (isFloatingX w) xdeny $ resetLayout)
2023-01-18 20:22:53 +00:00
, ((_4 , xK_l ), toggleFocus)
2018-12-01 10:40:33 +00:00
, ((_4 , xK_m ), windows W.focusMaster)
, ((_4 , xK_j ), windows W.focusDown)
, ((_4 , xK_k ), windows W.focusUp)
, ((_4S , xK_m ), windows W.swapMaster)
, ((_4S , xK_j ), windows W.swapDown)
, ((_4S , xK_k ), windows W.swapUp)
2018-12-01 10:40:01 +00:00
, ((_4M , xK_h ), sendMessage Shrink)
, ((_4M , xK_l ), sendMessage Expand)
, ((_4M , xK_j ), sendMessage MirrorShrink)
, ((_4M , xK_k ), sendMessage MirrorExpand)
2018-12-01 10:40:58 +00:00
, ((_4 , xK_t ), withFocused $ windows . W.sink)
, ((_4 , xK_comma ), sendMessage $ IncMasterN 1)
, ((_4 , xK_period ), sendMessage $ IncMasterN (-1))
2020-06-03 18:41:10 +00:00
, ((_4 , xK_a ), addWorkspacePrompt promptXPConfig)
, ((_4 , xK_r ), renameWorkspace promptXPConfig)
, ((_4 , xK_Delete ), removeEmptyWorkspace)
, ((_4 , xK_Return ), toggleWS)
2018-11-30 15:17:32 +00:00
, ((0, xF86XK_AudioLowerVolume), audioLowerVolume)
, ((0, xF86XK_AudioRaiseVolume), audioRaiseVolume)
, ((0, xF86XK_AudioMute), audioMute)
2022-04-05 22:24:49 +00:00
, ((0, xF86XK_AudioMicMute), audioMicMute)
2020-04-12 07:45:06 +00:00
, ((_4, xF86XK_AudioMute), pavucontrol [])
2018-12-02 14:43:49 +00:00
, ((_S, xK_F12), forkFile {-pkg-}"xdotool" ["click", "2"] Nothing)
2021-03-14 22:44:08 +00:00
, ((_4, xK_Prior), forkFile {-pkg-}"xcalib" ["-invert", "-alter"] Nothing)
2020-05-05 15:37:18 +00:00
2021-03-14 22:44:08 +00:00
, ((0, xK_Print), forkFile {-pkg-}"flameshot" [] Nothing)
2021-02-07 21:28:50 +00:00
2021-03-14 22:44:08 +00:00
, ((_C, xF86XK_Forward), forkFile {-pkg:xdpytools-}"xdpychvt" ["next"] Nothing)
, ((_C, xF86XK_Back), forkFile {-pkg:xdpytools-}"xdpychvt" ["prev"] Nothing)
]
where
_4 = mod4Mask
_C = controlMask
_S = shiftMask
_M = mod1Mask
_4C = _4 .|. _C
_4S = _4 .|. _S
_4M = _4 .|. _M
_4CM = _4 .|. _C .|. _M
_4SM = _4 .|. _S .|. _M
amixer args = forkFile {-pkg:alsaUtils-}"amixer" args Nothing
2021-03-14 22:44:08 +00:00
pavucontrol args = forkFile {-pkg-}"pavucontrol" args Nothing
2020-04-12 07:45:06 +00:00
audioLowerVolume = amixer ["-q", "sset", "Master", "5%-"]
audioRaiseVolume = amixer ["-q", "sset", "Master", "5%+"]
audioMute = amixer ["-q", "sset", "Master", "toggle"]
2022-04-05 22:24:49 +00:00
audioMicMute = amixer ["-q", "sset", "Capture", "toggle"]
2016-05-24 23:26:25 +00:00
2018-12-01 10:40:58 +00:00
resetLayout = setLayout $ XMonad.layoutHook conf
2020-06-03 18:41:10 +00:00
promptXPConfig =
def { XMonad.Prompt.font = font }
xdeny =
forkFile
{-pkg-}"xterm"
[ "-fn", font
, "-geometry", "300x100"
, "-name", "AlertFloat"
, "-bg", "#E4002B"
, "-e", "sleep", "0.05"
]
Nothing