xmonad-config/lib/XMonad/Internal/Concurrent/ACPIEvent.hs

114 lines
3.5 KiB
Haskell
Raw Normal View History

2020-03-28 18:38:38 -04:00
{-# LANGUAGE LambdaCase #-}
2020-03-22 23:20:10 -04:00
{-# LANGUAGE OverloadedStrings #-}
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Concurrent module to handle events from acpid
2020-04-01 20:17:47 -04:00
module XMonad.Internal.Concurrent.ACPIEvent
2020-04-01 22:06:00 -04:00
( runPowermon
2020-03-28 18:38:38 -04:00
, handleACPI
2020-03-22 23:20:10 -04:00
) where
2020-03-22 23:46:56 -04:00
import Control.Exception
import Control.Monad
2020-03-13 20:50:13 -04:00
2020-04-01 20:17:47 -04:00
import Data.ByteString hiding (readFile)
import Data.ByteString.Char8 as C hiding (readFile)
2020-03-22 23:46:56 -04:00
import Data.Connection
2020-03-22 23:20:10 -04:00
2020-04-01 20:17:47 -04:00
import Text.Read (readMaybe)
2020-03-22 23:20:10 -04:00
2021-11-07 20:16:53 -05:00
-- import System.Directory (doesPathExist)
2021-06-22 00:46:29 -04:00
import System.IO.Streams as S (read)
2020-04-01 20:17:47 -04:00
import System.IO.Streams.UnixSocket
2020-03-28 18:38:38 -04:00
import XMonad.Core
2020-04-01 20:17:47 -04:00
import XMonad.Internal.Command.Power
import XMonad.Internal.Concurrent.ClientMessage
import XMonad.Internal.Dependency
2020-03-28 18:38:38 -04:00
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Data structure to hold the ACPI events I care about
--
-- Enumerate so these can be converted to strings and back when sent in a
-- ClientMessage event to X
2020-03-22 23:20:10 -04:00
data ACPIEvent = Power
| Sleep
| LidClose
deriving (Eq)
instance Enum ACPIEvent where
toEnum 0 = Power
toEnum 1 = Sleep
toEnum 2 = LidClose
2020-03-22 23:46:56 -04:00
toEnum _ = errorWithoutStackTrace "ACPI.Enum.ACPIEvent.toEnum: bad argument"
2020-03-22 23:20:10 -04:00
fromEnum Power = 0
fromEnum Sleep = 1
fromEnum LidClose = 2
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Internal functions
2020-03-22 23:20:10 -04:00
2020-04-01 22:06:00 -04:00
-- | Convert a string to an ACPI event (this string is assumed to come from
-- the acpid socket)
2020-03-22 23:20:10 -04:00
parseLine :: ByteString -> Maybe ACPIEvent
parseLine line =
case splitLine line of
(_:"PBTN":_) -> Just Power
(_:"PWRF":_) -> Just Power
(_:"SLPB":_) -> Just Sleep
(_:"SBTN":_) -> Just Sleep
(_:"LID":"close":_) -> Just LidClose
_ -> Nothing
where
splitLine = C.words . C.reverse . C.dropWhile (== '\n') . C.reverse
2020-03-13 20:50:13 -04:00
2020-04-01 22:06:00 -04:00
-- | Send an ACPIEvent to the X server as a ClientMessage
sendACPIEvent :: ACPIEvent -> IO ()
sendACPIEvent = sendXMsg ACPI . show . fromEnum
2020-03-13 20:50:13 -04:00
isDischarging :: IO (Maybe Bool)
isDischarging = do
status <- try $ readFile "/sys/class/power_supply/BAT0/status"
:: IO (Either IOException String)
case status of
2020-03-22 23:20:10 -04:00
Left _ -> return Nothing
2020-03-13 20:50:13 -04:00
Right s -> return $ Just (s == "Discharging")
2020-03-22 23:20:10 -04:00
2021-06-22 00:46:29 -04:00
listenACPI :: IO ()
listenACPI = do
Connection { source = s } <- connect acpiPath
forever $ readStream s
where
readStream s = do
out <- S.read s
mapM_ sendACPIEvent $ parseLine =<< out
acpiPath :: FilePath
acpiPath = "/var/run/acpid.socket"
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Exported API
-- | Spawn a new thread that will listen for ACPI events on the acpid socket
-- and send ClientMessage events when it receives them
2021-11-20 01:15:04 -05:00
runPowermon :: FeatureIO
runPowermon = featureRun [pathR acpiPath] listenACPI
2020-03-28 18:38:38 -04:00
2020-04-01 22:06:00 -04:00
-- | Handle ClientMessage event containing and ACPI event (to be used in
-- Xmonad's event hook)
2021-11-19 22:42:19 -05:00
handleACPI :: X () -> String -> X ()
handleACPI lock tag = do
2020-03-28 18:38:38 -04:00
let acpiTag = toEnum <$> readMaybe tag :: Maybe ACPIEvent
forM_ acpiTag $ \case
2021-11-19 22:42:19 -05:00
Power -> runPowerPrompt lock
2020-03-28 18:38:38 -04:00
Sleep -> runSuspendPrompt
LidClose -> do
status <- io isDischarging
2021-06-22 00:46:29 -04:00
-- only run suspend if battery exists and is discharging
forM_ status $ flip when runSuspend
2021-11-19 22:42:19 -05:00
lock
2021-06-22 00:46:29 -04:00