module XMonad.Util.NamedScratchpad (
  
  
  NamedScratchpad(..),
  scratchpadWorkspaceTag,
  nonFloating,
  defaultFloating,
  customFloating,
  NamedScratchpads,
  namedScratchpadAction,
  spawnHereNamedScratchpadAction,
  customRunNamedScratchpadAction,
  allNamedScratchpadAction,
  namedScratchpadManageHook,
  namedScratchpadFilterOutWorkspace,
  namedScratchpadFilterOutWorkspacePP,
  nsHideOnFocusLoss,
  ) where
import XMonad
import XMonad.Actions.DynamicWorkspaces (addHiddenWorkspace)
import XMonad.Actions.SpawnOn (spawnHere)
import XMonad.Hooks.StatusBar.PP (PP, ppSort)
import XMonad.Hooks.ManageHelpers (doRectFloat)
import XMonad.Hooks.RefocusLast (withRecentsIn)
import XMonad.Prelude (filterM, find, unless, when)
import qualified Data.List.NonEmpty as NE
import qualified XMonad.StackSet as W
data NamedScratchpad = NS { NamedScratchpad -> String
name   :: String      
                          , NamedScratchpad -> String
cmd    :: String      
                          , NamedScratchpad -> Query Bool
query  :: Query Bool  
                          , NamedScratchpad -> Query (Endo WindowSet)
hook   :: ManageHook  
                          }
nonFloating :: ManageHook
nonFloating :: Query (Endo WindowSet)
nonFloating = Query (Endo WindowSet)
forall m. Monoid m => m
idHook
defaultFloating :: ManageHook
defaultFloating :: Query (Endo WindowSet)
defaultFloating = Query (Endo WindowSet)
doFloat
customFloating :: W.RationalRect -> ManageHook
customFloating :: RationalRect -> Query (Endo WindowSet)
customFloating = RationalRect -> Query (Endo WindowSet)
doRectFloat
type NamedScratchpads = [NamedScratchpad]
findByName :: NamedScratchpads -> String -> Maybe NamedScratchpad
findByName :: NamedScratchpads -> String -> Maybe NamedScratchpad
findByName NamedScratchpads
c String
s = (NamedScratchpad -> Bool)
-> NamedScratchpads -> Maybe NamedScratchpad
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
==) (String -> Bool)
-> (NamedScratchpad -> String) -> NamedScratchpad -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NamedScratchpad -> String
name) NamedScratchpads
c
runApplication :: NamedScratchpad -> X ()
runApplication :: NamedScratchpad -> X ()
runApplication = String -> X ()
forall (m :: * -> *). MonadIO m => String -> m ()
spawn (String -> X ())
-> (NamedScratchpad -> String) -> NamedScratchpad -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NamedScratchpad -> String
cmd
runApplicationHere :: NamedScratchpad -> X ()
runApplicationHere :: NamedScratchpad -> X ()
runApplicationHere = String -> X ()
spawnHere (String -> X ())
-> (NamedScratchpad -> String) -> NamedScratchpad -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NamedScratchpad -> String
cmd
namedScratchpadAction :: NamedScratchpads 
                      -> String           
                      -> X ()
namedScratchpadAction :: NamedScratchpads -> String -> X ()
namedScratchpadAction = (NamedScratchpad -> X ()) -> NamedScratchpads -> String -> X ()
customRunNamedScratchpadAction NamedScratchpad -> X ()
runApplication
spawnHereNamedScratchpadAction :: NamedScratchpads           
                               -> String                     
                               -> X ()
spawnHereNamedScratchpadAction :: NamedScratchpads -> String -> X ()
spawnHereNamedScratchpadAction = (NamedScratchpad -> X ()) -> NamedScratchpads -> String -> X ()
customRunNamedScratchpadAction NamedScratchpad -> X ()
runApplicationHere
customRunNamedScratchpadAction :: (NamedScratchpad -> X ())  
                               -> NamedScratchpads           
                               -> String                     
                               -> X ()
customRunNamedScratchpadAction :: (NamedScratchpad -> X ()) -> NamedScratchpads -> String -> X ()
customRunNamedScratchpadAction = ((Window -> X ()) -> NonEmpty Window -> X ())
-> (NamedScratchpad -> X ()) -> NamedScratchpads -> String -> X ()
someNamedScratchpadAction (\Window -> X ()
f NonEmpty Window
ws -> Window -> X ()
f (Window -> X ()) -> Window -> X ()
forall a b. (a -> b) -> a -> b
$ NonEmpty Window -> Window
forall a. NonEmpty a -> a
NE.head NonEmpty Window
ws)
allNamedScratchpadAction :: NamedScratchpads
                         -> String
                         -> X ()
allNamedScratchpadAction :: NamedScratchpads -> String -> X ()
allNamedScratchpadAction = ((Window -> X ()) -> NonEmpty Window -> X ())
-> (NamedScratchpad -> X ()) -> NamedScratchpads -> String -> X ()
someNamedScratchpadAction (Window -> X ()) -> NonEmpty Window -> X ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ NamedScratchpad -> X ()
runApplication
nsHideOnFocusLoss :: NamedScratchpads -> X ()
nsHideOnFocusLoss :: NamedScratchpads -> X ()
nsHideOnFocusLoss NamedScratchpads
scratches = (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
winSet -> do
    let cur :: String
cur = WindowSet -> String
forall i l a s sd. StackSet i l a s sd -> i
W.currentTag WindowSet
winSet
    String -> () -> (Window -> Window -> X ()) -> X ()
forall a. String -> a -> (Window -> Window -> X a) -> X a
withRecentsIn String
cur () ((Window -> Window -> X ()) -> X ())
-> (Window -> Window -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Window
lastFocus Window
_ ->
        Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Window
lastFocus Window -> [Window] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` WindowSet -> [Window]
forall i l a s sd. StackSet i l a s sd -> [a]
W.index WindowSet
winSet Bool -> Bool -> Bool
&& String
cur String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
scratchpadWorkspaceTag) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$
            X Bool -> X () -> X ()
whenX (Window -> X Bool
isNS Window
lastFocus) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$
                [WindowSpace] -> ((Window -> X ()) -> X ()) -> X ()
shiftToNSP (WindowSet -> [WindowSpace]
forall i l a s sd. StackSet i l a s sd -> [Workspace i l a]
W.workspaces WindowSet
winSet) ((Window -> X ()) -> Window -> X ()
forall a b. (a -> b) -> a -> b
$ Window
lastFocus)
  where
    isNS :: Window -> X Bool
    isNS :: Window -> X Bool
isNS Window
w = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Bool] -> Bool) -> X [Bool] -> X Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (NamedScratchpad -> X Bool) -> NamedScratchpads -> X [Bool]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Query Bool -> Window -> X Bool
forall a. Query a -> Window -> X a
`runQuery` Window
w) (Query Bool -> X Bool)
-> (NamedScratchpad -> Query Bool) -> NamedScratchpad -> X Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NamedScratchpad -> Query Bool
query) NamedScratchpads
scratches
someNamedScratchpadAction :: ((Window -> X ()) -> NE.NonEmpty Window -> X ())
                          -> (NamedScratchpad -> X ())
                          -> NamedScratchpads
                          -> String
                          -> X ()
someNamedScratchpadAction :: ((Window -> X ()) -> NonEmpty Window -> X ())
-> (NamedScratchpad -> X ()) -> NamedScratchpads -> String -> X ()
someNamedScratchpadAction (Window -> X ()) -> NonEmpty Window -> X ()
f NamedScratchpad -> X ()
runApp NamedScratchpads
scratchpadConfig String
scratchpadName =
    case NamedScratchpads -> String -> Maybe NamedScratchpad
findByName NamedScratchpads
scratchpadConfig String
scratchpadName of
        Just NamedScratchpad
conf -> (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
winSet -> do
            let focusedWspWindows :: [Window]
focusedWspWindows = [Window]
-> (Stack Window -> [Window]) -> Maybe (Stack Window) -> [Window]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Stack Window -> [Window]
forall a. Stack a -> [a]
W.integrate (WindowSpace -> Maybe (Stack Window)
forall i l a. Workspace i l a -> Maybe (Stack a)
W.stack (WindowSpace -> Maybe (Stack Window))
-> (WindowSet -> WindowSpace) -> WindowSet -> Maybe (Stack Window)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen String (Layout Window) Window ScreenId ScreenDetail
-> WindowSpace
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
W.workspace (Screen String (Layout Window) Window ScreenId ScreenDetail
 -> WindowSpace)
-> (WindowSet
    -> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> WindowSet
-> WindowSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
W.current (WindowSet -> Maybe (Stack Window))
-> WindowSet -> Maybe (Stack Window)
forall a b. (a -> b) -> a -> b
$ WindowSet
winSet)
                allWindows :: [Window]
allWindows        = WindowSet -> [Window]
forall a i l s sd. Eq a => StackSet i l a s sd -> [a]
W.allWindows WindowSet
winSet
            [Window]
matchingOnCurrent <- (Window -> X Bool) -> [Window] -> X [Window]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (Query Bool -> Window -> X Bool
forall a. Query a -> Window -> X a
runQuery (NamedScratchpad -> Query Bool
query NamedScratchpad
conf)) [Window]
focusedWspWindows
            [Window]
matchingOnAll     <- (Window -> X Bool) -> [Window] -> X [Window]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (Query Bool -> Window -> X Bool
forall a. Query a -> Window -> X a
runQuery (NamedScratchpad -> Query Bool
query NamedScratchpad
conf)) [Window]
allWindows
            case [Window] -> Maybe (NonEmpty Window)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty [Window]
matchingOnCurrent of
                
                Maybe (NonEmpty Window)
Nothing -> case [Window] -> Maybe (NonEmpty Window)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty [Window]
matchingOnAll of
                    Maybe (NonEmpty Window)
Nothing   -> NamedScratchpad -> X ()
runApp NamedScratchpad
conf
                    Just NonEmpty Window
wins -> (Window -> X ()) -> NonEmpty Window -> X ()
f ((WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Window -> WindowSet -> WindowSet) -> Window -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Window -> WindowSet -> WindowSet
forall a s i l sd.
(Ord a, Eq s, Eq i) =>
i -> a -> StackSet i l a s sd -> StackSet i l a s sd
W.shiftWin (WindowSet -> String
forall i l a s sd. StackSet i l a s sd -> i
W.currentTag WindowSet
winSet)) NonEmpty Window
wins
                
                Just NonEmpty Window
wins -> [WindowSpace] -> ((Window -> X ()) -> X ()) -> X ()
shiftToNSP (WindowSet -> [WindowSpace]
forall i l a s sd. StackSet i l a s sd -> [Workspace i l a]
W.workspaces WindowSet
winSet) ((Window -> X ()) -> NonEmpty Window -> X ()
`f` NonEmpty Window
wins)
        Maybe NamedScratchpad
Nothing -> () -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
scratchpadWorkspaceTag :: String
scratchpadWorkspaceTag :: String
scratchpadWorkspaceTag = String
"NSP"
namedScratchpadManageHook :: NamedScratchpads 
                          -> ManageHook
namedScratchpadManageHook :: NamedScratchpads -> Query (Endo WindowSet)
namedScratchpadManageHook = [Query (Endo WindowSet)] -> Query (Endo WindowSet)
forall m. Monoid m => [m] -> m
composeAll ([Query (Endo WindowSet)] -> Query (Endo WindowSet))
-> (NamedScratchpads -> [Query (Endo WindowSet)])
-> NamedScratchpads
-> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NamedScratchpad -> Query (Endo WindowSet))
-> NamedScratchpads -> [Query (Endo WindowSet)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\NamedScratchpad
c -> NamedScratchpad -> Query Bool
query NamedScratchpad
c Query Bool -> Query (Endo WindowSet) -> Query (Endo WindowSet)
forall (m :: * -> *) a. (Monad m, Monoid a) => m Bool -> m a -> m a
--> NamedScratchpad -> Query (Endo WindowSet)
hook NamedScratchpad
c)
shiftToNSP :: [WindowSpace] -> ((Window -> X ()) -> X ()) -> X ()
shiftToNSP :: [WindowSpace] -> ((Window -> X ()) -> X ()) -> X ()
shiftToNSP [WindowSpace]
ws (Window -> X ()) -> X ()
f = do
    Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((WindowSpace -> Bool) -> [WindowSpace] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((String
scratchpadWorkspaceTag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
==) (String -> Bool) -> (WindowSpace -> String) -> WindowSpace -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSpace -> String
forall i l a. Workspace i l a -> i
W.tag) [WindowSpace]
ws) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$
        String -> X ()
addHiddenWorkspace String
scratchpadWorkspaceTag
    (Window -> X ()) -> X ()
f ((WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Window -> WindowSet -> WindowSet) -> Window -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Window -> WindowSet -> WindowSet
forall a s i l sd.
(Ord a, Eq s, Eq i) =>
i -> a -> StackSet i l a s sd -> StackSet i l a s sd
W.shiftWin String
scratchpadWorkspaceTag)
namedScratchpadFilterOutWorkspace :: [WindowSpace] -> [WindowSpace]
namedScratchpadFilterOutWorkspace :: [WindowSpace] -> [WindowSpace]
namedScratchpadFilterOutWorkspace = (WindowSpace -> Bool) -> [WindowSpace] -> [WindowSpace]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(W.Workspace String
tag Layout Window
_ Maybe (Stack Window)
_) -> String
tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
scratchpadWorkspaceTag)
{-# DEPRECATED namedScratchpadFilterOutWorkspace "Use XMonad.Util.WorkspaceCompare.filterOutWs [scratchpadWorkspaceTag] instead" #-}
namedScratchpadFilterOutWorkspacePP :: PP -> PP
namedScratchpadFilterOutWorkspacePP :: PP -> PP
namedScratchpadFilterOutWorkspacePP PP
pp = PP
pp {
  ppSort :: X ([WindowSpace] -> [WindowSpace])
ppSort = (([WindowSpace] -> [WindowSpace])
 -> [WindowSpace] -> [WindowSpace])
-> X ([WindowSpace] -> [WindowSpace])
-> X ([WindowSpace] -> [WindowSpace])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([WindowSpace] -> [WindowSpace])
-> ([WindowSpace] -> [WindowSpace])
-> [WindowSpace]
-> [WindowSpace]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [WindowSpace] -> [WindowSpace]
namedScratchpadFilterOutWorkspace) (PP -> X ([WindowSpace] -> [WindowSpace])
ppSort PP
pp)
  }
{-# DEPRECATED namedScratchpadFilterOutWorkspacePP "Use XMonad.Hooks.StatusBar.PP.filterOutWsPP [scratchpadWorkspaceTag] instead" #-}