mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
This fixes several issues related to parsing of parent PIDs: * A process with lines or spaces or parentheses in its process name would confuse the code in X.A.SpawnOn and possibly lead to a `Prelude.read: no parse` exception. * `X.H.WindowSwallowing.isChildOf` looked for the parent PID anywhere in the output of pstree, so single-digit parent PIDs would be considered as parents of any process with that digit anywhere in its chain of parent PIDs. (Note that apps in PID namespaces like in Flatpak often have single-digit PIDs.) * `pstree` is no longer required in `$PATH`. Fixes: https://github.com/xmonad/xmonad-contrib/issues/726
44 lines
1.5 KiB
Haskell
44 lines
1.5 KiB
Haskell
{-# LANGUAGE OverloadedStrings #-}
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
{-# LANGUAGE ViewPatterns #-}
|
|
|
|
-- |
|
|
-- Module : XMonad.Util.Process
|
|
-- Description : Utilities for unix processes.
|
|
-- Copyright : (c) 2022 Tomáš Janoušek <tomi@nomi.cz>
|
|
-- License : BSD3
|
|
-- Maintainer : Tomáš Janoušek <tomi@nomi.cz>
|
|
--
|
|
-- This module should not be directly used by users, it's just common code for
|
|
-- other modules.
|
|
--
|
|
module XMonad.Util.Process (
|
|
getPPIDOf,
|
|
getPPIDChain,
|
|
) where
|
|
|
|
import Control.Exception (SomeException, handle)
|
|
import System.Posix.Types (ProcessID)
|
|
import qualified Data.ByteString.Char8 as B
|
|
|
|
import XMonad.Prelude (fi)
|
|
|
|
-- | Get the parent process id (PPID) of a given process.
|
|
getPPIDOf :: ProcessID -> IO (Maybe ProcessID)
|
|
getPPIDOf pid =
|
|
handle
|
|
(\(_ :: SomeException) -> pure Nothing)
|
|
(parse <$> B.readFile ("/proc/" <> show pid <> "/stat"))
|
|
where
|
|
-- Parse PPID out of /proc/*/stat, being careful not to trip over
|
|
-- processes with names like ":-) 1 2 3 4 5 6".
|
|
-- Inspired by https://gitlab.com/procps-ng/procps/-/blob/bcce3e440a1e1ee130c7371251a39c031519336a/proc/readproc.c#L561
|
|
parse stat = case B.words $ snd $ B.spanEnd (/= ')') stat of
|
|
_ : (B.readInt -> Just (ppid, "")) : _ -> Just (fi ppid)
|
|
_ -> Nothing
|
|
|
|
-- | Get the chain of parent processes of a given pid. Starts with the given
|
|
-- pid and continues up until the parent of all.
|
|
getPPIDChain :: ProcessID -> IO [ProcessID]
|
|
getPPIDChain pid = (pid :) <$> (maybe (pure []) getPPIDChain =<< getPPIDOf pid)
|