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
|
|
|
|
2020-04-01 20:17:47 -04:00
|
|
|
import System.IO.Streams.Internal as S (read)
|
|
|
|
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
|
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
|
|
|
|
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
|
2020-03-22 23:20:10 -04:00
|
|
|
runPowermon :: IO ()
|
|
|
|
runPowermon = do
|
|
|
|
-- TODO barf when the socket doesn't exist
|
|
|
|
Connection { source = s } <- connect "/var/run/acpid.socket"
|
|
|
|
forever $ readStream s
|
|
|
|
where
|
|
|
|
readStream s = do
|
|
|
|
out <- S.read s
|
|
|
|
mapM_ sendACPIEvent $ parseLine =<< out
|
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)
|
2020-03-28 18:38:38 -04:00
|
|
|
handleACPI :: String -> X ()
|
|
|
|
handleACPI tag = do
|
|
|
|
let acpiTag = toEnum <$> readMaybe tag :: Maybe ACPIEvent
|
|
|
|
forM_ acpiTag $ \case
|
|
|
|
Power -> runPowerPrompt
|
|
|
|
Sleep -> runSuspendPrompt
|
|
|
|
LidClose -> do
|
|
|
|
status <- io isDischarging
|
|
|
|
forM_ status $ \s -> runScreenLock >> when s runSuspend
|