Compare commits

...

3 Commits

  1. 4
      battery-monitor.sh
  2. 32
      xmonad.hs

@ -3,7 +3,7 @@ set -e
trap 'xmessage -nearmouse "WARNING: battery monitor died!"' EXIT
was_notified=0
while true; do
acpi_data=$(acpi -b)
acpi_data=$(acpi -b | grep -v 'rate information unavailable' | head -n1)
status=$(echo -n "$acpi_data" | awk -F'[,:%]' '{print $2}')
capacity=$(echo -n "$acpi_data" | awk -F'[,:%]' '{print $3}')
echo "Status: $status; Capacity: $capacity; was_notified: $was_notified"
@ -15,7 +15,7 @@ while true; do
was_notified=1
fi
if [[ "$status" =~ "Discharging" && "$capacity" -lt 10 ]]; then
bash -c 'echo "Battery critical, suspending"; acpi -b' | xmessage -nearmouse -file -&
echo -e "Battery critical, suspending\n$acpi_data" | xmessage -nearmouse -file -&
sleep 5
systemctl suspend
sleep 600 # Wait 10 minutes, so we only hibernate once

@ -1,5 +1,6 @@
import XMonad
import XMonad.Actions.CycleWS
import XMonad.Actions.Minimize(minimizeWindow, withLastMinimized, maximizeWindowAndFocus)
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
@ -9,13 +10,13 @@ import XMonad.Util.EZConfig
import XMonad.Util.Scratchpad
import XMonad.Config.Desktop
import XMonad.Config.Azerty
import XMonad.Layout.Fullscreen
import XMonad.Layout.NoBorders
import XMonad.Layout.Maximize
import XMonad.Layout.Tabbed
import XMonad.Layout.Minimize
import XMonad.Layout.Minimize(minimize)
import XMonad.Layout.BoringWindows
import XMonad.Layout.PerWorkspace
import XMonad.Layout.Fullscreen(fullscreenSupport)
import XMonad.Prompt
import XMonad.Prompt.Ssh
import System.IO
@ -23,13 +24,22 @@ import qualified Data.Map as M
import qualified XMonad.StackSet as W
import qualified Data.List as L
myLayout =
smartBorders
$ avoidStruts
$ boringWindows
$ minimize
$ maximizeWithPadding 0
$ onWorkspace "8:media" Full
$ onWorkspaces ["2:com", "9:div"] simpleTabbed
$ (Tall 1 0.03 0.5 ||| Full ||| simpleTabbed )
baseConfig = desktopConfig
{ modMask = mod5Mask -- AltGr
, startupHook = startupHook desktopConfig >> setWMName "LG3D"
, terminal = "mate-terminal.wrapper"
, workspaces = ["1:web", "2:com"] ++ map show [3..7] ++ ["8:media", "9:div"]
, layoutHook = smartBorders $ fullscreenFull $ avoidStruts $ boringWindows $ minimize $ maximizeWithPadding 0 $ onWorkspace "8:media" Full $ onWorkspaces ["2:com", "9:div"] simpleTabbed $ (Tall 1 0.03 0.5 ||| Full ||| simpleTabbed )
, handleEventHook = handleEventHook desktopConfig <+> fullscreenEventHook
, layoutHook = myLayout
}
`removeKeys`
[(m .|. modMask baseConfig , k)
@ -56,21 +66,23 @@ workspaceManageHook = composeAll [
,className =? "Screenlayout" --> doFloat
]
xmobarAction :: String -- action
xmobarActionWrapper :: String -- action
-> String -- output string
-> String
xmobarAction action = wrap t "</action>"
xmobarActionWrapper action = wrap t "</action>"
where t = concat ["<action=`", action, "`>"]
xmobarSwitchWs :: String -> String
xmobarSwitchWs wsName = xmobarAction action wsName
xmobarSwitchWs wsName = xmobarActionWrapper action wsName
where action = concat ["xdotool key ISO_Level3_Shift+F", workspace]
workspace = takeWhile (/=':') wsName -- Takes all chars until ':'
main = do
xmobar_proc <- spawnPipe "xmobar"
xmonad $ baseConfig
{ manageHook = (scratchpadManageHook $ W.RationalRect 0.0 0.0 1.0 0.5) <+> workspaceManageHook <+> fullscreenManageHook <+> manageDocks
xmonad
$ fullscreenSupport
$ baseConfig
{ manageHook = (scratchpadManageHook $ W.RationalRect 0.0 0.0 1.0 0.5) <+> workspaceManageHook <+> manageDocks
, logHook = dynamicLogWithPP xmobarPP
{ ppOutput = hPutStrLn xmobar_proc
, ppHidden = xmobarSwitchWs
@ -102,7 +114,7 @@ main = do
, ((modMask baseConfig, xK_s), sshPrompt baseXPConfig)
-- XMonad.Layout.Minimize
, ((modMask baseConfig, xK_c), withFocused minimizeWindow)
, ((modMask baseConfig, xK_g), sendMessage RestoreNextMinimizedWin)
, ((modMask baseConfig, xK_g), withLastMinimized maximizeWindowAndFocus)
-- XMonad.Layout.BoringWindows
, ((modMask baseConfig, xK_j), focusUp)
, ((modMask baseConfig, xK_k), focusDown)

Loading…
Cancel
Save