summaryrefslogtreecommitdiffstats
path: root/XMonad/Operations.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Operations.hs')
-rw-r--r--XMonad/Operations.hs10
1 files changed, 7 insertions, 3 deletions
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index fe124f3..f4a6bed 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -68,7 +68,7 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
where i = W.tag $ W.workspace $ W.current ws
mh <- asks (manageHook . config)
- g <- fmap appEndo $ userCodeDef (Endo id) (runQuery mh w)
+ g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
windows (g . f)
-- | unmanage. A window no longer exists, remove it from the window
@@ -413,9 +413,13 @@ restart :: String -> Bool -> X ()
restart prog resume = do
broadcastMessage ReleaseResources
io . flush =<< asks display
- args <- if resume then gets (("--resume":) . return . showWs . windowset) else return []
+ let wsData = show . W.mapLayout show . windowset
+ maybeShow (t, Right (PersistentExtension ext)) = Just (t, show ext)
+ maybeShow (t, Left str) = Just (t, str)
+ maybeShow _ = Nothing
+ extState = return . show . catMaybes . map maybeShow . M.toList . extensibleState
+ args <- if resume then gets (\s -> "--resume":wsData s:extState s) else return []
catchIO (executeFile prog True args Nothing)
- where showWs = show . W.mapLayout show
------------------------------------------------------------------------
-- | Floating layer support