From 58890bc80b28ed02e98b21a054849220a69919cb Mon Sep 17 00:00:00 2001 From: lassulus Date: Fri, 13 Nov 2015 01:07:54 +0100 Subject: l: use new xserver architecture --- lass/5pkgs/default.nix | 3 + lass/5pkgs/xmonad-lass/.gitignore | 1 + lass/5pkgs/xmonad-lass/Main.hs | 190 ++++++++++++++++++++++ lass/5pkgs/xmonad-lass/Makefile | 6 + lass/5pkgs/xmonad-lass/Util/PerWorkspaceConfig.hs | 52 ++++++ lass/5pkgs/xmonad-lass/xmonad.cabal | 17 ++ 6 files changed, 269 insertions(+) create mode 100644 lass/5pkgs/xmonad-lass/.gitignore create mode 100644 lass/5pkgs/xmonad-lass/Main.hs create mode 100644 lass/5pkgs/xmonad-lass/Makefile create mode 100644 lass/5pkgs/xmonad-lass/Util/PerWorkspaceConfig.hs create mode 100644 lass/5pkgs/xmonad-lass/xmonad.cabal (limited to 'lass/5pkgs') diff --git a/lass/5pkgs/default.nix b/lass/5pkgs/default.nix index 869f808c..844d68a4 100644 --- a/lass/5pkgs/default.nix +++ b/lass/5pkgs/default.nix @@ -15,4 +15,7 @@ rec { }; go = callPackage ./go/default.nix {}; newsbot-js = callPackage ./newsbot-js/default.nix {}; + xmonad-lass = + let src = pkgs.writeNixFromCabal "xmonad-lass.nix" ./xmonad-lass; in + pkgs.haskellPackages.callPackage src {}; } diff --git a/lass/5pkgs/xmonad-lass/.gitignore b/lass/5pkgs/xmonad-lass/.gitignore new file mode 100644 index 00000000..61620454 --- /dev/null +++ b/lass/5pkgs/xmonad-lass/.gitignore @@ -0,0 +1 @@ +/shell.nix diff --git a/lass/5pkgs/xmonad-lass/Main.hs b/lass/5pkgs/xmonad-lass/Main.hs new file mode 100644 index 00000000..10a3c563 --- /dev/null +++ b/lass/5pkgs/xmonad-lass/Main.hs @@ -0,0 +1,190 @@ +{-# LANGUAGE DeriveDataTypeable #-} -- for XS +{-# LANGUAGE FlexibleContexts #-} -- for xmonad' +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE ScopedTypeVariables #-} + + +module Main where + +import Control.Exception +import Text.Read (readEither) +import XMonad +import System.IO (hPutStrLn, stderr) +import System.Environment (getArgs, withArgs, getEnv, getEnvironment) +import System.Posix.Process (executeFile) +import XMonad.Prompt (defaultXPConfig) +import XMonad.Actions.DynamicWorkspaces ( addWorkspacePrompt, renameWorkspace + , removeEmptyWorkspace) +import XMonad.Actions.GridSelect +import XMonad.Actions.CycleWS (toggleWS) +--import XMonad.Actions.CopyWindow ( copy ) +import XMonad.Layout.NoBorders ( smartBorders ) +import qualified XMonad.StackSet as W +import Data.Map (Map) +import qualified Data.Map as Map +-- TODO import XMonad.Layout.WorkspaceDir +import XMonad.Hooks.UrgencyHook (SpawnUrgencyHook(..), withUrgencyHook) +-- import XMonad.Layout.Tabbed +--import XMonad.Layout.MouseResizableTile +import XMonad.Layout.Reflect (reflectVert) +import XMonad.Layout.FixedColumn (FixedColumn(..)) +import XMonad.Hooks.Place (placeHook, smart) +import XMonad.Hooks.FloatNext (floatNextHook) +import XMonad.Actions.PerWorkspaceKeys (chooseAction) +import XMonad.Layout.PerWorkspace (onWorkspace) +--import XMonad.Layout.BinarySpacePartition +import XMonad.Util.EZConfig (additionalKeysP) + +import XMonad.Prompt (autoComplete, defaultXPConfig, XPConfig, mkXPrompt) +import XMonad.Hooks.UrgencyHook (focusUrgent, withUrgencyHook, urgencyBorderColor, BorderUrgencyHook(BorderUrgencyHook)) +import XMonad.Actions.DynamicWorkspaces (addWorkspacePrompt, removeEmptyWorkspace, renameWorkspace, withWorkspace) +import XMonad.Hooks.FloatNext (floatNext, floatNextHook) +import XMonad.Prompt.Workspace +import XMonad.Actions.CopyWindow (copy, kill1) +import qualified Data.Map as M +import XMonad.Hooks.ManageDocks (avoidStruts, manageDocks, ToggleStruts(ToggleStruts)) + +--import XMonad.Actions.Submap +import XMonad.Stockholm.Pager +import XMonad.Stockholm.Rhombus +import XMonad.Stockholm.Shutdown + +myTerm :: String +myTerm = "urxvtc" + +myRootTerm :: String +myRootTerm = "urxvtc -name root-urxvt -e su -" + +myFont :: String +myFont = "-schumacher-*-*-*-*-*-*-*-*-*-*-*-iso10646-*" + +main :: IO () +main = getArgs >>= \case + ["--shutdown"] -> sendShutdownEvent + _ -> mainNoArgs + +mainNoArgs :: IO () +mainNoArgs = do + xmonad' + -- $ withUrgencyHookC dzenUrgencyHook { args = ["-bg", "magenta", "-fg", "magenta", "-h", "2"], duration = 500000 } + -- urgencyConfig { remindWhen = Every 1 } + -- $ withUrgencyHook borderUrgencyHook "magenta" + -- $ withUrgencyHookC BorderUrgencyHook { urgencyBorderColor = "magenta" } urgencyConfig { suppressWhen = Never } + $ withUrgencyHook (SpawnUrgencyHook "echo emit Urgency ") + $ defaultConfig + { terminal = myTerm + , modMask = mod4Mask + , layoutHook = smartBorders $ myLayoutHook + -- , handleEventHook = myHandleEventHooks <+> handleTimerEvent + --, handleEventHook = handleTimerEvent + , manageHook = placeHook (smart (1,0)) <+> floatNextHook + , startupHook = spawn "echo emit XMonadStartup" + , normalBorderColor = "#1c1c1c" + , focusedBorderColor = "#f000b0" + , handleEventHook = handleShutdownEvent + } `additionalKeysP` myKeyMap + +myLayoutHook = defLayout + where + defLayout = (avoidStruts $ Tall 1 (3/100) (1/2) ||| Full ||| Mirror (Tall 1 (3/100) (1/2))) ||| FixedColumn 2 80 80 1 + + +xmonad' :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO () +xmonad' conf = do + path <- getEnv "XMONAD_STATE" + try (readFile path) >>= \case + Right content -> do + hPutStrLn stderr ("resuming from " ++ path) + withArgs ("--resume" : lines content) (xmonad conf) + Left e -> do + hPutStrLn stderr (displaySomeException e) + xmonad conf + + +displaySomeException :: SomeException -> String +displaySomeException = displayException + + +myKeyMap = + [ ("M4-", spawn "i3lock -i ~/lock.png -u" ) + , ("M4-p", spawn "passmenu --type") + , ("M4-r", spawn "exe=$(yeganesh -x) && eval \"exec $exe\"") + -- , ("M4-r", io (readProcess "yeganesh" ["-x"] "" >>= putStrLn ) ) + , ("", spawn "pactl -- set-sink-volume 0 +4%") + , ("", spawn "pactl -- set-sink-volume 0 -4%") + , ("", gridselectWorkspace myWSConfig W.view) + + , ("M4-a", focusUrgent) + , ("M4-S-r", renameWorkspace defaultXPConfig) + , ("M4-S-a", addWorkspacePrompt defaultXPConfig) + , ("M4-S-", removeEmptyWorkspace) + , ("M4-S-c", kill1) + , ("M4-", toggleWS) + , ("M4-S-", spawn myTerm) + , ("M4-x", floatNext True >> spawn myTerm) + , ("M4-f", floatNext True) + , ("M4-b", sendMessage ToggleStruts) + + , ("M4-v", withWorkspace myXPConfig (windows . W.view)) + , ("M4-S-v", withWorkspace myXPConfig (windows . W.shift)) + , ("M4-C-v", withWorkspace myXPConfig (windows . copy)) + + -- , (_4 , xK_q ) & \k -> (k, goToSelected myCNConfig { gs_navigate = makeGSNav k } ) + -- , (_4S, xK_q ) & \k -> (k, bringSelected myCNConfig { gs_navigate = makeGSNav k } ) + -- , (_4C, xK_q ) & \k -> (k, withSelectedWindow ( \a -> get >>= \s -> put s { windowset = copyWindow a (W.tag $ W.workspace $ W.current $ windowset s) (windowset s) } ) myCNConfig { gs_navigate = makeGSNav k } ) + + --, ("M4-", perWorkspaceAction workspaceConfigs) + , ("M4-S-q", return ()) + ] + +myGSConfig = defaultGSConfig + { gs_cellheight = 50 + , gs_cellpadding = 2 + , gs_navigate = navNSearch + , gs_font = myFont + } + +myXPConfig :: XPConfig +myXPConfig = defaultXPConfig + { autoComplete = Just 5000 + } + +myWSConfig = myGSConfig + { gs_cellwidth = 50 + } + +pagerConfig :: PagerConfig +pagerConfig = defaultPagerConfig + { pc_font = myFont + , pc_cellwidth = 64 + --, pc_cellheight = 36 -- TODO automatically keep screen aspect + --, pc_borderwidth = 1 + --, pc_matchcolor = "#f0b000" + , pc_matchmethod = MatchPrefix + --, pc_colors = pagerWorkspaceColors + , pc_windowColors = windowColors + } + where + windowColors _ _ _ True _ = ("#ef4242","#ff2323") + windowColors wsf m c u wf = do + let def = defaultWindowColors wsf m c u wf + if m == False && wf == True + then ("#402020", snd def) + else def + +wGSConfig :: GSConfig Window +wGSConfig = defaultGSConfig + { gs_cellheight = 20 + , gs_cellwidth = 192 + , gs_cellpadding = 5 + , gs_font = myFont + , gs_navigate = navNSearch + } + + +(&) :: a -> (a -> c) -> c +(&) = flip ($) + +allWorkspaceNames :: W.StackSet i l a sid sd -> X [i] +allWorkspaceNames ws = + return $ map W.tag (W.hidden ws) ++ [W.tag $ W.workspace $ W.current ws] diff --git a/lass/5pkgs/xmonad-lass/Makefile b/lass/5pkgs/xmonad-lass/Makefile new file mode 100644 index 00000000..cbb0776e --- /dev/null +++ b/lass/5pkgs/xmonad-lass/Makefile @@ -0,0 +1,6 @@ +.PHONY: ghci +ghci: shell.nix + nix-shell --command 'exec ghci -Wall' + +shell.nix: xmonad.cabal + cabal2nix --shell . > $@ diff --git a/lass/5pkgs/xmonad-lass/Util/PerWorkspaceConfig.hs b/lass/5pkgs/xmonad-lass/Util/PerWorkspaceConfig.hs new file mode 100644 index 00000000..bba7c8c6 --- /dev/null +++ b/lass/5pkgs/xmonad-lass/Util/PerWorkspaceConfig.hs @@ -0,0 +1,52 @@ +module Util.PerWorkspaceConfig + ( WorkspaceConfig (..) + , WorkspaceConfigs + , switchToWorkspace + , defaultWorkspaceConfig + , perWorkspaceAction + , perWorkspaceTermAction +-- , myLayoutHack + ) +where + +import XMonad +import XMonad.Core (LayoutClass) +import Control.Monad (when) + +import qualified Data.Map as M +import qualified XMonad.StackSet as W + +data WorkspaceConfig l = + WorkspaceConfig + { switchAction :: X () + , startAction :: X () + , keyAction :: X () + , termAction :: X () + } + +type WorkspaceConfigs l = M.Map WorkspaceId (WorkspaceConfig l) + +defaultWorkspaceConfig = WorkspaceConfig + { switchAction = return () + , startAction = return () + , keyAction = return () + , termAction = spawn "urxvtc" + } + +whenLookup wsId cfg a = + when (M.member wsId cfg) (a $ cfg M.! wsId) + +switchToWorkspace :: WorkspaceConfigs l -> WorkspaceId -> X () +switchToWorkspace cfg wsId = do + windows $ W.greedyView wsId + wins <- gets (W.integrate' . W.stack . W.workspace . W.current . windowset) + when (null wins) $ whenLookup wsId cfg startAction + whenLookup wsId cfg switchAction + +perWorkspaceAction :: WorkspaceConfigs l -> X () +perWorkspaceAction cfg = withWindowSet $ \s -> whenLookup (W.currentTag s) cfg keyAction + +perWorkspaceTermAction :: WorkspaceConfigs l -> X () +perWorkspaceTermAction cfg = withWindowSet $ \s -> case M.lookup (W.currentTag s) cfg of + Just x -> termAction x + _ -> termAction defaultWorkspaceConfig diff --git a/lass/5pkgs/xmonad-lass/xmonad.cabal b/lass/5pkgs/xmonad-lass/xmonad.cabal new file mode 100644 index 00000000..37809b59 --- /dev/null +++ b/lass/5pkgs/xmonad-lass/xmonad.cabal @@ -0,0 +1,17 @@ +Author: lass +Build-Type: Simple +Cabal-Version: >= 1.2 +License: MIT +Name: xmonad-lass +Version: 0 + +Executable xmonad + Build-Depends: + base, + containers, + unix, + xmonad, + xmonad-contrib, + xmonad-stockholm + GHC-Options: -Wall -O3 -threaded -rtsopts + Main-Is: Main.hs -- cgit v1.2.3