{-# LANGUAGE LambdaCase #-}
module XMonad.Actions.RepeatAction (
rememberAction,
rememberActions,
repeatLast,
) where
import XMonad
import qualified XMonad.Util.ExtensibleState as XS
newtype LastAction = LastAction { LastAction -> X ()
runLastAction :: X () }
instance ExtensionClass LastAction where
initialValue :: LastAction
initialValue = X () -> LastAction
LastAction (X () -> LastAction) -> X () -> LastAction
forall a b. (a -> b) -> a -> b
$ () -> X ()
forall a. a -> X a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
rememberAction :: X () -> X ()
rememberAction :: X () -> X ()
rememberAction X ()
x = X () -> X (Maybe ())
forall a. X a -> X (Maybe a)
userCode X ()
x X (Maybe ()) -> (Maybe () -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe ()
Nothing -> () -> X ()
forall a. a -> X a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just () -> LastAction -> X ()
forall a (m :: * -> *). (ExtensionClass a, XLike m) => a -> m ()
XS.put (X () -> LastAction
LastAction X ()
x)
rememberActions' :: [(a, X ())] -> [(a, X ())]
rememberActions' :: forall a. [(a, X ())] -> [(a, X ())]
rememberActions' = ((a, X ()) -> (a, X ())) -> [(a, X ())] -> [(a, X ())]
forall a b. (a -> b) -> [a] -> [b]
map ((X () -> X ()) -> (a, X ()) -> (a, X ())
forall a b. (a -> b) -> (a, a) -> (a, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap X () -> X ()
rememberAction)
infixl 4 `rememberActions`
rememberActions :: a -> [(a, X ())] -> [(a, X ())]
rememberActions :: forall a. a -> [(a, X ())] -> [(a, X ())]
rememberActions a
key [(a, X ())]
keyList = (a
key, X ()
repeatLast) (a, X ()) -> [(a, X ())] -> [(a, X ())]
forall a. a -> [a] -> [a]
: [(a, X ())] -> [(a, X ())]
forall a. [(a, X ())] -> [(a, X ())]
rememberActions' [(a, X ())]
keyList
repeatLast :: X ()
repeatLast :: X ()
repeatLast = X LastAction
forall a (m :: * -> *). (ExtensionClass a, XLike m) => m a
XS.get X LastAction -> (LastAction -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= LastAction -> X ()
runLastAction