{-# 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(..)
, ScrollbarRenderer(..)
, 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]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScrollRequest]
$creadListPrec :: ReadPrec [ScrollRequest]
readPrec :: ReadPrec ScrollRequest
$creadPrec :: ReadPrec ScrollRequest
readList :: ReadS [ScrollRequest]
$creadList :: ReadS [ScrollRequest]
readsPrec :: Int -> ReadS ScrollRequest
$creadsPrec :: Int -> ReadS ScrollRequest
Read, Int -> ScrollRequest -> ShowS
[ScrollRequest] -> ShowS
ScrollRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScrollRequest] -> ShowS
$cshowList :: [ScrollRequest] -> ShowS
show :: ScrollRequest -> String
$cshow :: ScrollRequest -> String
showsPrec :: Int -> ScrollRequest -> ShowS
$cshowsPrec :: Int -> ScrollRequest -> ShowS
Show, 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
$cto :: forall x. Rep ScrollRequest x -> ScrollRequest
$cfrom :: forall x. ScrollRequest -> Rep ScrollRequest x
Generic, ScrollRequest -> ()
forall a. (a -> ()) -> NFData a
rnf :: ScrollRequest -> ()
$crnf :: ScrollRequest -> ()
NFData)
data Size = Fixed
| Greedy
deriving (Int -> Size -> ShowS
[Size] -> ShowS
Size -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Size] -> ShowS
$cshowList :: [Size] -> ShowS
show :: Size -> String
$cshow :: Size -> String
showsPrec :: Int -> Size -> ShowS
$cshowsPrec :: Int -> Size -> ShowS
Show, Size -> Size -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Size -> Size -> Bool
$c/= :: Size -> Size -> Bool
== :: Size -> Size -> Bool
$c== :: Size -> Size -> Bool
Eq, Eq 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
min :: Size -> Size -> Size
$cmin :: Size -> Size -> Size
max :: Size -> Size -> Size
$cmax :: Size -> Size -> Size
>= :: Size -> Size -> Bool
$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
compare :: Size -> Size -> Ordering
$ccompare :: Size -> Size -> Ordering
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)
ReadS [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
readListPrec :: ReadPrec [RenderState n]
$creadListPrec :: forall n. (Ord n, Read n) => ReadPrec [RenderState n]
readPrec :: ReadPrec (RenderState n)
$creadPrec :: forall n. (Ord n, Read n) => ReadPrec (RenderState n)
readList :: ReadS [RenderState n]
$creadList :: forall n. (Ord n, Read n) => ReadS [RenderState n]
readsPrec :: Int -> ReadS (RenderState n)
$creadsPrec :: forall n. (Ord n, Read n) => Int -> ReadS (RenderState n)
Read, Int -> RenderState n -> ShowS
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
showList :: [RenderState n] -> ShowS
$cshowList :: forall n. Show n => [RenderState n] -> ShowS
show :: RenderState n -> String
$cshow :: forall n. Show n => RenderState n -> String
showsPrec :: Int -> RenderState n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> RenderState n -> ShowS
Show, 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
$cto :: forall n x. Rep (RenderState n) x -> RenderState n
$cfrom :: forall n x. RenderState n -> Rep (RenderState n) x
Generic, forall n. NFData n => RenderState n -> ()
forall a. (a -> ()) -> NFData a
rnf :: RenderState n -> ()
$crnf :: forall n. NFData n => 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 = forall r (m :: * -> *). MonadReader r m => m r
ask
data VScrollBarOrientation = OnLeft | OnRight
deriving (Int -> VScrollBarOrientation -> ShowS
[VScrollBarOrientation] -> ShowS
VScrollBarOrientation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VScrollBarOrientation] -> ShowS
$cshowList :: [VScrollBarOrientation] -> ShowS
show :: VScrollBarOrientation -> String
$cshow :: VScrollBarOrientation -> String
showsPrec :: Int -> VScrollBarOrientation -> ShowS
$cshowsPrec :: Int -> VScrollBarOrientation -> ShowS
Show, VScrollBarOrientation -> VScrollBarOrientation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
$c/= :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
== :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
$c== :: VScrollBarOrientation -> VScrollBarOrientation -> Bool
Eq)
data HScrollBarOrientation = OnBottom | OnTop
deriving (Int -> HScrollBarOrientation -> ShowS
[HScrollBarOrientation] -> ShowS
HScrollBarOrientation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HScrollBarOrientation] -> ShowS
$cshowList :: [HScrollBarOrientation] -> ShowS
show :: HScrollBarOrientation -> String
$cshow :: HScrollBarOrientation -> String
showsPrec :: Int -> HScrollBarOrientation -> ShowS
$cshowsPrec :: Int -> HScrollBarOrientation -> ShowS
Show, HScrollBarOrientation -> HScrollBarOrientation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
$c/= :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
== :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
$c== :: HScrollBarOrientation -> HScrollBarOrientation -> Bool
Eq)
data ScrollbarRenderer n =
ScrollbarRenderer { forall n. ScrollbarRenderer n -> Widget n
renderScrollbar :: Widget n
, forall n. ScrollbarRenderer n -> Widget n
renderScrollbarTrough :: Widget n
, forall n. ScrollbarRenderer n -> Widget n
renderScrollbarHandleBefore :: Widget n
, forall n. ScrollbarRenderer n -> Widget n
renderScrollbarHandleAfter :: Widget n
}
data VisibilityRequest =
VR { VisibilityRequest -> Location
vrPosition :: Location
, VisibilityRequest -> (Int, Int)
vrSize :: DisplayRegion
}
deriving (Int -> VisibilityRequest -> ShowS
[VisibilityRequest] -> ShowS
VisibilityRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VisibilityRequest] -> ShowS
$cshowList :: [VisibilityRequest] -> ShowS
show :: VisibilityRequest -> String
$cshow :: VisibilityRequest -> String
showsPrec :: Int -> VisibilityRequest -> ShowS
$cshowsPrec :: Int -> VisibilityRequest -> ShowS
Show, VisibilityRequest -> VisibilityRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VisibilityRequest -> VisibilityRequest -> Bool
$c/= :: VisibilityRequest -> VisibilityRequest -> Bool
== :: VisibilityRequest -> VisibilityRequest -> Bool
$c== :: VisibilityRequest -> VisibilityRequest -> Bool
Eq, ReadPrec [VisibilityRequest]
ReadPrec VisibilityRequest
Int -> ReadS VisibilityRequest
ReadS [VisibilityRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VisibilityRequest]
$creadListPrec :: ReadPrec [VisibilityRequest]
readPrec :: ReadPrec VisibilityRequest
$creadPrec :: ReadPrec VisibilityRequest
readList :: ReadS [VisibilityRequest]
$creadList :: ReadS [VisibilityRequest]
readsPrec :: Int -> ReadS VisibilityRequest
$creadsPrec :: Int -> ReadS VisibilityRequest
Read, 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
$cto :: forall x. Rep VisibilityRequest x -> VisibilityRequest
$cfrom :: forall x. VisibilityRequest -> Rep VisibilityRequest x
Generic, VisibilityRequest -> ()
forall a. (a -> ()) -> NFData a
rnf :: VisibilityRequest -> ()
$crnf :: VisibilityRequest -> ()
NFData)
data Viewport =
VP { Viewport -> Int
_vpLeft :: Int
, Viewport -> Int
_vpTop :: Int
, Viewport -> (Int, Int)
_vpSize :: DisplayRegion
, Viewport -> (Int, Int)
_vpContentSize :: DisplayRegion
}
deriving (Int -> Viewport -> ShowS
[Viewport] -> ShowS
Viewport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Viewport] -> ShowS
$cshowList :: [Viewport] -> ShowS
show :: Viewport -> String
$cshow :: Viewport -> String
showsPrec :: Int -> Viewport -> ShowS
$cshowsPrec :: Int -> Viewport -> ShowS
Show, ReadPrec [Viewport]
ReadPrec Viewport
Int -> ReadS Viewport
ReadS [Viewport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Viewport]
$creadListPrec :: ReadPrec [Viewport]
readPrec :: ReadPrec Viewport
$creadPrec :: ReadPrec Viewport
readList :: ReadS [Viewport]
$creadList :: ReadS [Viewport]
readsPrec :: Int -> ReadS Viewport
$creadsPrec :: Int -> ReadS Viewport
Read, 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
$cto :: forall x. Rep Viewport x -> Viewport
$cfrom :: forall x. Viewport -> Rep Viewport x
Generic, Viewport -> ()
forall a. (a -> ()) -> NFData a
rnf :: Viewport -> ()
$crnf :: Viewport -> ()
NFData)
data ViewportType =
Vertical
| Horizontal
| Both
deriving (Int -> ViewportType -> ShowS
[ViewportType] -> ShowS
ViewportType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ViewportType] -> ShowS
$cshowList :: [ViewportType] -> ShowS
show :: ViewportType -> String
$cshow :: ViewportType -> String
showsPrec :: Int -> ViewportType -> ShowS
$cshowsPrec :: Int -> ViewportType -> ShowS
Show, ViewportType -> ViewportType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ViewportType -> ViewportType -> Bool
$c/= :: ViewportType -> ViewportType -> Bool
== :: ViewportType -> ViewportType -> Bool
$c== :: ViewportType -> ViewportType -> Bool
Eq)
data CacheInvalidateRequest n =
InvalidateSingle n
| InvalidateEntire
deriving (CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering
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
min :: CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
$cmin :: forall n.
Ord n =>
CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
max :: CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
$cmax :: forall n.
Ord n =>
CacheInvalidateRequest n
-> CacheInvalidateRequest n -> CacheInvalidateRequest n
>= :: 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
$c< :: forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
compare :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering
$ccompare :: forall n.
Ord n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Ordering
Ord, CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
forall n.
Eq n =>
CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CacheInvalidateRequest n -> CacheInvalidateRequest n -> Bool
$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
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 -> (Int, Int)
extentSize :: !(Int, Int)
}
deriving (Int -> Extent n -> ShowS
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
showList :: [Extent n] -> ShowS
$cshowList :: forall n. Show n => [Extent n] -> ShowS
show :: Extent n -> String
$cshow :: forall n. Show n => Extent n -> String
showsPrec :: Int -> Extent n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> Extent n -> ShowS
Show, ReadPrec [Extent n]
ReadPrec (Extent n)
ReadS [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
readListPrec :: ReadPrec [Extent n]
$creadListPrec :: forall n. Read n => ReadPrec [Extent n]
readPrec :: ReadPrec (Extent n)
$creadPrec :: forall n. Read n => ReadPrec (Extent n)
readList :: ReadS [Extent n]
$creadList :: forall n. Read n => ReadS [Extent n]
readsPrec :: Int -> ReadS (Extent n)
$creadsPrec :: forall n. Read n => Int -> ReadS (Extent n)
Read, 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
$cto :: forall n x. Rep (Extent n) x -> Extent n
$cfrom :: forall n x. Extent n -> Rep (Extent n) x
Generic, forall n. NFData n => Extent n -> ()
forall a. (a -> ()) -> NFData a
rnf :: Extent n -> ()
$crnf :: forall n. NFData n => Extent n -> ()
NFData)
data NextAction =
Continue
| ContinueWithoutRedraw
| Halt
data Direction = Up
| Down
deriving (Int -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Direction] -> ShowS
$cshowList :: [Direction] -> ShowS
show :: Direction -> String
$cshow :: Direction -> String
showsPrec :: Int -> Direction -> ShowS
$cshowsPrec :: Int -> Direction -> ShowS
Show, Direction -> Direction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c== :: Direction -> Direction -> Bool
Eq, ReadPrec [Direction]
ReadPrec Direction
Int -> ReadS Direction
ReadS [Direction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Direction]
$creadListPrec :: ReadPrec [Direction]
readPrec :: ReadPrec Direction
$creadPrec :: ReadPrec Direction
readList :: ReadS [Direction]
$creadList :: ReadS [Direction]
readsPrec :: Int -> ReadS Direction
$creadsPrec :: Int -> ReadS Direction
Read, 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
$cto :: forall x. Rep Direction x -> Direction
$cfrom :: forall x. Direction -> Rep Direction x
Generic, Direction -> ()
forall a. (a -> ()) -> NFData a
rnf :: Direction -> ()
$crnf :: 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 = forall s t a b. Field1 s t a b => Lens s t a b
_1
locationColumn :: Location -> Int
locationColumn (Location (Int, Int)
t) = forall a b. (a, b) -> a
fst (Int, Int)
t
locationRowL :: Lens' Location Int
locationRowL = forall s t a b. Field2 s t a b => Lens s t a b
_2
locationRow :: Location -> Int
locationRow (Location (Int, Int)
t) = forall a b. (a, b) -> b
snd (Int, Int)
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)
ReadS [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
readListPrec :: ReadPrec [CursorLocation n]
$creadListPrec :: forall n. Read n => ReadPrec [CursorLocation n]
readPrec :: ReadPrec (CursorLocation n)
$creadPrec :: forall n. Read n => ReadPrec (CursorLocation n)
readList :: ReadS [CursorLocation n]
$creadList :: forall n. Read n => ReadS [CursorLocation n]
readsPrec :: Int -> ReadS (CursorLocation n)
$creadsPrec :: forall n. Read n => Int -> ReadS (CursorLocation n)
Read, Int -> CursorLocation n -> ShowS
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
showList :: [CursorLocation n] -> ShowS
$cshowList :: forall n. Show n => [CursorLocation n] -> ShowS
show :: CursorLocation n -> String
$cshow :: forall n. Show n => CursorLocation n -> String
showsPrec :: Int -> CursorLocation n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> CursorLocation n -> ShowS
Show, 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
$cto :: forall n x. Rep (CursorLocation n) x -> CursorLocation n
$cfrom :: forall n x. CursorLocation n -> Rep (CursorLocation n) x
Generic, forall n. NFData n => CursorLocation n -> ()
forall a. (a -> ()) -> NFData a
rnf :: CursorLocation n -> ()
$crnf :: forall n. NFData n => CursorLocation n -> ()
NFData)
data BorderSegment = BorderSegment
{ BorderSegment -> Bool
bsAccept :: Bool
, BorderSegment -> Bool
bsOffer :: Bool
, BorderSegment -> Bool
bsDraw :: Bool
} deriving (BorderSegment -> BorderSegment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BorderSegment -> BorderSegment -> Bool
$c/= :: BorderSegment -> BorderSegment -> Bool
== :: BorderSegment -> BorderSegment -> Bool
$c== :: BorderSegment -> BorderSegment -> Bool
Eq, Eq 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
min :: BorderSegment -> BorderSegment -> BorderSegment
$cmin :: BorderSegment -> BorderSegment -> BorderSegment
max :: BorderSegment -> BorderSegment -> BorderSegment
$cmax :: BorderSegment -> BorderSegment -> BorderSegment
>= :: BorderSegment -> BorderSegment -> Bool
$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
compare :: BorderSegment -> BorderSegment -> Ordering
$ccompare :: BorderSegment -> BorderSegment -> Ordering
Ord, ReadPrec [BorderSegment]
ReadPrec BorderSegment
Int -> ReadS BorderSegment
ReadS [BorderSegment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BorderSegment]
$creadListPrec :: ReadPrec [BorderSegment]
readPrec :: ReadPrec BorderSegment
$creadPrec :: ReadPrec BorderSegment
readList :: ReadS [BorderSegment]
$creadList :: ReadS [BorderSegment]
readsPrec :: Int -> ReadS BorderSegment
$creadsPrec :: Int -> ReadS BorderSegment
Read, Int -> BorderSegment -> ShowS
[BorderSegment] -> ShowS
BorderSegment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BorderSegment] -> ShowS
$cshowList :: [BorderSegment] -> ShowS
show :: BorderSegment -> String
$cshow :: BorderSegment -> String
showsPrec :: Int -> BorderSegment -> ShowS
$cshowsPrec :: Int -> BorderSegment -> ShowS
Show, 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
$cto :: forall x. Rep BorderSegment x -> BorderSegment
$cfrom :: forall x. BorderSegment -> Rep BorderSegment x
Generic, BorderSegment -> ()
forall a. (a -> ()) -> NFData a
rnf :: BorderSegment -> ()
$crnf :: BorderSegment -> ()
NFData)
data DynBorder = DynBorder
{ DynBorder -> BorderStyle
dbStyle :: BorderStyle
, DynBorder -> Attr
dbAttr :: Attr
, DynBorder -> Edges BorderSegment
dbSegments :: Edges BorderSegment
} deriving (DynBorder -> DynBorder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DynBorder -> DynBorder -> Bool
$c/= :: DynBorder -> DynBorder -> Bool
== :: DynBorder -> DynBorder -> Bool
$c== :: DynBorder -> DynBorder -> Bool
Eq, ReadPrec [DynBorder]
ReadPrec DynBorder
Int -> ReadS DynBorder
ReadS [DynBorder]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DynBorder]
$creadListPrec :: ReadPrec [DynBorder]
readPrec :: ReadPrec DynBorder
$creadPrec :: ReadPrec DynBorder
readList :: ReadS [DynBorder]
$creadList :: ReadS [DynBorder]
readsPrec :: Int -> ReadS DynBorder
$creadsPrec :: Int -> ReadS DynBorder
Read, Int -> DynBorder -> ShowS
[DynBorder] -> ShowS
DynBorder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DynBorder] -> ShowS
$cshowList :: [DynBorder] -> ShowS
show :: DynBorder -> String
$cshow :: DynBorder -> String
showsPrec :: Int -> DynBorder -> ShowS
$cshowsPrec :: Int -> DynBorder -> ShowS
Show, 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
$cto :: forall x. Rep DynBorder x -> DynBorder
$cfrom :: forall x. DynBorder -> Rep DynBorder x
Generic, DynBorder -> ()
forall a. (a -> ()) -> NFData a
rnf :: DynBorder -> ()
$crnf :: 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
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
showList :: [Result n] -> ShowS
$cshowList :: forall n. Show n => [Result n] -> ShowS
show :: Result n -> String
$cshow :: forall n. Show n => Result n -> String
showsPrec :: Int -> Result n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> Result n -> ShowS
Show, ReadPrec [Result n]
ReadPrec (Result n)
ReadS [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
readListPrec :: ReadPrec [Result n]
$creadListPrec :: forall n. Read n => ReadPrec [Result n]
readPrec :: ReadPrec (Result n)
$creadPrec :: forall n. Read n => ReadPrec (Result n)
readList :: ReadS [Result n]
$creadList :: forall n. Read n => ReadS [Result n]
readsPrec :: Int -> ReadS (Result n)
$creadsPrec :: forall n. Read n => Int -> ReadS (Result n)
Read, 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
$cto :: forall n x. Rep (Result n) x -> Result n
$cfrom :: forall n x. Result n -> Rep (Result n) x
Generic, forall n. NFData n => Result n -> ()
forall a. (a -> ()) -> NFData a
rnf :: Result n -> ()
$crnf :: forall n. NFData n => 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 = 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
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
showList :: [BrickEvent n e] -> ShowS
$cshowList :: forall n e. (Show e, Show n) => [BrickEvent n e] -> ShowS
show :: BrickEvent n e -> String
$cshow :: forall n e. (Show e, Show n) => BrickEvent n e -> String
showsPrec :: Int -> BrickEvent n e -> ShowS
$cshowsPrec :: forall n e. (Show e, Show n) => Int -> BrickEvent n e -> ShowS
Show, BrickEvent n e -> BrickEvent n e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
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
$c== :: forall n e.
(Eq e, Eq n) =>
BrickEvent n e -> BrickEvent n e -> Bool
Eq, BrickEvent n e -> BrickEvent n e -> Ordering
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
min :: 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
max :: BrickEvent n e -> BrickEvent n e -> BrickEvent n e
$cmax :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> BrickEvent n e
>= :: 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
$c< :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Bool
compare :: BrickEvent n e -> BrickEvent n e -> Ordering
$ccompare :: forall n e.
(Ord e, Ord n) =>
BrickEvent n e -> BrickEvent n e -> Ordering
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$c/= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
== :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$c== :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
Eq, Int -> ClickableScrollbarElement -> ShowS
[ClickableScrollbarElement] -> ShowS
ClickableScrollbarElement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClickableScrollbarElement] -> ShowS
$cshowList :: [ClickableScrollbarElement] -> ShowS
show :: ClickableScrollbarElement -> String
$cshow :: ClickableScrollbarElement -> String
showsPrec :: Int -> ClickableScrollbarElement -> ShowS
$cshowsPrec :: Int -> ClickableScrollbarElement -> ShowS
Show, Eq 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
min :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
$cmin :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
max :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
$cmax :: ClickableScrollbarElement
-> ClickableScrollbarElement -> ClickableScrollbarElement
>= :: ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
$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
compare :: ClickableScrollbarElement -> ClickableScrollbarElement -> Ordering
$ccompare :: ClickableScrollbarElement -> ClickableScrollbarElement -> Ordering
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 (ScrollbarRenderer n)
ctxVScrollBarRenderer :: Maybe (ScrollbarRenderer n)
, forall n. Context n -> Maybe HScrollBarOrientation
ctxHScrollBarOrientation :: Maybe HScrollBarOrientation
, forall n. Context n -> Maybe (ScrollbarRenderer n)
ctxHScrollBarRenderer :: Maybe (ScrollbarRenderer 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 <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use forall n. Lens' (RenderState n) (Map n (Extent n))
reportedExtentsL
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup n
n Map n (Extent n)
m