module TitleShellF where
import AllFudgets
titleShellF :: String -> F c d -> F (Either String c) d
titleShellF = forall {c} {d}.
(ShellF -> ShellF) -> String -> F c d -> F (Either String c) d
titleShellF' forall a. Customiser a
standard
titleShellF' :: (ShellF -> ShellF) -> String -> F c d -> F (Either String c) d
titleShellF' ShellF -> ShellF
pm String
title F c d
fud =
forall {a1} {b}. SP (Either a1 b) b
filterRightSP forall a b e. SP a b -> F e a -> F e b
>^^=< forall {c} {d}.
(ShellF -> ShellF)
-> String
-> F c d
-> F (Either (Either String Bool) c) (Either () d)
wmShellF' ShellF -> ShellF
pm' String
title F c d
fud forall c d e. F c d -> (e -> c) -> F e d
>=^< forall {t1} {a} {t2} {b}.
(t1 -> a) -> (t2 -> b) -> Either t1 t2 -> Either a b
mapEither forall a b. a -> Either a b
Left forall a. Customiser a
id
where
pm' :: ShellF -> ShellF
pm' = ShellF -> ShellF
pm forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe DeleteWindowAction -> ShellF -> ShellF
setDeleteWindowAction (forall a. a -> Maybe a
Just DeleteWindowAction
DeleteQuit)
wmShellF :: String -> F c d -> F (Either (Either String Bool) c) (Either () d)
wmShellF = forall {c} {d}.
(ShellF -> ShellF)
-> String
-> F c d
-> F (Either (Either String Bool) c) (Either () d)
wmShellF' forall a. Customiser a
standard
wmShellF' :: (ShellF -> ShellF)
-> String
-> F c d
-> F (Either (Either String Bool) c) (Either () d)
wmShellF' ShellF -> ShellF
pm0 String
title F c d
fud =
forall a b c d.
(ShellF -> ShellF) -> K a b -> F c d -> F (Either a c) (Either b d)
shellKF' ShellF -> ShellF
pm K (Either String Bool) ()
titleK0 F c d
fud
where pm :: ShellF -> ShellF
pm = Maybe DeleteWindowAction -> ShellF -> ShellF
setDeleteWindowAction forall a. Maybe a
Nothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShellF -> ShellF
pm0
action :: Maybe (K hi () -> K hi ())
action = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. a -> Maybe a
Just forall {hi}. K hi () -> K hi ()
reportK)
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {hi} {ho}. DeleteWindowAction -> K hi ho -> K hi ho
action')
((ShellF -> ShellF) -> Maybe (Maybe DeleteWindowAction)
getDeleteWindowActionMaybe' ShellF -> ShellF
pm0)
where
action' :: DeleteWindowAction -> K hi ho -> K hi ho
action' DeleteWindowAction
DeleteQuit = forall {p} {hi} {ho}. p -> K hi ho
exitK
action' DeleteWindowAction
DeleteUnmap = forall {i} {o}. K i o -> K i o
unmapWindowK
titleK0 :: K (Either String Bool) ()
titleK0 = forall {hi} {ho}. [KEvent hi] -> K hi ho -> K hi ho
startupK [forall a b. b -> Message a b
High (forall a b. a -> Either a b
Left String
title)] K (Either String Bool) ()
titleK
titleK :: K (Either String Bool) ()
titleK = forall {c}.
Maybe (K (Either String Bool) c -> K (Either String Bool) c)
-> K (Either String Bool) c
wmK forall {hi}. Maybe (K hi () -> K hi ())
action