{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
module Brick.Main
( App(..)
, defaultMain
, customMain
, customMainWithVty
, simpleMain
, resizeOrQuit
, simpleApp
, continueWithoutRedraw
, halt
, suspendAndResume
, suspendAndResume'
, makeVisible
, lookupViewport
, lookupExtent
, findClickedExtents
, clickedExtent
, getVtyHandle
, viewportScroll
, ViewportScroll
, vScrollBy
, vScrollPage
, vScrollToBeginning
, vScrollToEnd
, hScrollBy
, hScrollPage
, hScrollToBeginning
, hScrollToEnd
, setTop
, setLeft
, neverShowCursor
, showFirstCursor
, showCursorNamed
, invalidateCacheEntry
, invalidateCache
, renderFinal
, getRenderState
, resetRenderState
, renderWidget
)
where
import qualified Control.Exception as E
import Lens.Micro ((^.), (&), (.~), (%~), _1, _2)
import Control.Monad
import Control.Monad.State.Strict
import Control.Monad.Reader
import Control.Concurrent (forkIO, killThread)
import qualified Data.Foldable as F
import Data.List (find)
import Data.Maybe (listToMaybe)
import qualified Data.Map as M
import qualified Data.Set as S
import Graphics.Vty
( Vty
, Picture(..)
, Cursor(..)
, Event(..)
, update
, outputIface
, displayBounds
, shutdown
, nextEvent
, mkVty
, defaultConfig
, restoreInputState
, inputIface
)
import Graphics.Vty.Attributes (defAttr)
import Brick.BChan (BChan, newBChan, readBChan, readBChan2, writeBChan)
import Brick.Types.EventM
import Brick.Types.Internal
import Brick.Widgets.Internal
import Brick.AttrMap
data App s e n =
App { forall s e n. App s e n -> s -> [Widget n]
appDraw :: s -> [Widget n]
, forall s e n.
App s e n -> s -> [CursorLocation n] -> Maybe (CursorLocation n)
appChooseCursor :: s -> [CursorLocation n] -> Maybe (CursorLocation n)
, forall s e n. App s e n -> BrickEvent n e -> EventM n s ()
appHandleEvent :: BrickEvent n e -> EventM n s ()
, forall s e n. App s e n -> EventM n s ()
appStartEvent :: EventM n s ()
, forall s e n. App s e n -> s -> AttrMap
appAttrMap :: s -> AttrMap
}
defaultMain :: (Ord n)
=> App s e n
-> s
-> IO s
defaultMain :: forall n s e. Ord n => App s e n -> s -> IO s
defaultMain App s e n
app s
st = do
let builder :: IO Vty
builder = Config -> IO Vty
mkVty Config
defaultConfig
Vty
initialVty <- IO Vty
builder
forall n e s.
Ord n =>
Vty -> IO Vty -> Maybe (BChan e) -> App s e n -> s -> IO s
customMain Vty
initialVty IO Vty
builder forall a. Maybe a
Nothing App s e n
app s
st
simpleMain :: (Ord n)
=> Widget n
-> IO ()
simpleMain :: forall n. Ord n => Widget n -> IO ()
simpleMain Widget n
w = forall n s e. Ord n => App s e n -> s -> IO s
defaultMain (forall n s e. Widget n -> App s e n
simpleApp Widget n
w) ()
simpleApp :: Widget n -> App s e n
simpleApp :: forall n s e. Widget n -> App s e n
simpleApp Widget n
w =
App { appDraw :: s -> [Widget n]
appDraw = forall a b. a -> b -> a
const [Widget n
w]
, appHandleEvent :: BrickEvent n e -> EventM n s ()
appHandleEvent = forall n e s. BrickEvent n e -> EventM n s ()
resizeOrQuit
, appStartEvent :: EventM n s ()
appStartEvent = forall (m :: * -> *) a. Monad m => a -> m a
return ()
, appAttrMap :: s -> AttrMap
appAttrMap = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ Attr -> [(AttrName, Attr)] -> AttrMap
attrMap Attr
defAttr []
, appChooseCursor :: s -> [CursorLocation n] -> Maybe (CursorLocation n)
appChooseCursor = forall s n. s -> [CursorLocation n] -> Maybe (CursorLocation n)
neverShowCursor
}
resizeOrQuit :: BrickEvent n e -> EventM n s ()
resizeOrQuit :: forall n e s. BrickEvent n e -> EventM n s ()
resizeOrQuit (VtyEvent (EvResize Int
_ Int
_)) = forall (m :: * -> *) a. Monad m => a -> m a
return ()
resizeOrQuit BrickEvent n e
_ = forall n s. EventM n s ()
halt
readBrickEvent :: BChan (BrickEvent n e) -> BChan e -> IO (BrickEvent n e)
readBrickEvent :: forall n e.
BChan (BrickEvent n e) -> BChan e -> IO (BrickEvent n e)
readBrickEvent BChan (BrickEvent n e)
brickChan BChan e
userChan = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> a
id forall n e. e -> BrickEvent n e
AppEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. BChan a -> BChan b -> IO (Either a b)
readBChan2 BChan (BrickEvent n e)
brickChan BChan e
userChan
runWithVty :: (Ord n)
=> VtyContext
-> BChan (BrickEvent n e)
-> Maybe (BChan e)
-> App s e n
-> RenderState n
-> s
-> IO (s, VtyContext)
runWithVty :: forall n e s.
Ord n =>
VtyContext
-> BChan (BrickEvent n e)
-> Maybe (BChan e)
-> App s e n
-> RenderState n
-> s
-> IO (s, VtyContext)
runWithVty VtyContext
vtyCtx BChan (BrickEvent n e)
brickChan Maybe (BChan e)
mUserChan App s e n
app RenderState n
initialRS s
initialSt = do
let readEvent :: IO (BrickEvent n e)
readEvent = case Maybe (BChan e)
mUserChan of
Maybe (BChan e)
Nothing -> forall a. BChan a -> IO a
readBChan BChan (BrickEvent n e)
brickChan
Just BChan e
uc -> forall n e.
BChan (BrickEvent n e) -> BChan e -> IO (BrickEvent n e)
readBrickEvent BChan (BrickEvent n e)
brickChan BChan e
uc
runInner :: VtyContext
-> RenderState n -> [Extent n] -> Bool -> s -> IO (s, VtyContext)
runInner VtyContext
ctx RenderState n
rs [Extent n]
es Bool
draw s
st = do
let nextRS :: RenderState n
nextRS = if Bool
draw
then forall n. RenderState n -> RenderState n
resetRenderState RenderState n
rs
else RenderState n
rs
(s
nextSt, NextAction
result, RenderState n
newRS, [Extent n]
newExtents, VtyContext
newCtx) <- forall n e s.
Ord n =>
VtyContext
-> IO (BrickEvent n e)
-> App s e n
-> s
-> RenderState n
-> [Extent n]
-> Bool
-> IO (s, NextAction, RenderState n, [Extent n], VtyContext)
runVty VtyContext
ctx IO (BrickEvent n e)
readEvent App s e n
app s
st RenderState n
nextRS [Extent n]
es Bool
draw
case NextAction
result of
NextAction
Halt ->
forall (m :: * -> *) a. Monad m => a -> m a
return (s
nextSt, VtyContext
newCtx)
NextAction
Continue ->
VtyContext
-> RenderState n -> [Extent n] -> Bool -> s -> IO (s, VtyContext)
runInner VtyContext
newCtx RenderState n
newRS [Extent n]
newExtents Bool
True s
nextSt
NextAction
ContinueWithoutRedraw ->
VtyContext
-> RenderState n -> [Extent n] -> Bool -> s -> IO (s, VtyContext)
runInner VtyContext
newCtx RenderState n
newRS [Extent n]
newExtents Bool
False s
nextSt
VtyContext
-> RenderState n -> [Extent n] -> Bool -> s -> IO (s, VtyContext)
runInner VtyContext
vtyCtx RenderState n
initialRS forall a. Monoid a => a
mempty Bool
True s
initialSt
customMain :: (Ord n)
=> Vty
-> IO Vty
-> Maybe (BChan e)
-> App s e n
-> s
-> IO s
customMain :: forall n e s.
Ord n =>
Vty -> IO Vty -> Maybe (BChan e) -> App s e n -> s -> IO s
customMain Vty
initialVty IO Vty
buildVty Maybe (BChan e)
mUserChan App s e n
app s
initialAppState = do
let restoreInitialState :: IO ()
restoreInitialState = Input -> IO ()
restoreInputState forall a b. (a -> b) -> a -> b
$ Vty -> Input
inputIface Vty
initialVty
(s
s, Vty
vty) <- forall n e s.
Ord n =>
Vty -> IO Vty -> Maybe (BChan e) -> App s e n -> s -> IO (s, Vty)
customMainWithVty Vty
initialVty IO Vty
buildVty Maybe (BChan e)
mUserChan App s e n
app s
initialAppState
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` (\(SomeException
e::E.SomeException) -> IO ()
restoreInitialState forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a e. Exception e => e -> a
E.throw SomeException
e)
Vty -> IO ()
shutdown Vty
vty
IO ()
restoreInitialState
forall (m :: * -> *) a. Monad m => a -> m a
return s
s
customMainWithVty :: (Ord n)
=> Vty
-> IO Vty
-> Maybe (BChan e)
-> App s e n
-> s
-> IO (s, Vty)
customMainWithVty :: forall n e s.
Ord n =>
Vty -> IO Vty -> Maybe (BChan e) -> App s e n -> s -> IO (s, Vty)
customMainWithVty Vty
initialVty IO Vty
buildVty Maybe (BChan e)
mUserChan App s e n
app s
initialAppState = do
BChan (BrickEvent n e)
brickChan <- forall a. Int -> IO (BChan a)
newBChan Int
20
VtyContext
vtyCtx <- IO Vty -> Maybe Vty -> (Event -> IO ()) -> IO VtyContext
newVtyContext IO Vty
buildVty (forall a. a -> Maybe a
Just Vty
initialVty) (forall a. BChan a -> a -> IO ()
writeBChan BChan (BrickEvent n e)
brickChan forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n e. Event -> BrickEvent n e
VtyEvent)
let emptyES :: EventState n
emptyES = ES { esScrollRequests :: [(n, ScrollRequest)]
esScrollRequests = []
, cacheInvalidateRequests :: Set (CacheInvalidateRequest n)
cacheInvalidateRequests = forall a. Monoid a => a
mempty
, requestedVisibleNames :: Set n
requestedVisibleNames = forall a. Monoid a => a
mempty
, nextAction :: NextAction
nextAction = NextAction
Continue
, vtyContext :: VtyContext
vtyContext = VtyContext
vtyCtx
}
emptyRS :: RenderState n
emptyRS = forall n.
Map n Viewport
-> [(n, ScrollRequest)]
-> Set n
-> Map n ([n], Result n)
-> [n]
-> Set n
-> Map n (Extent n)
-> RenderState n
RS forall k a. Map k a
M.empty forall a. Monoid a => a
mempty forall a. Set a
S.empty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty
eventRO :: EventRO n
eventRO = forall n.
Map n Viewport -> [Extent n] -> RenderState n -> EventRO n
EventRO forall k a. Map k a
M.empty forall a. Monoid a => a
mempty RenderState n
emptyRS
(((), s
appState), EventState n
eState) <- forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall n s a.
EventM n s a
-> ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
runEventM (forall s e n. App s e n -> EventM n s ()
appStartEvent App s e n
app)) EventRO n
eventRO) s
initialAppState) EventState n
emptyES
let initialRS :: RenderState n
initialRS = RS { viewportMap :: Map n Viewport
viewportMap = forall k a. Map k a
M.empty
, rsScrollRequests :: [(n, ScrollRequest)]
rsScrollRequests = forall n. EventState n -> [(n, ScrollRequest)]
esScrollRequests EventState n
eState
, observedNames :: Set n
observedNames = forall a. Set a
S.empty
, renderCache :: Map n ([n], Result n)
renderCache = forall a. Monoid a => a
mempty
, clickableNames :: [n]
clickableNames = []
, requestedVisibleNames_ :: Set n
requestedVisibleNames_ = forall n. EventState n -> Set n
requestedVisibleNames EventState n
eState
, reportedExtents :: Map n (Extent n)
reportedExtents = forall a. Monoid a => a
mempty
}
(s
s, VtyContext
ctx) <- forall n e s.
Ord n =>
VtyContext
-> BChan (BrickEvent n e)
-> Maybe (BChan e)
-> App s e n
-> RenderState n
-> s
-> IO (s, VtyContext)
runWithVty VtyContext
vtyCtx BChan (BrickEvent n e)
brickChan Maybe (BChan e)
mUserChan App s e n
app RenderState n
initialRS s
appState
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` (\(SomeException
e::E.SomeException) -> VtyContext -> IO ()
shutdownVtyContext VtyContext
vtyCtx forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a e. Exception e => e -> a
E.throw SomeException
e)
VtyContext -> IO ()
shutdownVtyContextThread VtyContext
ctx
forall (m :: * -> *) a. Monad m => a -> m a
return (s
s, VtyContext -> Vty
vtyContextHandle VtyContext
ctx)
supplyVtyEvents :: Vty -> (Event -> IO ()) -> IO ()
supplyVtyEvents :: Vty -> (Event -> IO ()) -> IO ()
supplyVtyEvents Vty
vty Event -> IO ()
putEvent =
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever forall a b. (a -> b) -> a -> b
$ Event -> IO ()
putEvent forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Vty -> IO Event
nextEvent Vty
vty
newVtyContextFrom :: VtyContext -> IO VtyContext
newVtyContextFrom :: VtyContext -> IO VtyContext
newVtyContextFrom VtyContext
old =
IO Vty -> Maybe Vty -> (Event -> IO ()) -> IO VtyContext
newVtyContext (VtyContext -> IO Vty
vtyContextBuilder VtyContext
old) forall a. Maybe a
Nothing (VtyContext -> Event -> IO ()
vtyContextPutEvent VtyContext
old)
newVtyContext :: IO Vty -> Maybe Vty -> (Event -> IO ()) -> IO VtyContext
newVtyContext :: IO Vty -> Maybe Vty -> (Event -> IO ()) -> IO VtyContext
newVtyContext IO Vty
builder Maybe Vty
handle Event -> IO ()
putEvent = do
Vty
vty <- case Maybe Vty
handle of
Just Vty
h -> forall (m :: * -> *) a. Monad m => a -> m a
return Vty
h
Maybe Vty
Nothing -> IO Vty
builder
ThreadId
tId <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ Vty -> (Event -> IO ()) -> IO ()
supplyVtyEvents Vty
vty Event -> IO ()
putEvent
forall (m :: * -> *) a. Monad m => a -> m a
return VtyContext { vtyContextHandle :: Vty
vtyContextHandle = Vty
vty
, vtyContextBuilder :: IO Vty
vtyContextBuilder = IO Vty
builder
, vtyContextThread :: ThreadId
vtyContextThread = ThreadId
tId
, vtyContextPutEvent :: Event -> IO ()
vtyContextPutEvent = Event -> IO ()
putEvent
}
shutdownVtyContext :: VtyContext -> IO ()
shutdownVtyContext :: VtyContext -> IO ()
shutdownVtyContext VtyContext
ctx = do
Vty -> IO ()
shutdown forall a b. (a -> b) -> a -> b
$ VtyContext -> Vty
vtyContextHandle VtyContext
ctx
VtyContext -> IO ()
shutdownVtyContextThread VtyContext
ctx
shutdownVtyContextThread :: VtyContext -> IO ()
shutdownVtyContextThread :: VtyContext -> IO ()
shutdownVtyContextThread VtyContext
ctx =
ThreadId -> IO ()
killThread forall a b. (a -> b) -> a -> b
$ VtyContext -> ThreadId
vtyContextThread VtyContext
ctx
runVty :: (Ord n)
=> VtyContext
-> IO (BrickEvent n e)
-> App s e n
-> s
-> RenderState n
-> [Extent n]
-> Bool
-> IO (s, NextAction, RenderState n, [Extent n], VtyContext)
runVty :: forall n e s.
Ord n =>
VtyContext
-> IO (BrickEvent n e)
-> App s e n
-> s
-> RenderState n
-> [Extent n]
-> Bool
-> IO (s, NextAction, RenderState n, [Extent n], VtyContext)
runVty VtyContext
vtyCtx IO (BrickEvent n e)
readEvent App s e n
app s
appState RenderState n
rs [Extent n]
prevExtents Bool
draw = do
(RenderState n
firstRS, [Extent n]
exts) <- if Bool
draw
then forall n s e.
Ord n =>
VtyContext
-> App s e n
-> s
-> RenderState n
-> IO (RenderState n, [Extent n])
renderApp VtyContext
vtyCtx App s e n
app s
appState RenderState n
rs
else forall (m :: * -> *) a. Monad m => a -> m a
return (RenderState n
rs, [Extent n]
prevExtents)
BrickEvent n e
e <- IO (BrickEvent n e)
readEvent
(BrickEvent n e
e', RenderState n
nextRS, [Extent n]
nextExts) <- case BrickEvent n e
e of
VtyEvent (EvResize Int
_ Int
_) -> do
(RenderState n
rs', [Extent n]
exts') <- forall n s e.
Ord n =>
VtyContext
-> App s e n
-> s
-> RenderState n
-> IO (RenderState n, [Extent n])
renderApp VtyContext
vtyCtx App s e n
app s
appState forall a b. (a -> b) -> a -> b
$ RenderState n
firstRS forall a b. a -> (a -> b) -> b
& forall n. Lens' (RenderState n) (Set n)
observedNamesL forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. Set a
S.empty
forall (m :: * -> *) a. Monad m => a -> m a
return (BrickEvent n e
e, RenderState n
rs', [Extent n]
exts')
VtyEvent (EvMouseDown Int
c Int
r Button
button [Modifier]
mods) -> do
let matching :: [Extent n]
matching = forall n. (Int, Int) -> [Extent n] -> [Extent n]
findClickedExtents_ (Int
c, Int
r) [Extent n]
exts
case [Extent n]
matching of
(Extent n
n (Location (Int
ec, Int
er)) (Int, Int)
_:[Extent n]
_) ->
if n
n forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` RenderState n
firstRSforall s a. s -> Getting a s a -> a
^.forall n. Lens' (RenderState n) [n]
clickableNamesL
then do
let localCoords :: Location
localCoords = (Int, Int) -> Location
Location (Int
lc, Int
lr)
lc :: Int
lc = Int
c forall a. Num a => a -> a -> a
- Int
ec
lr :: Int
lr = Int
r forall a. Num a => a -> a -> a
- Int
er
newCoords :: Location
newCoords = case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup n
n (forall n. RenderState n -> Map n Viewport
viewportMap RenderState n
firstRS) of
Maybe Viewport
Nothing -> Location
localCoords
Just Viewport
vp -> Location
localCoords forall a b. a -> (a -> b) -> b
& forall s t a b. Field1 s t a b => Lens s t a b
_1 forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (forall a. Num a => a -> a -> a
+ (Viewport
vpforall s a. s -> Getting a s a -> a
^.Lens' Viewport Int
vpLeft))
forall a b. a -> (a -> b) -> b
& forall s t a b. Field2 s t a b => Lens s t a b
_2 forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (forall a. Num a => a -> a -> a
+ (Viewport
vpforall s a. s -> Getting a s a -> a
^.Lens' Viewport Int
vpTop))
forall (m :: * -> *) a. Monad m => a -> m a
return (forall n e. n -> Button -> [Modifier] -> Location -> BrickEvent n e
MouseDown n
n Button
button [Modifier]
mods Location
newCoords, RenderState n
firstRS, [Extent n]
exts)
else forall (m :: * -> *) a. Monad m => a -> m a
return (BrickEvent n e
e, RenderState n
firstRS, [Extent n]
exts)
[Extent n]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (BrickEvent n e
e, RenderState n
firstRS, [Extent n]
exts)
VtyEvent (EvMouseUp Int
c Int
r Maybe Button
button) -> do
let matching :: [Extent n]
matching = forall n. (Int, Int) -> [Extent n] -> [Extent n]
findClickedExtents_ (Int
c, Int
r) [Extent n]
exts
case [Extent n]
matching of
(Extent n
n (Location (Int
ec, Int
er)) (Int, Int)
_:[Extent n]
_) ->
if n
n forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` RenderState n
firstRSforall s a. s -> Getting a s a -> a
^.forall n. Lens' (RenderState n) [n]
clickableNamesL
then do
let localCoords :: Location
localCoords = (Int, Int) -> Location
Location (Int
lc, Int
lr)
lc :: Int
lc = Int
c forall a. Num a => a -> a -> a
- Int
ec
lr :: Int
lr = Int
r forall a. Num a => a -> a -> a
- Int
er
newCoords :: Location
newCoords = case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup n
n (forall n. RenderState n -> Map n Viewport
viewportMap RenderState n
firstRS) of
Maybe Viewport
Nothing -> Location
localCoords
Just Viewport
vp -> Location
localCoords forall a b. a -> (a -> b) -> b
& forall s t a b. Field1 s t a b => Lens s t a b
_1 forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (forall a. Num a => a -> a -> a
+ (Viewport
vpforall s a. s -> Getting a s a -> a
^.Lens' Viewport Int
vpLeft))
forall a b. a -> (a -> b) -> b
& forall s t a b. Field2 s t a b => Lens s t a b
_2 forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (forall a. Num a => a -> a -> a
+ (Viewport
vpforall s a. s -> Getting a s a -> a
^.Lens' Viewport Int
vpTop))
forall (m :: * -> *) a. Monad m => a -> m a
return (forall n e. n -> Maybe Button -> Location -> BrickEvent n e
MouseUp n
n Maybe Button
button Location
newCoords, RenderState n
firstRS, [Extent n]
exts)
else forall (m :: * -> *) a. Monad m => a -> m a
return (BrickEvent n e
e, RenderState n
firstRS, [Extent n]
exts)
[Extent n]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (BrickEvent n e
e, RenderState n
firstRS, [Extent n]
exts)
BrickEvent n e
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (BrickEvent n e
e, RenderState n
firstRS, [Extent n]
exts)
let emptyES :: EventState n
emptyES = forall n.
[(n, ScrollRequest)]
-> Set (CacheInvalidateRequest n)
-> Set n
-> NextAction
-> VtyContext
-> EventState n
ES [] forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty NextAction
Continue VtyContext
vtyCtx
eventRO :: EventRO n
eventRO = forall n.
Map n Viewport -> [Extent n] -> RenderState n -> EventRO n
EventRO (forall n. RenderState n -> Map n Viewport
viewportMap RenderState n
nextRS) [Extent n]
nextExts RenderState n
nextRS
(((), s
newAppState), EventState n
eState) <- forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall n s a.
EventM n s a
-> ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
runEventM (forall s e n. App s e n -> BrickEvent n e -> EventM n s ()
appHandleEvent App s e n
app BrickEvent n e
e'))
EventRO n
eventRO) s
appState) EventState n
emptyES
forall (m :: * -> *) a. Monad m => a -> m a
return ( s
newAppState
, forall n. EventState n -> NextAction
nextAction EventState n
eState
, RenderState n
nextRS { rsScrollRequests :: [(n, ScrollRequest)]
rsScrollRequests = forall n. EventState n -> [(n, ScrollRequest)]
esScrollRequests EventState n
eState
, renderCache :: Map n ([n], Result n)
renderCache = forall n v.
Ord n =>
Set (CacheInvalidateRequest n) -> Map n v -> Map n v
applyInvalidations (forall n. EventState n -> Set (CacheInvalidateRequest n)
cacheInvalidateRequests EventState n
eState) forall a b. (a -> b) -> a -> b
$
forall n. RenderState n -> Map n ([n], Result n)
renderCache RenderState n
nextRS
, requestedVisibleNames_ :: Set n
requestedVisibleNames_ = forall n. EventState n -> Set n
requestedVisibleNames EventState n
eState
}
, [Extent n]
nextExts
, forall n. EventState n -> VtyContext
vtyContext EventState n
eState
)
applyInvalidations :: (Ord n) => S.Set (CacheInvalidateRequest n) -> M.Map n v -> M.Map n v
applyInvalidations :: forall n v.
Ord n =>
Set (CacheInvalidateRequest n) -> Map n v -> Map n v
applyInvalidations Set (CacheInvalidateRequest n)
ns Map n v
cache =
if forall n. CacheInvalidateRequest n
InvalidateEntire forall a. Ord a => a -> Set a -> Bool
`S.member` Set (CacheInvalidateRequest n)
ns
then forall a. Monoid a => a
mempty
else forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall a. a -> a
id (forall {k} {a}.
Ord k =>
CacheInvalidateRequest k -> Map k a -> Map k a
mkFunc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList Set (CacheInvalidateRequest n)
ns) Map n v
cache
where
mkFunc :: CacheInvalidateRequest k -> Map k a -> Map k a
mkFunc CacheInvalidateRequest k
InvalidateEntire = forall a b. a -> b -> a
const forall a. Monoid a => a
mempty
mkFunc (InvalidateSingle k
n) = forall k a. Ord k => k -> Map k a -> Map k a
M.delete k
n
lookupViewport :: (Ord n) => n -> EventM n s (Maybe Viewport)
lookupViewport :: forall n s. Ord n => n -> EventM n s (Maybe Viewport)
lookupViewport n
n = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup n
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. EventRO n -> Map n Viewport
eventViewportMap)
clickedExtent :: (Int, Int) -> Extent n -> Bool
clickedExtent :: forall n. (Int, Int) -> Extent n -> Bool
clickedExtent (Int
c, Int
r) (Extent n
_ (Location (Int
lc, Int
lr)) (Int
w, Int
h)) =
Int
c forall a. Ord a => a -> a -> Bool
>= Int
lc Bool -> Bool -> Bool
&& Int
c forall a. Ord a => a -> a -> Bool
< (Int
lc forall a. Num a => a -> a -> a
+ Int
w) Bool -> Bool -> Bool
&&
Int
r forall a. Ord a => a -> a -> Bool
>= Int
lr Bool -> Bool -> Bool
&& Int
r forall a. Ord a => a -> a -> Bool
< (Int
lr forall a. Num a => a -> a -> a
+ Int
h)
lookupExtent :: (Eq n) => n -> EventM n s (Maybe (Extent n))
lookupExtent :: forall n s. Eq n => n -> EventM n s (Maybe (Extent n))
lookupExtent n
n = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find Extent n -> Bool
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. EventRO n -> [Extent n]
latestExtents)
where
f :: Extent n -> Bool
f (Extent n
n' Location
_ (Int, Int)
_) = n
n forall a. Eq a => a -> a -> Bool
== n
n'
findClickedExtents :: (Int, Int) -> EventM n s [Extent n]
findClickedExtents :: forall n s. (Int, Int) -> EventM n s [Extent n]
findClickedExtents (Int, Int)
pos = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (forall n. (Int, Int) -> [Extent n] -> [Extent n]
findClickedExtents_ (Int, Int)
pos forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. EventRO n -> [Extent n]
latestExtents)
findClickedExtents_ :: (Int, Int) -> [Extent n] -> [Extent n]
findClickedExtents_ :: forall n. (Int, Int) -> [Extent n] -> [Extent n]
findClickedExtents_ (Int, Int)
pos = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall n. (Int, Int) -> Extent n -> Bool
clickedExtent (Int, Int)
pos)
getVtyHandle :: EventM n s Vty
getVtyHandle :: forall n s. EventM n s Vty
getVtyHandle = VtyContext -> Vty
vtyContextHandle forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall n s. EventM n s VtyContext
getVtyContext
setVtyContext :: VtyContext -> EventM n s ()
setVtyContext :: forall n s. VtyContext -> EventM n s ()
setVtyContext VtyContext
ctx =
forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \EventState n
s -> EventState n
s { vtyContext :: VtyContext
vtyContext = VtyContext
ctx }
invalidateCacheEntry :: (Ord n) => n -> EventM n s ()
invalidateCacheEntry :: forall n s. Ord n => n -> EventM n s ()
invalidateCacheEntry n
n = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\EventState n
s -> EventState n
s { cacheInvalidateRequests :: Set (CacheInvalidateRequest n)
cacheInvalidateRequests = forall a. Ord a => a -> Set a -> Set a
S.insert (forall n. n -> CacheInvalidateRequest n
InvalidateSingle n
n) forall a b. (a -> b) -> a -> b
$ forall n. EventState n -> Set (CacheInvalidateRequest n)
cacheInvalidateRequests EventState n
s })
invalidateCache :: (Ord n) => EventM n s ()
invalidateCache :: forall n s. Ord n => EventM n s ()
invalidateCache = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\EventState n
s -> EventState n
s { cacheInvalidateRequests :: Set (CacheInvalidateRequest n)
cacheInvalidateRequests = forall a. Ord a => a -> Set a -> Set a
S.insert forall n. CacheInvalidateRequest n
InvalidateEntire forall a b. (a -> b) -> a -> b
$ forall n. EventState n -> Set (CacheInvalidateRequest n)
cacheInvalidateRequests EventState n
s })
getRenderState :: EventM n s (RenderState n)
getRenderState :: forall n s. EventM n s (RenderState n)
getRenderState = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks forall n. EventRO n -> RenderState n
oldState
resetRenderState :: RenderState n -> RenderState n
resetRenderState :: forall n. RenderState n -> RenderState n
resetRenderState RenderState n
s =
RenderState n
s forall a b. a -> (a -> b) -> b
& forall n. Lens' (RenderState n) (Set n)
observedNamesL forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. Set a
S.empty
forall a b. a -> (a -> b) -> b
& forall n. Lens' (RenderState n) [n]
clickableNamesL forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. Monoid a => a
mempty
renderApp :: (Ord n) => VtyContext -> App s e n -> s -> RenderState n -> IO (RenderState n, [Extent n])
renderApp :: forall n s e.
Ord n =>
VtyContext
-> App s e n
-> s
-> RenderState n
-> IO (RenderState n, [Extent n])
renderApp VtyContext
vtyCtx App s e n
app s
appState RenderState n
rs = do
(Int, Int)
sz <- Output -> IO (Int, Int)
displayBounds forall a b. (a -> b) -> a -> b
$ Vty -> Output
outputIface forall a b. (a -> b) -> a -> b
$ VtyContext -> Vty
vtyContextHandle VtyContext
vtyCtx
let (RenderState n
newRS, Picture
pic, Maybe (CursorLocation n)
theCursor, [Extent n]
exts) = forall n.
Ord n =>
AttrMap
-> [Widget n]
-> (Int, Int)
-> ([CursorLocation n] -> Maybe (CursorLocation n))
-> RenderState n
-> (RenderState n, Picture, Maybe (CursorLocation n), [Extent n])
renderFinal (forall s e n. App s e n -> s -> AttrMap
appAttrMap App s e n
app s
appState)
(forall s e n. App s e n -> s -> [Widget n]
appDraw App s e n
app s
appState)
(Int, Int)
sz
(forall s e n.
App s e n -> s -> [CursorLocation n] -> Maybe (CursorLocation n)
appChooseCursor App s e n
app s
appState)
RenderState n
rs
picWithCursor :: Picture
picWithCursor = case Maybe (CursorLocation n)
theCursor of
Maybe (CursorLocation n)
Nothing -> Picture
pic { picCursor :: Cursor
picCursor = Cursor
NoCursor }
Just CursorLocation n
cloc -> Picture
pic { picCursor :: Cursor
picCursor = (if forall n. CursorLocation n -> Bool
cursorLocationVisible CursorLocation n
cloc
then Int -> Int -> Cursor
AbsoluteCursor
else Bool -> Int -> Int -> Cursor
PositionOnly Bool
True)
(CursorLocation n
clocforall s a. s -> Getting a s a -> a
^.forall a. TerminalLocation a => Lens' a Int
locationColumnL)
(CursorLocation n
clocforall s a. s -> Getting a s a -> a
^.forall a. TerminalLocation a => Lens' a Int
locationRowL)
}
Vty -> Picture -> IO ()
update (VtyContext -> Vty
vtyContextHandle VtyContext
vtyCtx) Picture
picWithCursor
forall (m :: * -> *) a. Monad m => a -> m a
return (RenderState n
newRS, [Extent n]
exts)
neverShowCursor :: s -> [CursorLocation n] -> Maybe (CursorLocation n)
neverShowCursor :: forall s n. s -> [CursorLocation n] -> Maybe (CursorLocation n)
neverShowCursor = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall a. Maybe a
Nothing
showFirstCursor :: s -> [CursorLocation n] -> Maybe (CursorLocation n)
showFirstCursor :: forall s n. s -> [CursorLocation n] -> Maybe (CursorLocation n)
showFirstCursor = forall a b. a -> b -> a
const forall a. [a] -> Maybe a
listToMaybe
showCursorNamed :: (Eq n) => n -> [CursorLocation n] -> Maybe (CursorLocation n)
showCursorNamed :: forall n.
Eq n =>
n -> [CursorLocation n] -> Maybe (CursorLocation n)
showCursorNamed n
name [CursorLocation n]
locs =
let matches :: CursorLocation n -> Bool
matches CursorLocation n
l = CursorLocation n
lforall s a. s -> Getting a s a -> a
^.forall n1 n2.
Lens (CursorLocation n1) (CursorLocation n2) (Maybe n1) (Maybe n2)
cursorLocationNameL forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just n
name
in forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find CursorLocation n -> Bool
matches [CursorLocation n]
locs
data ViewportScroll n =
ViewportScroll { forall n. ViewportScroll n -> n
viewportName :: n
, forall n. ViewportScroll n -> forall s. Direction -> EventM n s ()
hScrollPage :: forall s. Direction -> EventM n s ()
, forall n. ViewportScroll n -> forall s. Int -> EventM n s ()
hScrollBy :: forall s. Int -> EventM n s ()
, forall n. ViewportScroll n -> forall s. EventM n s ()
hScrollToBeginning :: forall s. EventM n s ()
, forall n. ViewportScroll n -> forall s. EventM n s ()
hScrollToEnd :: forall s. EventM n s ()
, forall n. ViewportScroll n -> forall s. Direction -> EventM n s ()
vScrollPage :: forall s. Direction -> EventM n s ()
, forall n. ViewportScroll n -> forall s. Int -> EventM n s ()
vScrollBy :: forall s. Int -> EventM n s ()
, forall n. ViewportScroll n -> forall s. EventM n s ()
vScrollToBeginning :: forall s. EventM n s ()
, forall n. ViewportScroll n -> forall s. EventM n s ()
vScrollToEnd :: forall s. EventM n s ()
, forall n. ViewportScroll n -> forall s. Int -> EventM n s ()
setTop :: forall s. Int -> EventM n s ()
, forall n. ViewportScroll n -> forall s. Int -> EventM n s ()
setLeft :: forall s. Int -> EventM n s ()
}
addScrollRequest :: (n, ScrollRequest) -> EventM n s ()
addScrollRequest :: forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n, ScrollRequest)
req = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\EventState n
s -> EventState n
s { esScrollRequests :: [(n, ScrollRequest)]
esScrollRequests = (n, ScrollRequest)
req forall a. a -> [a] -> [a]
: forall n. EventState n -> [(n, ScrollRequest)]
esScrollRequests EventState n
s })
viewportScroll :: n -> ViewportScroll n
viewportScroll :: forall n. n -> ViewportScroll n
viewportScroll n
n =
ViewportScroll { viewportName :: n
viewportName = n
n
, hScrollPage :: forall s. Direction -> EventM n s ()
hScrollPage = \Direction
dir -> forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, Direction -> ScrollRequest
HScrollPage Direction
dir)
, hScrollBy :: forall s. Int -> EventM n s ()
hScrollBy = \Int
i -> forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, Int -> ScrollRequest
HScrollBy Int
i)
, hScrollToBeginning :: forall s. EventM n s ()
hScrollToBeginning = forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, ScrollRequest
HScrollToBeginning)
, hScrollToEnd :: forall s. EventM n s ()
hScrollToEnd = forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, ScrollRequest
HScrollToEnd)
, vScrollPage :: forall s. Direction -> EventM n s ()
vScrollPage = \Direction
dir -> forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, Direction -> ScrollRequest
VScrollPage Direction
dir)
, vScrollBy :: forall s. Int -> EventM n s ()
vScrollBy = \Int
i -> forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, Int -> ScrollRequest
VScrollBy Int
i)
, vScrollToBeginning :: forall s. EventM n s ()
vScrollToBeginning = forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, ScrollRequest
VScrollToBeginning)
, vScrollToEnd :: forall s. EventM n s ()
vScrollToEnd = forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, ScrollRequest
VScrollToEnd)
, setTop :: forall s. Int -> EventM n s ()
setTop = \Int
i -> forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, Int -> ScrollRequest
SetTop Int
i)
, setLeft :: forall s. Int -> EventM n s ()
setLeft = \Int
i -> forall n s. (n, ScrollRequest) -> EventM n s ()
addScrollRequest (n
n, Int -> ScrollRequest
SetLeft Int
i)
}
continueWithoutRedraw :: EventM n s ()
continueWithoutRedraw :: forall n s. EventM n s ()
continueWithoutRedraw =
forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \EventState n
es -> EventState n
es { nextAction :: NextAction
nextAction = NextAction
ContinueWithoutRedraw }
halt :: EventM n s ()
halt :: forall n s. EventM n s ()
halt =
forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \EventState n
es -> EventState n
es { nextAction :: NextAction
nextAction = NextAction
Halt }
suspendAndResume :: (Ord n) => IO s -> EventM n s ()
suspendAndResume :: forall n s. Ord n => IO s -> EventM n s ()
suspendAndResume IO s
act = forall n a s. Ord n => IO a -> EventM n s a
suspendAndResume' IO s
act forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall s (m :: * -> *). MonadState s m => s -> m ()
put
suspendAndResume' :: (Ord n) => IO a -> EventM n s a
suspendAndResume' :: forall n a s. Ord n => IO a -> EventM n s a
suspendAndResume' IO a
act = do
VtyContext
ctx <- forall n s. EventM n s VtyContext
getVtyContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ VtyContext -> IO ()
shutdownVtyContext VtyContext
ctx
a
result <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
act
forall n s. VtyContext -> EventM n s ()
setVtyContext forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ VtyContext -> IO VtyContext
newVtyContextFrom VtyContext
ctx)
forall n s. Ord n => EventM n s ()
invalidateCache
forall (m :: * -> *) a. Monad m => a -> m a
return a
result
makeVisible :: (Ord n) => n -> EventM n s ()
makeVisible :: forall n s. Ord n => n -> EventM n s ()
makeVisible n
n = forall n s a.
ReaderT (EventRO n) (StateT s (StateT (EventState n) IO)) a
-> EventM n s a
EventM forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\EventState n
s -> EventState n
s { requestedVisibleNames :: Set n
requestedVisibleNames = forall a. Ord a => a -> Set a -> Set a
S.insert n
n forall a b. (a -> b) -> a -> b
$ forall n. EventState n -> Set n
requestedVisibleNames EventState n
s })