{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
module Brick.Types.Internal
( ScrollRequest(..)
, VisibilityRequest(..)
, vrPositionL
, vrSizeL
, Location(..)
, locL
, origin
, TerminalLocation(..)
, Viewport(..)
, ViewportType(..)
, RenderState(..)
, Direction(..)
, CursorLocation(..)
, cursorLocationL
, cursorLocationNameL
, cursorLocationVisibleL
, VScrollBarOrientation(..)
, HScrollBarOrientation(..)
, VScrollbarRenderer(..)
, HScrollbarRenderer(..)
, ClickableScrollbarElement(..)
, Context(..)
, ctxAttrMapL
, ctxAttrNameL
, ctxBorderStyleL
, ctxDynBordersL
, ctxVScrollBarOrientationL
, ctxVScrollBarRendererL
, ctxHScrollBarOrientationL
, ctxHScrollBarRendererL
, ctxVScrollBarShowHandlesL
, ctxHScrollBarShowHandlesL
, ctxVScrollBarClickableConstrL
, ctxHScrollBarClickableConstrL
, availWidthL
, availHeightL
, windowWidthL
, windowHeightL
, Size(..)
, EventState(..)
, VtyContext(..)
, EventRO(..)
, NextAction(..)
, Result(..)
, Extent(..)
, Edges(..)
, eTopL, eBottomL, eRightL, eLeftL
, BorderSegment(..)
, bsAcceptL, bsOfferL, bsDrawL
, DynBorder(..)
, dbStyleL, dbAttrL, dbSegmentsL
, CacheInvalidateRequest(..)
, BrickEvent(..)
, RenderM
, getContext
, lookupReportedExtent
, Widget(..)
, rsScrollRequestsL
, viewportMapL
, clickableNamesL
, reportedExtentsL
, renderCacheL
, observedNamesL
, requestedVisibleNames_L
, vpSize
, vpLeft
, vpTop
, vpContentSize
, imageL
, cursorsL
, extentsL
, bordersL
, visibilityRequestsL
, emptyResult
)
where
import Control.Concurrent (ThreadId)
import Control.Monad.Reader
import Control.Monad.State.Strict
import Lens.Micro (_1, _2, Lens')
import Lens.Micro.Mtl (use)
import Lens.Micro.TH (makeLenses)
import qualified Data.Set as S
import qualified Data.Map as M
import Graphics.Vty (Vty, Event, Button, Modifier, DisplayRegion, Image, Attr, emptyImage)
import GHC.Generics
import Control.DeepSeq (NFData)
import Brick.BorderMap (BorderMap)
import qualified Brick.BorderMap as BM
import Brick.Types.Common
import Brick.Types.TH
import Brick.AttrMap (AttrName, AttrMap)
import Brick.Widgets.Border.Style (BorderStyle)
data ScrollRequest = HScrollBy Int
| HScrollPage Direction
| HScrollToBeginning
| HScrollToEnd
| VScrollBy Int
| VScrollPage Direction
| VScrollToBeginning
| VScrollToEnd
| SetTop Int
| SetLeft Int
deriving (ReadPrec [ScrollRequest]
ReadPrec ScrollRequest
Int -> ReadS ScrollRequest
ReadS [ScrollRequest]
(Int -> ReadS ScrollRequest)
-> ReadS [ScrollRequest]
-> ReadPrec ScrollRequest
-> ReadPrec [ScrollRequest]
-> Read ScrollRequest
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ScrollRequest
readsPrec :: Int -> ReadS ScrollRequest
$creadList :: ReadS [ScrollRequest]
readList :: ReadS [ScrollRequest]
$creadPrec :: ReadPrec ScrollRequest
readPrec :: ReadPrec ScrollRequest
$creadListPrec :: ReadPrec [ScrollRequest]
readListPrec :: ReadPrec [ScrollRequest]
Read, Int -> ScrollRequest -> ShowS
[ScrollRequest] -> ShowS
ScrollRequest -> String
(Int -> ScrollRequest -> ShowS)
-> (ScrollRequest -> String)
-> ([ScrollRequest] -> ShowS)
-> Show ScrollRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScrollRequest -> ShowS
showsPrec :: Int -> ScrollRequest -> ShowS
$cshow :: ScrollRequest -> String
show :: ScrollRequest -> String
$cshowList :: [ScrollRequest] -> ShowS
showList :: [ScrollRequest] -> ShowS
Show, (forall x. ScrollRequest -> Rep ScrollRequest x)
-> (forall x. Rep ScrollRequest x -> ScrollRequest)
-> Generic ScrollRequest
forall x. Rep ScrollRequest x -> ScrollRequest
forall x. ScrollRequest -> Rep ScrollRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScrollRequest -> Rep ScrollRequest x
from :: forall x. ScrollRequest -> Rep ScrollRequest x
$cto :: forall x. Rep ScrollRequest x -> ScrollRequest
to :: forall x. Rep ScrollRequest x -> ScrollRequest
Generic, ScrollRequest -> ()
(ScrollRequest -> ()) -> NFData ScrollRequest
forall a. (a -> ()) -> NFData a
$crnf :: ScrollRequest -> ()
rnf :: ScrollRequest -> ()
NFData)
data Size = Fixed
| Greedy
deriving (Int -> Size -> ShowS
[Size] -> ShowS
Size -> String
(Int -> Size -> ShowS)
-> (Size -> String) -> ([Size] -> ShowS) -> Show Size
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Size -> ShowS
showsPrec :: Int -> Size -> ShowS
$cshow :: Size -> String
show :: Size -> String
$cshowList :: [Size] -> ShowS
showList :: [Size] -> ShowS
Show, Size -> Size -> Bool
(Size -> Size -> Bool) -> (Size -> Size -> Bool) -> Eq Size
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Size -> Size -> Bool
== :: Size -> Size -> Bool
$c/= :: Size -> Size -> Bool
/= :: Size -> Size -> Bool
Eq, Eq Size
Eq Size =>
(Size -> Size -> Ordering)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> Ord Size
Size -> Size -> Bool
Size -> Size -> Ordering
Size -> Size -> Size
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Size -> Size -> Ordering
compare :: Size -> Size -> Ordering
$c< :: Size -> Size -> Bool
< :: Size -> Size -> Bool
$c<= :: Size -> Size -> Bool
<= :: Size -> Size -> Bool
$c> :: Size -> Size -> Bool
> :: Size -> Size -> Bool
$c>= :: Size -> Size -> Bool
>= :: Size -> Size -> Bool
$cmax :: Size -> Size -> Size
max :: Size -> Size -> Size
$cmin :: Size -> Size -> Size
min :: Size -> Size -> Size
Ord)
data Widget n =
Widget { forall n. Widget n -> Size
hSize :: Size
, forall n. Widget n -> Size
vSize :: Size
, forall n. Widget n -> RenderM n (Result n)
render :: RenderM n (Result n)
}
data RenderState n =
RS { forall n. RenderState n -> Map n Viewport
viewportMap :: !(M.Map n Viewport)
, :: ![(n, ScrollRequest)]
, forall n. RenderState n -> Set n
observedNames :: !(S.Set n)
, forall n. RenderState n -> Map n ([n], Result n)
renderCache :: !(M.Map n ([n], Result n))
, forall n. RenderState n -> [n]
clickableNames :: ![n]
, forall n. RenderState n -> Set n
requestedVisibleNames_ :: !(S.Set n)
, forall n. RenderState n -> Map n (Extent n)
reportedExtents :: !(M.Map n (Extent n))
} deriving (ReadPrec [RenderState n]
ReadPrec (RenderState n)
Int -> ReadS (RenderState n)
ReadS [RenderState n]
(Int -> ReadS (RenderState n))
-> ReadS [RenderState n]
-> ReadPrec (RenderState n)
-> ReadPrec [RenderState n]
-> Read (RenderState n)
forall n. (Ord n, Read n) => ReadPrec [RenderState n]
forall n. (Ord n, Read n) => ReadPrec (RenderState n)
forall n. (Ord n, Read n) => Int -> ReadS (RenderState n)
forall n. (Ord n, Read n) => ReadS [RenderState n]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall n. (Ord n, Read n) => Int -> ReadS (RenderState n)
readsPrec :: Int -> ReadS (RenderState n)
$creadList :: forall n. (Ord n, Read n) => ReadS [RenderState n]
readList :: ReadS [RenderState n]
$creadPrec :: forall n. (Ord n, Read n) => ReadPrec (RenderState n)
readPrec :: ReadPrec (RenderState n)
$creadListPrec :: forall n. (Ord n, Read n) => ReadPrec [RenderState n]
readListPrec :: ReadPrec [RenderState n]
Read, Int -> RenderState n -> ShowS
[RenderState n] -> ShowS
RenderState n -> String
(Int -> RenderState n -> ShowS)
-> (RenderState n -> String)
-> ([RenderState n] -> ShowS)
-> Show (RenderState n)
forall n. Show n => Int -> RenderState n -> ShowS
forall n. Show n => [RenderState n] -> ShowS
forall n. Show n => RenderState n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> RenderState n -> ShowS
showsPrec :: Int -> RenderState n -> ShowS
$cshow :: forall n. Show n => RenderState n -> String
show :: RenderState n -> String
$cshowList :: forall n. Show n => [RenderState n] -> ShowS
showList :: [RenderState n] -> ShowS
Show, (forall x. RenderState n -> Rep (RenderState n) x)
-> (forall x. Rep (RenderState n) x -> RenderState n)
-> Generic (RenderState n)
forall x. Rep (RenderState n) x -> RenderState n
forall x. RenderState n -> Rep (RenderState n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (RenderState n) x -> RenderState n
forall n x. RenderState n -> Rep (RenderState n) x
$cfrom :: forall n x. RenderState n -> Rep (RenderState n) x
from :: forall x. RenderState n -> Rep (RenderState n) x
$cto :: forall n x. Rep (RenderState n) x -> RenderState n
to :: forall x. Rep (RenderState n) x -> RenderState n
Generic, RenderState n -> ()
(RenderState n -> ()) -> NFData (RenderState n)
forall n. NFData n => RenderState n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => RenderState n -> ()
rnf :: RenderState n -> ()
NFData)
type RenderM n a = ReaderT (Context n) (State (RenderState n)) a
getContext :: RenderM n (Context n)
getContext :: forall n. RenderM n (Context n)
getContext = ReaderT (Context n) (State (RenderState n)) (Context n)
forall r (m :: * -> *). MonadReader r m => m r
ask
data VScrollBarOrientation = OnLeft | OnRight
deriving (Int -> VScrollBarOrientation -> ShowS
[VScrollBarOrientation] -> ShowS
VScrollBarOrientation -> String
(Int -> VScrollBarOrientation -> ShowS)
-> (VScrollBarOrientation -> String)
-> ([VScrollBarOrientation] -> ShowS)
-> Show VScrollBarOrientation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VScrollBarOrientation -> ShowS
showsPrec :: Int -> VScrollBarOrientation -> ShowS
$cshow :: VScrollBarOrientation -> String
show :: VScrollBarOrientation -> String
$cshowList :: [VScrollBarOrientation] -> ShowS
showList :: [VScrollBarOrientation] -> ShowS
Show, VScrollBarOrientation -> VScrollBarOrientation -> Bool
(VScrollBarOrientation -> VScrollBarOrientation -> Bool)
-> (VScrollBarOrientation -> VScrollBarOrientation -> Bool)
-> Eq VScrollBarOrientation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
== :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
$c/= :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
/= :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
Eq)
data HScrollBarOrientation = OnBottom | OnTop
deriving (Int -> HScrollBarOrientation -> ShowS
[HScrollBarOrientation] -> ShowS
HScrollBarOrientation -> String
(Int -> HScrollBarOrientation -> ShowS)
-> (HScrollBarOrientation -> String)
-> ([HScrollBarOrientation] -> ShowS)
-> Show HScrollBarOrientation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HScrollBarOrientation -> ShowS
showsPrec :: Int -> HScrollBarOrientation -> ShowS
$cshow :: HScrollBarOrientation -> String
show :: HScrollBarOrientation -> String
$cshowList :: [HScrollBarOrientation] -> ShowS
showList :: [HScrollBarOrientation] -> ShowS
Show, HScrollBarOrientation -> HScrollBarOrientation -> Bool
(HScrollBarOrientation -> HScrollBarOrientation -> Bool)
-> (HScrollBarOrientation -> HScrollBarOrientation -> Bool)
-> Eq HScrollBarOrientation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
== :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
$c/= :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
/= :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
Eq)
data VScrollbarRenderer n =
VScrollbarRenderer { forall n. VScrollbarRenderer n -> Widget n
renderVScrollbar :: Widget n
, forall n. VScrollbarRenderer n -> Widget n
renderVScrollbarTrough :: Widget n
, forall n. VScrollbarRenderer n -> Widget n
renderVScrollbarHandleBefore :: Widget n
, forall n. VScrollbarRenderer n -> Widget n
renderVScrollbarHandleAfter :: Widget n
, forall n. VScrollbarRenderer n -> Int
scrollbarWidthAllocation :: Int
}
data HScrollbarRenderer n =
HScrollbarRenderer { forall n. HScrollbarRenderer n -> Widget n
renderHScrollbar :: Widget n
, forall n. HScrollbarRenderer n -> Widget n
renderHScrollbarTrough :: Widget n
, forall n. HScrollbarRenderer n -> Widget n
renderHScrollbarHandleBefore :: Widget n
, forall n. HScrollbarRenderer n -> Widget n
renderHScrollbarHandleAfter :: Widget n
, forall n. HScrollbarRenderer n -> Int
scrollbarHeightAllocation :: Int
}
data VisibilityRequest =
VR { VisibilityRequest -> Location
vrPosition :: Location
, VisibilityRequest -> DisplayRegion
vrSize :: DisplayRegion
}
deriving (Int -> VisibilityRequest -> ShowS
[VisibilityRequest] -> ShowS
VisibilityRequest -> String
(Int -> VisibilityRequest -> ShowS)
-> (VisibilityRequest -> String)
-> ([VisibilityRequest] -> ShowS)
-> Show VisibilityRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VisibilityRequest -> ShowS
showsPrec :: Int -> VisibilityRequest -> ShowS
$cshow :: VisibilityRequest -> String
show :: VisibilityRequest -> String
$cshowList :: [VisibilityRequest] -> ShowS
showList :: [VisibilityRequest] -> ShowS
Show, VisibilityRequest -> VisibilityRequest -> Bool
(VisibilityRequest -> VisibilityRequest -> Bool)
-> (VisibilityRequest -> VisibilityRequest -> Bool)
-> Eq VisibilityRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VisibilityRequest -> VisibilityRequest -> Bool
== :: VisibilityRequest -> VisibilityRequest -> Bool
$c/= :: VisibilityRequest -> VisibilityRequest -> Bool
/= :: VisibilityRequest -> VisibilityRequest -> Bool
Eq, ReadPrec [VisibilityRequest]
ReadPrec VisibilityRequest
Int -> ReadS VisibilityRequest
ReadS [VisibilityRequest]
(Int -> ReadS VisibilityRequest)
-> ReadS [VisibilityRequest]
-> ReadPrec VisibilityRequest
-> ReadPrec [VisibilityRequest]
-> Read VisibilityRequest
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VisibilityRequest
readsPrec :: Int -> ReadS VisibilityRequest
$creadList :: ReadS [VisibilityRequest]
readList :: ReadS [VisibilityRequest]
$creadPrec :: ReadPrec VisibilityRequest
readPrec :: ReadPrec VisibilityRequest
$creadListPrec :: ReadPrec [VisibilityRequest]
readListPrec :: ReadPrec [VisibilityRequest]
Read, (forall x. VisibilityRequest -> Rep VisibilityRequest x)
-> (forall x. Rep VisibilityRequest x -> VisibilityRequest)
-> Generic VisibilityRequest
forall x. Rep VisibilityRequest x -> VisibilityRequest
forall x. VisibilityRequest -> Rep VisibilityRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VisibilityRequest -> Rep VisibilityRequest x
from :: forall x. VisibilityRequest -> Rep VisibilityRequest x
$cto :: forall x. Rep VisibilityRequest x -> VisibilityRequest
to :: forall x. Rep VisibilityRequest x -> VisibilityRequest
Generic, VisibilityRequest -> ()
(VisibilityRequest -> ()) -> NFData VisibilityRequest
forall a. (a -> ()) -> NFData a
$crnf :: VisibilityRequest -> ()
rnf :: VisibilityRequest -> ()
NFData)
data Viewport =
VP { Viewport -> Int
_vpLeft :: Int
, Viewport -> Int
_vpTop :: Int
, Viewport -> DisplayRegion
_vpSize :: DisplayRegion
, Viewport -> DisplayRegion
_vpContentSize :: DisplayRegion
}
deriving (Int -> Viewport -> ShowS
[Viewport] -> ShowS
Viewport -> String
(Int -> Viewport -> ShowS)
-> (Viewport -> String) -> ([Viewport] -> ShowS) -> Show Viewport
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Viewport -> ShowS
showsPrec :: Int -> Viewport -> ShowS
$cshow :: Viewport -> String
show :: Viewport -> String
$cshowList :: [Viewport] -> ShowS
showList :: [Viewport] -> ShowS
Show, ReadPrec [Viewport]
ReadPrec Viewport
Int -> ReadS Viewport
ReadS [Viewport]
(Int -> ReadS Viewport)
-> ReadS [Viewport]
-> ReadPrec Viewport
-> ReadPrec [Viewport]
-> Read Viewport
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Viewport
readsPrec :: Int -> ReadS Viewport
$creadList :: ReadS [Viewport]
readList :: ReadS [Viewport]
$creadPrec :: ReadPrec Viewport
readPrec :: ReadPrec Viewport
$creadListPrec :: ReadPrec [Viewport]
readListPrec :: ReadPrec [Viewport]
Read, (forall x. Viewport -> Rep Viewport x)
-> (forall x. Rep Viewport x -> Viewport) -> Generic Viewport
forall x. Rep Viewport x -> Viewport
forall x. Viewport -> Rep Viewport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Viewport -> Rep Viewport x
from :: forall x. Viewport -> Rep Viewport x
$cto :: forall x. Rep Viewport x -> Viewport
to :: forall x. Rep Viewport x -> Viewport
Generic, Viewport -> ()
(Viewport -> ()) -> NFData Viewport
forall a. (a -> ()) -> NFData a
$crnf :: Viewport -> ()
rnf :: Viewport -> ()
NFData)
data ViewportType =
Vertical
| Horizontal
| Both
deriving (Int -> ViewportType -> ShowS
[ViewportType] -> ShowS
ViewportType -> String
(Int -> ViewportType -> ShowS)
-> (ViewportType -> String)
-> ([ViewportType] -> ShowS)
-> Show ViewportType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ViewportType -> ShowS
showsPrec :: Int -> ViewportType -> ShowS
$cshow :: ViewportType -> String
show :: ViewportType -> String
$cshowList :: [ViewportType] -> ShowS
showList :: [ViewportType] -> ShowS
Show, ViewportType -> ViewportType -> Bool
(ViewportType -> ViewportType -> Bool)
-> (ViewportType -> ViewportType -> Bool) -> Eq ViewportType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ViewportType -> ViewportType -> Bool
== :: ViewportType -> ViewportType -> Bool
$c/= :: ViewportType -> ViewportType -> Bool
/= :: ViewportType -> ViewportType -> Bool
Eq)
data CacheInvalidateRequest n =
InvalidateSingle n
| InvalidateEntire
deriving (Eq (CacheInvalidateRequest n)
Eq (CacheInvalidateRequest n) =>
(CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering)
-> (CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool)
-> (CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool)
-> (CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool)
-> (CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool)
-> (CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n)
-> (CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n)
-> Ord (CacheInvalidateRequest n)
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering
CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall n. Ord n => Eq (CacheInvalidateRequest n)
forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering
forall n.
Ord n =>
CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
$ccompare :: forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering
compare :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering
$c< :: forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
< :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
$c<= :: forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
<= :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
$c> :: forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
> :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
$c>= :: forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
>= :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
$cmax :: forall n.
Ord n =>
CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
max :: CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
$cmin :: forall n.
Ord n =>
CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
min :: CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
Ord, CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
(CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool)
-> (CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool)
-> Eq (CacheInvalidateRequest n)
forall n.
Eq n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall n.
Eq n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
== :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
$c/= :: forall n.
Eq n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
/= :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
Eq)
data EventState n =
ES { forall n. EventState n -> [(n, ScrollRequest)]
esScrollRequests :: ![(n, ScrollRequest)]
, forall n. EventState n -> Set (CacheInvalidateRequest n)
cacheInvalidateRequests :: !(S.Set (CacheInvalidateRequest n))
, forall n. EventState n -> Set n
requestedVisibleNames :: !(S.Set n)
, forall n. EventState n -> NextAction
nextAction :: !NextAction
, forall n. EventState n -> VtyContext
vtyContext :: VtyContext
}
data VtyContext =
VtyContext { VtyContext -> IO Vty
vtyContextBuilder :: IO Vty
, VtyContext -> Vty
vtyContextHandle :: Vty
, VtyContext -> ThreadId
vtyContextThread :: ThreadId
, VtyContext -> Event -> IO ()
vtyContextPutEvent :: Event -> IO ()
}
data Extent n = Extent { forall n. Extent n -> n
extentName :: !n
, forall n. Extent n -> Location
extentUpperLeft :: !Location
, forall n. Extent n -> DisplayRegion
extentSize :: !(Int, Int)
}
deriving (Int -> Extent n -> ShowS
[Extent n] -> ShowS
Extent n -> String
(Int -> Extent n -> ShowS)
-> (Extent n -> String) -> ([Extent n] -> ShowS) -> Show (Extent n)
forall n. Show n => Int -> Extent n -> ShowS
forall n. Show n => [Extent n] -> ShowS
forall n. Show n => Extent n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> Extent n -> ShowS
showsPrec :: Int -> Extent n -> ShowS
$cshow :: forall n. Show n => Extent n -> String
show :: Extent n -> String
$cshowList :: forall n. Show n => [Extent n] -> ShowS
showList :: [Extent n] -> ShowS
Show, ReadPrec [Extent n]
ReadPrec (Extent n)
Int -> ReadS (Extent n)
ReadS [Extent n]
(Int -> ReadS (Extent n))
-> ReadS [Extent n]
-> ReadPrec (Extent n)
-> ReadPrec [Extent n]
-> Read (Extent n)
forall n. Read n => ReadPrec [Extent n]
forall n. Read n => ReadPrec (Extent n)
forall n. Read n => Int -> ReadS (Extent n)
forall n. Read n => ReadS [Extent n]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall n. Read n => Int -> ReadS (Extent n)
readsPrec :: Int -> ReadS (Extent n)
$creadList :: forall n. Read n => ReadS [Extent n]
readList :: ReadS [Extent n]
$creadPrec :: forall n. Read n => ReadPrec (Extent n)
readPrec :: ReadPrec (Extent n)
$creadListPrec :: forall n. Read n => ReadPrec [Extent n]
readListPrec :: ReadPrec [Extent n]
Read, (forall x. Extent n -> Rep (Extent n) x)
-> (forall x. Rep (Extent n) x -> Extent n) -> Generic (Extent n)
forall x. Rep (Extent n) x -> Extent n
forall x. Extent n -> Rep (Extent n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (Extent n) x -> Extent n
forall n x. Extent n -> Rep (Extent n) x
$cfrom :: forall n x. Extent n -> Rep (Extent n) x
from :: forall x. Extent n -> Rep (Extent n) x
$cto :: forall n x. Rep (Extent n) x -> Extent n
to :: forall x. Rep (Extent n) x -> Extent n
Generic, Extent n -> ()
(Extent n -> ()) -> NFData (Extent n)
forall n. NFData n => Extent n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => Extent n -> ()
rnf :: Extent n -> ()
NFData)
data NextAction =
Continue
| ContinueWithoutRedraw
| Halt
data Direction = Up
| Down
deriving (Int -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
(Int -> Direction -> ShowS)
-> (Direction -> String)
-> ([Direction] -> ShowS)
-> Show Direction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Direction -> ShowS
showsPrec :: Int -> Direction -> ShowS
$cshow :: Direction -> String
show :: Direction -> String
$cshowList :: [Direction] -> ShowS
showList :: [Direction] -> ShowS
Show, Direction -> Direction -> Bool
(Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool) -> Eq Direction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
/= :: Direction -> Direction -> Bool
Eq, ReadPrec [Direction]
ReadPrec Direction
Int -> ReadS Direction
ReadS [Direction]
(Int -> ReadS Direction)
-> ReadS [Direction]
-> ReadPrec Direction
-> ReadPrec [Direction]
-> Read Direction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Direction
readsPrec :: Int -> ReadS Direction
$creadList :: ReadS [Direction]
readList :: ReadS [Direction]
$creadPrec :: ReadPrec Direction
readPrec :: ReadPrec Direction
$creadListPrec :: ReadPrec [Direction]
readListPrec :: ReadPrec [Direction]
Read, (forall x. Direction -> Rep Direction x)
-> (forall x. Rep Direction x -> Direction) -> Generic Direction
forall x. Rep Direction x -> Direction
forall x. Direction -> Rep Direction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Direction -> Rep Direction x
from :: forall x. Direction -> Rep Direction x
$cto :: forall x. Rep Direction x -> Direction
to :: forall x. Rep Direction x -> Direction
Generic, Direction -> ()
(Direction -> ()) -> NFData Direction
forall a. (a -> ()) -> NFData a
$crnf :: Direction -> ()
rnf :: Direction -> ()
NFData)
class TerminalLocation a where
locationColumnL :: Lens' a Int
locationColumn :: a -> Int
locationRowL :: Lens' a Int
locationRow :: a -> Int
instance TerminalLocation Location where
locationColumnL :: Lens' Location Int
locationColumnL = (Int -> f Int) -> Location -> f Location
forall s t a b. Field1 s t a b => Lens s t a b
Lens' Location Int
_1
locationColumn :: Location -> Int
locationColumn (Location DisplayRegion
t) = DisplayRegion -> Int
forall a b. (a, b) -> a
fst DisplayRegion
t
locationRowL :: Lens' Location Int
locationRowL = (Int -> f Int) -> Location -> f Location
forall s t a b. Field2 s t a b => Lens s t a b
Lens' Location Int
_2
locationRow :: Location -> Int
locationRow (Location DisplayRegion
t) = DisplayRegion -> Int
forall a b. (a, b) -> b
snd DisplayRegion
t
data CursorLocation n =
CursorLocation { forall n. CursorLocation n -> Location
cursorLocation :: !Location
, forall n. CursorLocation n -> Maybe n
cursorLocationName :: !(Maybe n)
, forall n. CursorLocation n -> Bool
cursorLocationVisible :: !Bool
}
deriving (ReadPrec [CursorLocation n]
ReadPrec (CursorLocation n)
Int -> ReadS (CursorLocation n)
ReadS [CursorLocation n]
(Int -> ReadS (CursorLocation n))
-> ReadS [CursorLocation n]
-> ReadPrec (CursorLocation n)
-> ReadPrec [CursorLocation n]
-> Read (CursorLocation n)
forall n. Read n => ReadPrec [CursorLocation n]
forall n. Read n => ReadPrec (CursorLocation n)
forall n. Read n => Int -> ReadS (CursorLocation n)
forall n. Read n => ReadS [CursorLocation n]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall n. Read n => Int -> ReadS (CursorLocation n)
readsPrec :: Int -> ReadS (CursorLocation n)
$creadList :: forall n. Read n => ReadS [CursorLocation n]
readList :: ReadS [CursorLocation n]
$creadPrec :: forall n. Read n => ReadPrec (CursorLocation n)
readPrec :: ReadPrec (CursorLocation n)
$creadListPrec :: forall n. Read n => ReadPrec [CursorLocation n]
readListPrec :: ReadPrec [CursorLocation n]
Read, Int -> CursorLocation n -> ShowS
[CursorLocation n] -> ShowS
CursorLocation n -> String
(Int -> CursorLocation n -> ShowS)
-> (CursorLocation n -> String)
-> ([CursorLocation n] -> ShowS)
-> Show (CursorLocation n)
forall n. Show n => Int -> CursorLocation n -> ShowS
forall n. Show n => [CursorLocation n] -> ShowS
forall n. Show n => CursorLocation n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> CursorLocation n -> ShowS
showsPrec :: Int -> CursorLocation n -> ShowS
$cshow :: forall n. Show n => CursorLocation n -> String
show :: CursorLocation n -> String
$cshowList :: forall n. Show n => [CursorLocation n] -> ShowS
showList :: [CursorLocation n] -> ShowS
Show, (forall x. CursorLocation n -> Rep (CursorLocation n) x)
-> (forall x. Rep (CursorLocation n) x -> CursorLocation n)
-> Generic (CursorLocation n)
forall x. Rep (CursorLocation n) x -> CursorLocation n
forall x. CursorLocation n -> Rep (CursorLocation n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (CursorLocation n) x -> CursorLocation n
forall n x. CursorLocation n -> Rep (CursorLocation n) x
$cfrom :: forall n x. CursorLocation n -> Rep (CursorLocation n) x
from :: forall x. CursorLocation n -> Rep (CursorLocation n) x
$cto :: forall n x. Rep (CursorLocation n) x -> CursorLocation n
to :: forall x. Rep (CursorLocation n) x -> CursorLocation n
Generic, CursorLocation n -> ()
(CursorLocation n -> ()) -> NFData (CursorLocation n)
forall n. NFData n => CursorLocation n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => CursorLocation n -> ()
rnf :: CursorLocation n -> ()
NFData)
data BorderSegment = BorderSegment
{ BorderSegment -> Bool
bsAccept :: Bool
, BorderSegment -> Bool
bsOffer :: Bool
, BorderSegment -> Bool
bsDraw :: Bool
} deriving (BorderSegment -> BorderSegment -> Bool
(BorderSegment -> BorderSegment -> Bool)
-> (BorderSegment -> BorderSegment -> Bool) -> Eq BorderSegment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BorderSegment -> BorderSegment -> Bool
== :: BorderSegment -> BorderSegment -> Bool
$c/= :: BorderSegment -> BorderSegment -> Bool
/= :: BorderSegment -> BorderSegment -> Bool
Eq, Eq BorderSegment
Eq BorderSegment =>
(BorderSegment -> BorderSegment -> Ordering)
-> (BorderSegment -> BorderSegment -> Bool)
-> (BorderSegment -> BorderSegment -> Bool)
-> (BorderSegment -> BorderSegment -> Bool)
-> (BorderSegment -> BorderSegment -> Bool)
-> (BorderSegment -> BorderSegment -> BorderSegment)
-> (BorderSegment -> BorderSegment -> BorderSegment)
-> Ord BorderSegment
BorderSegment -> BorderSegment -> Bool
BorderSegment -> BorderSegment -> Ordering
BorderSegment -> BorderSegment -> BorderSegment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BorderSegment -> BorderSegment -> Ordering
compare :: BorderSegment -> BorderSegment -> Ordering
$c< :: BorderSegment -> BorderSegment -> Bool
< :: BorderSegment -> BorderSegment -> Bool
$c<= :: BorderSegment -> BorderSegment -> Bool
<= :: BorderSegment -> BorderSegment -> Bool
$c> :: BorderSegment -> BorderSegment -> Bool
> :: BorderSegment -> BorderSegment -> Bool
$c>= :: BorderSegment -> BorderSegment -> Bool
>= :: BorderSegment -> BorderSegment -> Bool
$cmax :: BorderSegment -> BorderSegment -> BorderSegment
max :: BorderSegment -> BorderSegment -> BorderSegment
$cmin :: BorderSegment -> BorderSegment -> BorderSegment
min :: BorderSegment -> BorderSegment -> BorderSegment
Ord, ReadPrec [BorderSegment]
ReadPrec BorderSegment
Int -> ReadS BorderSegment
ReadS [BorderSegment]
(Int -> ReadS BorderSegment)
-> ReadS [BorderSegment]
-> ReadPrec BorderSegment
-> ReadPrec [BorderSegment]
-> Read BorderSegment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BorderSegment
readsPrec :: Int -> ReadS BorderSegment
$creadList :: ReadS [BorderSegment]
readList :: ReadS [BorderSegment]
$creadPrec :: ReadPrec BorderSegment
readPrec :: ReadPrec BorderSegment
$creadListPrec :: ReadPrec [BorderSegment]
readListPrec :: ReadPrec [BorderSegment]
Read, Int -> BorderSegment -> ShowS
[BorderSegment] -> ShowS
BorderSegment -> String
(Int -> BorderSegment -> ShowS)
-> (BorderSegment -> String)
-> ([BorderSegment] -> ShowS)
-> Show BorderSegment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BorderSegment -> ShowS
showsPrec :: Int -> BorderSegment -> ShowS
$cshow :: BorderSegment -> String
show :: BorderSegment -> String
$cshowList :: [BorderSegment] -> ShowS
showList :: [BorderSegment] -> ShowS
Show, (forall x. BorderSegment -> Rep BorderSegment x)
-> (forall x. Rep BorderSegment x -> BorderSegment)
-> Generic BorderSegment
forall x. Rep BorderSegment x -> BorderSegment
forall x. BorderSegment -> Rep BorderSegment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BorderSegment -> Rep BorderSegment x
from :: forall x. BorderSegment -> Rep BorderSegment x
$cto :: forall x. Rep BorderSegment x -> BorderSegment
to :: forall x. Rep BorderSegment x -> BorderSegment
Generic, BorderSegment -> ()
(BorderSegment -> ()) -> NFData BorderSegment
forall a. (a -> ()) -> NFData a
$crnf :: BorderSegment -> ()
rnf :: BorderSegment -> ()
NFData)
data DynBorder = DynBorder
{ DynBorder -> BorderStyle
dbStyle :: BorderStyle
, DynBorder -> Attr
dbAttr :: Attr
, DynBorder -> Edges BorderSegment
dbSegments :: Edges BorderSegment
} deriving (DynBorder -> DynBorder -> Bool
(DynBorder -> DynBorder -> Bool)
-> (DynBorder -> DynBorder -> Bool) -> Eq DynBorder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DynBorder -> DynBorder -> Bool
== :: DynBorder -> DynBorder -> Bool
$c/= :: DynBorder -> DynBorder -> Bool
/= :: DynBorder -> DynBorder -> Bool
Eq, ReadPrec [DynBorder]
ReadPrec DynBorder
Int -> ReadS DynBorder
ReadS [DynBorder]
(Int -> ReadS DynBorder)
-> ReadS [DynBorder]
-> ReadPrec DynBorder
-> ReadPrec [DynBorder]
-> Read DynBorder
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DynBorder
readsPrec :: Int -> ReadS DynBorder
$creadList :: ReadS [DynBorder]
readList :: ReadS [DynBorder]
$creadPrec :: ReadPrec DynBorder
readPrec :: ReadPrec DynBorder
$creadListPrec :: ReadPrec [DynBorder]
readListPrec :: ReadPrec [DynBorder]
Read, Int -> DynBorder -> ShowS
[DynBorder] -> ShowS
DynBorder -> String
(Int -> DynBorder -> ShowS)
-> (DynBorder -> String)
-> ([DynBorder] -> ShowS)
-> Show DynBorder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DynBorder -> ShowS
showsPrec :: Int -> DynBorder -> ShowS
$cshow :: DynBorder -> String
show :: DynBorder -> String
$cshowList :: [DynBorder] -> ShowS
showList :: [DynBorder] -> ShowS
Show, (forall x. DynBorder -> Rep DynBorder x)
-> (forall x. Rep DynBorder x -> DynBorder) -> Generic DynBorder
forall x. Rep DynBorder x -> DynBorder
forall x. DynBorder -> Rep DynBorder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DynBorder -> Rep DynBorder x
from :: forall x. DynBorder -> Rep DynBorder x
$cto :: forall x. Rep DynBorder x -> DynBorder
to :: forall x. Rep DynBorder x -> DynBorder
Generic, DynBorder -> ()
(DynBorder -> ()) -> NFData DynBorder
forall a. (a -> ()) -> NFData a
$crnf :: DynBorder -> ()
rnf :: DynBorder -> ()
NFData)
data Result n =
Result { forall n. Result n -> Image
image :: !Image
, forall n. Result n -> [CursorLocation n]
cursors :: ![CursorLocation n]
, forall n. Result n -> [VisibilityRequest]
visibilityRequests :: ![VisibilityRequest]
, forall n. Result n -> [Extent n]
extents :: ![Extent n]
, forall n. Result n -> BorderMap DynBorder
borders :: !(BorderMap DynBorder)
}
deriving (Int -> Result n -> ShowS
[Result n] -> ShowS
Result n -> String
(Int -> Result n -> ShowS)
-> (Result n -> String) -> ([Result n] -> ShowS) -> Show (Result n)
forall n. Show n => Int -> Result n -> ShowS
forall n. Show n => [Result n] -> ShowS
forall n. Show n => Result n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall n. Show n => Int -> Result n -> ShowS
showsPrec :: Int -> Result n -> ShowS
$cshow :: forall n. Show n => Result n -> String
show :: Result n -> String
$cshowList :: forall n. Show n => [Result n] -> ShowS
showList :: [Result n] -> ShowS
Show, ReadPrec [Result n]
ReadPrec (Result n)
Int -> ReadS (Result n)
ReadS [Result n]
(Int -> ReadS (Result n))
-> ReadS [Result n]
-> ReadPrec (Result n)
-> ReadPrec [Result n]
-> Read (Result n)
forall n. Read n => ReadPrec [Result n]
forall n. Read n => ReadPrec (Result n)
forall n. Read n => Int -> ReadS (Result n)
forall n. Read n => ReadS [Result n]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall n. Read n => Int -> ReadS (Result n)
readsPrec :: Int -> ReadS (Result n)
$creadList :: forall n. Read n => ReadS [Result n]
readList :: ReadS [Result n]
$creadPrec :: forall n. Read n => ReadPrec (Result n)
readPrec :: ReadPrec (Result n)
$creadListPrec :: forall n. Read n => ReadPrec [Result n]
readListPrec :: ReadPrec [Result n]
Read, (forall x. Result n -> Rep (Result n) x)
-> (forall x. Rep (Result n) x -> Result n) -> Generic (Result n)
forall x. Rep (Result n) x -> Result n
forall x. Result n -> Rep (Result n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall n x. Rep (Result n) x -> Result n
forall n x. Result n -> Rep (Result n) x
$cfrom :: forall n x. Result n -> Rep (Result n) x
from :: forall x. Result n -> Rep (Result n) x
$cto :: forall n x. Rep (Result n) x -> Result n
to :: forall x. Rep (Result n) x -> Result n
Generic, Result n -> ()
(Result n -> ()) -> NFData (Result n)
forall n. NFData n => Result n -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall n. NFData n => Result n -> ()
rnf :: Result n -> ()
NFData)
emptyResult :: Result n
emptyResult :: forall n. Result n
emptyResult =
Result { image :: Image
image = Image
emptyImage
, cursors :: [CursorLocation n]
cursors = []
, visibilityRequests :: [VisibilityRequest]
visibilityRequests = []
, extents :: [Extent n]
extents = []
, borders :: BorderMap DynBorder
borders = BorderMap DynBorder
forall a. BorderMap a
BM.empty
}
data BrickEvent n e = VtyEvent Event
| AppEvent e
| MouseDown n Button [Modifier] Location
| MouseUp n (Maybe Button) Location
deriving (Int -> BrickEvent n e -> ShowS
[BrickEvent n e] -> ShowS
BrickEvent n e -> String
(Int -> BrickEvent n e -> ShowS)
-> (BrickEvent n e -> String)
-> ([BrickEvent n e] -> ShowS)
-> Show (BrickEvent n e)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall n e. (Show e, Show n) => Int -> BrickEvent n e -> ShowS
forall n e. (Show e, Show n) => [BrickEvent n e] -> ShowS
forall n e. (Show e, Show n) => BrickEvent n e -> String
$cshowsPrec :: forall n e. (Show e, Show n) => Int -> BrickEvent n e -> ShowS
showsPrec :: Int -> BrickEvent n e -> ShowS
$cshow :: forall n e. (Show e, Show n) => BrickEvent n e -> String
show :: BrickEvent n e -> String
$cshowList :: forall n e. (Show e, Show n) => [BrickEvent n e] -> ShowS
showList :: [BrickEvent n e] -> ShowS
Show, BrickEvent n e -> BrickEvent n e -> Bool
(BrickEvent n e -> BrickEvent n e -> Bool)
-> (BrickEvent n e -> BrickEvent n e -> Bool)
-> Eq (BrickEvent n e)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall n e.
(Eq e, Eq n) =>
BrickEvent n e -> BrickEvent n e -> Bool
$c== :: forall n e.
(Eq e, Eq n) =>
BrickEvent n e -> BrickEvent n e -> Bool
== :: BrickEvent n e -> BrickEvent n e -> Bool
$c/= :: forall n e.
(Eq e, Eq n) =>
BrickEvent n e -> BrickEvent n e -> Bool
/= :: BrickEvent n e -> BrickEvent n e -> Bool
Eq, Eq (BrickEvent n e)
Eq (BrickEvent n e) =>
(BrickEvent n e -> BrickEvent n e -> Ordering)
-> (BrickEvent n e -> BrickEvent n e -> Bool)
-> (BrickEvent n e -> BrickEvent n e -> Bool)
-> (BrickEvent n e -> BrickEvent n e -> Bool)
-> (BrickEvent n e -> BrickEvent n e -> Bool)
-> (BrickEvent n e -> BrickEvent n e -> BrickEvent n e)
-> (BrickEvent n e -> BrickEvent n e -> BrickEvent n e)
-> Ord (BrickEvent n e)
BrickEvent n e -> BrickEvent n e -> Bool
BrickEvent n e -> BrickEvent n e -> Ordering
BrickEvent n e -> BrickEvent n e -> BrickEvent n e
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall n e. (Ord e, Ord n) => Eq (BrickEvent n e)
forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Bool
forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Ordering
forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> BrickEvent n e
$ccompare :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Ordering
compare :: BrickEvent n e -> BrickEvent n e -> Ordering
$c< :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Bool
< :: BrickEvent n e -> BrickEvent n e -> Bool
$c<= :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Bool
<= :: BrickEvent n e -> BrickEvent n e -> Bool
$c> :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Bool
> :: BrickEvent n e -> BrickEvent n e -> Bool
$c>= :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Bool
>= :: BrickEvent n e -> BrickEvent n e -> Bool
$cmax :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> BrickEvent n e
max :: BrickEvent n e -> BrickEvent n e -> BrickEvent n e
$cmin :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> BrickEvent n e
min :: BrickEvent n e -> BrickEvent n e -> BrickEvent n e
Ord)
data EventRO n = EventRO { forall n. EventRO n -> Map n Viewport
eventViewportMap :: M.Map n Viewport
, forall n. EventRO n -> [Extent n]
latestExtents :: [Extent n]
, forall n. EventRO n -> RenderState n
oldState :: RenderState n
}
data ClickableScrollbarElement =
SBHandleBefore
| SBHandleAfter
| SBBar
| SBTroughBefore
| SBTroughAfter
deriving (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
(ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> Eq ClickableScrollbarElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
== :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$c/= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
/= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
Eq, Int -> ClickableScrollbarElement -> ShowS
[ClickableScrollbarElement] -> ShowS
ClickableScrollbarElement -> String
(Int -> ClickableScrollbarElement -> ShowS)
-> (ClickableScrollbarElement -> String)
-> ([ClickableScrollbarElement] -> ShowS)
-> Show ClickableScrollbarElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClickableScrollbarElement -> ShowS
showsPrec :: Int -> ClickableScrollbarElement -> ShowS
$cshow :: ClickableScrollbarElement -> String
show :: ClickableScrollbarElement -> String
$cshowList :: [ClickableScrollbarElement] -> ShowS
showList :: [ClickableScrollbarElement] -> ShowS
Show, Eq ClickableScrollbarElement
Eq ClickableScrollbarElement =>
(ClickableScrollbarElement
-> ClickableScrollbarElement -> Ordering)
-> (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> (ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement)
-> (ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement)
-> Ord ClickableScrollbarElement
ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
ClickableScrollbarElement -> ClickableScrollbarElement -> Ordering
ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ClickableScrollbarElement -> ClickableScrollbarElement -> Ordering
compare :: ClickableScrollbarElement -> ClickableScrollbarElement -> Ordering
$c< :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
< :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$c<= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
<= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$c> :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
> :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$c>= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
>= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$cmax :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
max :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
$cmin :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
min :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
Ord)
data Context n =
Context { forall n. Context n -> AttrName
ctxAttrName :: AttrName
, forall n. Context n -> Int
availWidth :: Int
, forall n. Context n -> Int
availHeight :: Int
, forall n. Context n -> Int
windowWidth :: Int
, forall n. Context n -> Int
windowHeight :: Int
, forall n. Context n -> BorderStyle
ctxBorderStyle :: BorderStyle
, forall n. Context n -> AttrMap
ctxAttrMap :: AttrMap
, forall n. Context n -> Bool
ctxDynBorders :: Bool
, forall n. Context n -> Maybe VScrollBarOrientation
ctxVScrollBarOrientation :: Maybe VScrollBarOrientation
, forall n. Context n -> Maybe (VScrollbarRenderer n)
ctxVScrollBarRenderer :: Maybe (VScrollbarRenderer n)
, forall n. Context n -> Maybe HScrollBarOrientation
ctxHScrollBarOrientation :: Maybe HScrollBarOrientation
, forall n. Context n -> Maybe (HScrollbarRenderer n)
ctxHScrollBarRenderer :: Maybe (HScrollbarRenderer n)
, forall n. Context n -> Bool
ctxVScrollBarShowHandles :: Bool
, forall n. Context n -> Bool
ctxHScrollBarShowHandles :: Bool
, forall n. Context n -> Maybe (ClickableScrollbarElement -> n -> n)
ctxVScrollBarClickableConstr :: Maybe (ClickableScrollbarElement -> n -> n)
, forall n. Context n -> Maybe (ClickableScrollbarElement -> n -> n)
ctxHScrollBarClickableConstr :: Maybe (ClickableScrollbarElement -> n -> n)
}
suffixLenses ''VisibilityRequest
suffixLenses ''CursorLocation
suffixLenses ''Context
suffixLenses ''DynBorder
suffixLenses ''Result
suffixLenses ''BorderSegment
makeLenses ''Viewport
lookupReportedExtent :: (Ord n) => n -> RenderM n (Maybe (Extent n))
lookupReportedExtent :: forall n. Ord n => n -> RenderM n (Maybe (Extent n))
lookupReportedExtent n
n = do
Map n (Extent n)
m <- State (RenderState n) (Map n (Extent n))
-> ReaderT (Context n) (State (RenderState n)) (Map n (Extent n))
forall (m :: * -> *) a. Monad m => m a -> ReaderT (Context n) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (State (RenderState n) (Map n (Extent n))
-> ReaderT (Context n) (State (RenderState n)) (Map n (Extent n)))
-> State (RenderState n) (Map n (Extent n))
-> ReaderT (Context n) (State (RenderState n)) (Map n (Extent n))
forall a b. (a -> b) -> a -> b
$ Getting (Map n (Extent n)) (RenderState n) (Map n (Extent n))
-> State (RenderState n) (Map n (Extent n))
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Map n (Extent n)) (RenderState n) (Map n (Extent n))
forall n (f :: * -> *).
Functor f =>
(Map n (Extent n) -> f (Map n (Extent n)))
-> RenderState n -> f (RenderState n)
reportedExtentsL
Maybe (Extent n) -> RenderM n (Maybe (Extent n))
forall a. a -> ReaderT (Context n) (State (RenderState n)) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Extent n) -> RenderM n (Maybe (Extent n)))
-> Maybe (Extent n) -> RenderM n (Maybe (Extent n))
forall a b. (a -> b) -> a -> b
$ n -> Map n (Extent n) -> Maybe (Extent n)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup n
n Map n (Extent n)
m