xmonad-contrib/XMonad/Util/SpawnOnce.hs
Joan Milev f732082fdc Remove all derivations of Typeable
Typeable has been automatically derived for every type since GHC 7.10,
so remove these obsolete derivations.  This also allows us to get rid of
the `DeriveDataTypeable` pragma quite naturally.

Related: https://github.com/xmonad/xmonad/pull/299 (xmonad/xmonad@9e5b16ed8a)
Related: bd5b969d9ba24236c0d5ef521c0397390dbc4b37
Fixes: https://github.com/xmonad/xmonad-contrib/issues/548
2021-06-18 14:10:23 +02:00

59 lines
1.9 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Util.SpawnOnce
-- Copyright : (c) Spencer Janssen 2009
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : spencerjanssen@gmail.com
-- Stability : unstable
-- Portability : not portable
--
-- A module for spawning a command once, and only once. Useful to start
-- status bars and make session settings inside startupHook.
--
-----------------------------------------------------------------------------
module XMonad.Util.SpawnOnce (spawnOnce, spawnOnOnce, spawnNOnOnce, spawnAndDoOnce) where
import XMonad
import XMonad.Actions.SpawnOn
import Data.Set as Set
import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Prelude
newtype SpawnOnce = SpawnOnce { unspawnOnce :: Set String }
deriving (Read, Show)
instance ExtensionClass SpawnOnce where
initialValue = SpawnOnce Set.empty
extensionType = PersistentExtension
doOnce :: (String -> X ()) -> String -> X ()
doOnce f s = do
b <- XS.gets (Set.member s . unspawnOnce)
unless b $ do
f s
XS.modify (SpawnOnce . Set.insert s . unspawnOnce)
-- | The first time 'spawnOnce' is executed on a particular command,
-- that command is executed. Subsequent invocations for a command do
-- nothing.
spawnOnce :: String -> X ()
spawnOnce = doOnce spawn
-- | Like spawnOnce but launches the application on the given workspace.
spawnOnOnce :: WorkspaceId -> String -> X ()
spawnOnOnce ws = doOnce (spawnOn ws)
-- | Lanch the given application n times on the specified
-- workspace. Subsequent attempts to spawn this application will be
-- ignored.
spawnNOnOnce :: Int -> WorkspaceId -> String -> X ()
spawnNOnOnce n ws = doOnce (replicateM_ n . spawnOn ws)
-- | Spawn the application once and apply the manage hook. Subsequent
-- attempts to spawn this application will be ignored.
spawnAndDoOnce :: ManageHook -> String -> X ()
spawnAndDoOnce mh = doOnce (spawnAndDo mh)