{-# LANGUAGE LambdaCase #-}
module XMonad.Actions.SpawnOn (
Spawner,
manageSpawn,
manageSpawnWithGC,
spawnHere,
spawnOn,
spawnAndDo,
shellPromptHere,
shellPromptOn
) where
import System.Posix.Types (ProcessID)
import XMonad
import XMonad.Prelude
import qualified XMonad.StackSet as W
import XMonad.Hooks.ManageHelpers
import XMonad.Prompt
import XMonad.Prompt.Shell
import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Util.Process (getPPIDChain)
newtype Spawner = Spawner {Spawner -> [(ProcessID, Query (Endo WindowSet))]
pidsRef :: [(ProcessID, ManageHook)]}
instance ExtensionClass Spawner where
initialValue :: Spawner
initialValue = [(ProcessID, Query (Endo WindowSet))] -> Spawner
Spawner []
modifySpawner :: ([(ProcessID, ManageHook)] -> [(ProcessID, ManageHook)]) -> X ()
modifySpawner :: ([(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))])
-> X ()
modifySpawner [(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))]
f = (Spawner -> Spawner) -> X ()
forall a (m :: * -> *).
(ExtensionClass a, XLike m) =>
(a -> a) -> m ()
XS.modify ([(ProcessID, Query (Endo WindowSet))] -> Spawner
Spawner ([(ProcessID, Query (Endo WindowSet))] -> Spawner)
-> (Spawner -> [(ProcessID, Query (Endo WindowSet))])
-> Spawner
-> Spawner
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))]
f ([(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))])
-> (Spawner -> [(ProcessID, Query (Endo WindowSet))])
-> Spawner
-> [(ProcessID, Query (Endo WindowSet))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Spawner -> [(ProcessID, Query (Endo WindowSet))]
pidsRef)
modifySpawnerM :: ([(ProcessID, ManageHook)] -> X [(ProcessID, ManageHook)]) -> X ()
modifySpawnerM :: ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> X ()
modifySpawnerM [(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))]
f = (Spawner -> X Spawner) -> X ()
forall a (m :: * -> *).
(ExtensionClass a, XLike m) =>
(a -> m a) -> m ()
XS.modifyM (([(ProcessID, Query (Endo WindowSet))] -> Spawner)
-> X [(ProcessID, Query (Endo WindowSet))] -> X Spawner
forall a b. (a -> b) -> X a -> X b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(ProcessID, Query (Endo WindowSet))] -> Spawner
Spawner (X [(ProcessID, Query (Endo WindowSet))] -> X Spawner)
-> (Spawner -> X [(ProcessID, Query (Endo WindowSet))])
-> Spawner
-> X Spawner
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))]
f ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> (Spawner -> [(ProcessID, Query (Endo WindowSet))])
-> Spawner
-> X [(ProcessID, Query (Endo WindowSet))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Spawner -> [(ProcessID, Query (Endo WindowSet))]
pidsRef)
manageSpawn :: ManageHook
manageSpawn :: Query (Endo WindowSet)
manageSpawn = ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> Query (Endo WindowSet)
manageSpawnWithGC ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))]
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> ([(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))])
-> [(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> [(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))]
forall a. Int -> [a] -> [a]
take Int
20)
manageSpawnWithGC :: ([(ProcessID, ManageHook)] -> X [(ProcessID, ManageHook)])
-> ManageHook
manageSpawnWithGC :: ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> Query (Endo WindowSet)
manageSpawnWithGC [(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))]
garbageCollect = Query (Maybe ProcessID)
pid Query (Maybe ProcessID)
-> (Maybe ProcessID -> Query (Endo WindowSet))
-> Query (Endo WindowSet)
forall a b. Query a -> (a -> Query b) -> Query b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe ProcessID
Nothing -> Query (Endo WindowSet)
forall a. Monoid a => a
mempty
Just ProcessID
p -> do
Spawner [(ProcessID, Query (Endo WindowSet))]
pids <- X Spawner -> Query Spawner
forall a. X a -> Query a
liftX X Spawner
forall a (m :: * -> *). (ExtensionClass a, XLike m) => m a
XS.get
[ProcessID]
ppid_chain <- IO [ProcessID] -> Query [ProcessID]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO [ProcessID] -> Query [ProcessID])
-> IO [ProcessID] -> Query [ProcessID]
forall a b. (a -> b) -> a -> b
$ ProcessID -> IO [ProcessID]
getPPIDChain ProcessID
p
case (ProcessID -> Maybe (Query (Endo WindowSet)))
-> [ProcessID] -> [Query (Endo WindowSet)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ProcessID
-> [(ProcessID, Query (Endo WindowSet))]
-> Maybe (Query (Endo WindowSet))
forall a b. Eq a => a -> [(a, b)] -> Maybe b
`lookup` [(ProcessID, Query (Endo WindowSet))]
pids) [ProcessID]
ppid_chain of
[] -> Query (Endo WindowSet)
forall a. Monoid a => a
mempty
Query (Endo WindowSet)
mh : [Query (Endo WindowSet)]
_ -> X () -> Query ()
forall a. X a -> Query a
liftX (ProcessID -> X ()
gc ProcessID
p) Query () -> Query (Endo WindowSet) -> Query (Endo WindowSet)
forall a b. Query a -> Query b -> Query b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Query (Endo WindowSet)
mh
where
gc :: ProcessID -> X ()
gc ProcessID
p = ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> X ()
modifySpawnerM (([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> X ())
-> ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> X ()
forall a b. (a -> b) -> a -> b
$ [(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))]
garbageCollect ([(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))])
-> ([(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))])
-> [(ProcessID, Query (Endo WindowSet))]
-> X [(ProcessID, Query (Endo WindowSet))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ProcessID, Query (Endo WindowSet)) -> Bool)
-> [(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))]
forall a. (a -> Bool) -> [a] -> [a]
filter ((ProcessID -> ProcessID -> Bool
forall a. Eq a => a -> a -> Bool
/= ProcessID
p) (ProcessID -> Bool)
-> ((ProcessID, Query (Endo WindowSet)) -> ProcessID)
-> (ProcessID, Query (Endo WindowSet))
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProcessID, Query (Endo WindowSet)) -> ProcessID
forall a b. (a, b) -> a
fst)
mkPrompt :: (String -> X ()) -> XPConfig -> X ()
mkPrompt :: (String -> X ()) -> XPConfig -> X ()
mkPrompt String -> X ()
cb XPConfig
c = do
[String]
cmds <- IO [String] -> X [String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io IO [String]
getCommands
Shell -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
forall p.
XPrompt p =>
p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
mkXPrompt Shell
Shell XPConfig
c ([String] -> Predicate -> ComplFunction
getShellCompl [String]
cmds (Predicate -> ComplFunction) -> Predicate -> ComplFunction
forall a b. (a -> b) -> a -> b
$ XPConfig -> Predicate
searchPredicate XPConfig
c) String -> X ()
cb
shellPromptHere :: XPConfig -> X ()
shellPromptHere :: XPConfig -> X ()
shellPromptHere = (String -> X ()) -> XPConfig -> X ()
mkPrompt String -> X ()
spawnHere
shellPromptOn :: WorkspaceId -> XPConfig -> X ()
shellPromptOn :: String -> XPConfig -> X ()
shellPromptOn String
ws = (String -> X ()) -> XPConfig -> X ()
mkPrompt (String -> String -> X ()
spawnOn String
ws)
spawnHere :: String -> X ()
spawnHere :: String -> X ()
spawnHere String
cmd = (WindowSet -> X ()) -> X ()
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X ()) -> X ()) -> (WindowSet -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \WindowSet
ws -> String -> String -> X ()
spawnOn (WindowSet -> String
forall i l a s sd. StackSet i l a s sd -> i
W.currentTag WindowSet
ws) String
cmd
spawnOn :: WorkspaceId -> String -> X ()
spawnOn :: String -> String -> X ()
spawnOn String
ws = Query (Endo WindowSet) -> String -> X ()
spawnAndDo (String -> Query (Endo WindowSet)
doShift String
ws)
spawnAndDo :: ManageHook -> String -> X ()
spawnAndDo :: Query (Endo WindowSet) -> String -> X ()
spawnAndDo Query (Endo WindowSet)
mh String
cmd = do
ProcessID
p <- String -> X ProcessID
forall (m :: * -> *). MonadIO m => String -> m ProcessID
spawnPID (String -> X ProcessID) -> String -> X ProcessID
forall a b. (a -> b) -> a -> b
$ String -> String
mangle String
cmd
([(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))])
-> X ()
modifySpawner ((ProcessID
p,Query (Endo WindowSet)
mh) (ProcessID, Query (Endo WindowSet))
-> [(ProcessID, Query (Endo WindowSet))]
-> [(ProcessID, Query (Endo WindowSet))]
forall a. a -> [a] -> [a]
:)
where
mangle :: String -> String
mangle String
xs | (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
metaChars) String
xs Bool -> Bool -> Bool
|| String
"exec" Predicate
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
xs = String
xs
| Bool
otherwise = String
"exec " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
xs
metaChars :: String
metaChars = String
"&|;"