{-# 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(..)
  , EventRO(..)
  , Next(..)
  , Result(..)
  , Extent(..)
  , Edges(..)
  , eTopL, eBottomL, eRightL, eLeftL
  , BorderSegment(..)
  , bsAcceptL, bsOfferL, bsDrawL
  , DynBorder(..)
  , dbStyleL, dbAttrL, dbSegmentsL
  , CacheInvalidateRequest(..)
  , BrickEvent(..)
  , RenderM
  , getContext
  , Widget(..)

  , rsScrollRequestsL
  , viewportMapL
  , clickableNamesL
  , renderCacheL
  , observedNamesL
  , requestedVisibleNames_L
  , vpSize
  , vpLeft
  , vpTop
  , vpContentSize
  , imageL
  , cursorsL
  , extentsL
  , bordersL
  , visibilityRequestsL
  , emptyResult
  )
where

import Control.Monad.Trans.Reader
import Control.Monad.Trans.State.Lazy
import Lens.Micro (_1, _2, Lens')
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
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
(Int -> ScrollRequest -> ShowS)
-> (ScrollRequest -> String)
-> ([ScrollRequest] -> ShowS)
-> Show ScrollRequest
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. 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
$cto :: forall x. Rep ScrollRequest x -> ScrollRequest
$cfrom :: forall x. ScrollRequest -> Rep ScrollRequest x
Generic, ScrollRequest -> ()
(ScrollRequest -> ()) -> NFData ScrollRequest
forall a. (a -> ()) -> NFData a
rnf :: ScrollRequest -> ()
$crnf :: ScrollRequest -> ()
NFData)

-- | Widget size policies. These policies communicate how a widget uses
-- space when being rendered. These policies influence rendering order
-- and space allocation in the box layout algorithm for 'hBox' and
-- 'vBox'.
data Size = Fixed
          -- ^ Widgets advertising this size policy should take up the
          -- same amount of space no matter how much they are given,
          -- i.e. their size depends on their contents alone rather than
          -- on the size of the rendering area.
          | Greedy
          -- ^ Widgets advertising this size policy must take up all the
          -- space they are given.
          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
showList :: [Size] -> ShowS
$cshowList :: [Size] -> ShowS
show :: Size -> String
$cshow :: Size -> String
showsPrec :: Int -> Size -> ShowS
$cshowsPrec :: Int -> Size -> ShowS
Show, Size -> Size -> Bool
(Size -> Size -> Bool) -> (Size -> Size -> Bool) -> Eq Size
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
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
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
$cp1Ord :: Eq Size
Ord)

-- | The type of widgets.
data Widget n =
    Widget { Widget n -> Size
hSize :: Size
           -- ^ This widget's horizontal growth policy
           , Widget n -> Size
vSize :: Size
           -- ^ This widget's vertical growth policy
           , Widget n -> RenderM n (Result n)
render :: RenderM n (Result n)
           -- ^ This widget's rendering function
           }

data RenderState n =
    RS { RenderState n -> Map n Viewport
viewportMap :: !(M.Map n Viewport)
       , RenderState n -> [(n, ScrollRequest)]
rsScrollRequests :: ![(n, ScrollRequest)]
       , RenderState n -> Set n
observedNames :: !(S.Set n)
       , RenderState n -> Map n ([n], Result n)
renderCache :: !(M.Map n ([n], Result n))
       , RenderState n -> [n]
clickableNames :: ![n]
       , RenderState n -> Set n
requestedVisibleNames_ :: !(S.Set 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
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
[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
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 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
$cto :: forall n x. Rep (RenderState n) x -> RenderState n
$cfrom :: forall n x. RenderState n -> Rep (RenderState n) x
Generic, RenderState n -> ()
(RenderState n -> ()) -> NFData (RenderState n)
forall n. NFData n => RenderState n -> ()
forall a. (a -> ()) -> NFData a
rnf :: RenderState n -> ()
$crnf :: forall n. NFData n => RenderState n -> ()
NFData)

-- | The type of the rendering monad. This monad is used by the
-- library's rendering routines to manage rendering state and
-- communicate rendering parameters to widgets' rendering functions.
type RenderM n a = ReaderT (Context n) (State (RenderState n)) a

-- | Get the current rendering context.
getContext :: RenderM n (Context n)
getContext :: RenderM n (Context n)
getContext = RenderM n (Context n)
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask

-- | Orientations for vertical scroll bars.
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
showList :: [VScrollBarOrientation] -> ShowS
$cshowList :: [VScrollBarOrientation] -> ShowS
show :: VScrollBarOrientation -> String
$cshow :: VScrollBarOrientation -> String
showsPrec :: Int -> VScrollBarOrientation -> ShowS
$cshowsPrec :: Int -> VScrollBarOrientation -> ShowS
Show, VScrollBarOrientation -> VScrollBarOrientation -> Bool
(VScrollBarOrientation -> VScrollBarOrientation -> Bool)
-> (VScrollBarOrientation -> VScrollBarOrientation -> Bool)
-> Eq VScrollBarOrientation
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)

-- | Orientations for horizontal scroll bars.
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
showList :: [HScrollBarOrientation] -> ShowS
$cshowList :: [HScrollBarOrientation] -> ShowS
show :: HScrollBarOrientation -> String
$cshow :: HScrollBarOrientation -> String
showsPrec :: Int -> HScrollBarOrientation -> ShowS
$cshowsPrec :: Int -> HScrollBarOrientation -> ShowS
Show, HScrollBarOrientation -> HScrollBarOrientation -> Bool
(HScrollBarOrientation -> HScrollBarOrientation -> Bool)
-> (HScrollBarOrientation -> HScrollBarOrientation -> Bool)
-> Eq HScrollBarOrientation
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)

-- | A scroll bar renderer.
data ScrollbarRenderer n =
    ScrollbarRenderer { ScrollbarRenderer n -> Widget n
renderScrollbar :: Widget n
                      -- ^ How to render the body of the scroll bar.
                      -- This should provide a widget that expands in
                      -- whatever direction(s) this renderer will be
                      -- used for. So, for example, if this was used to
                      -- render vertical scroll bars, this widget would
                      -- need to be one that expands vertically such as
                      -- @fill@. The same goes for the trough widget.
                      , ScrollbarRenderer n -> Widget n
renderScrollbarTrough :: Widget n
                      -- ^ How to render the "trough" of the scroll bar
                      -- (the area to either side of the scroll bar
                      -- body). This should expand as described in the
                      -- documentation for the scroll bar field.
                      , ScrollbarRenderer n -> Widget n
renderScrollbarHandleBefore :: Widget n
                      -- ^ How to render the handle that appears at the
                      -- top or left of the scrollbar. The result should
                      -- be at most one row high for horizontal handles
                      -- and one column wide for vertical handles.
                      , ScrollbarRenderer n -> Widget n
renderScrollbarHandleAfter :: Widget n
                      -- ^ How to render the handle that appears at
                      -- the bottom or right of the scrollbar. The
                      -- result should be at most one row high for
                      -- horizontal handles and one column wide for
                      -- vertical handles.
                      }

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
showList :: [VisibilityRequest] -> ShowS
$cshowList :: [VisibilityRequest] -> ShowS
show :: VisibilityRequest -> String
$cshow :: VisibilityRequest -> String
showsPrec :: Int -> VisibilityRequest -> ShowS
$cshowsPrec :: Int -> VisibilityRequest -> ShowS
Show, VisibilityRequest -> VisibilityRequest -> Bool
(VisibilityRequest -> VisibilityRequest -> Bool)
-> (VisibilityRequest -> VisibilityRequest -> Bool)
-> Eq VisibilityRequest
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]
(Int -> ReadS VisibilityRequest)
-> ReadS [VisibilityRequest]
-> ReadPrec VisibilityRequest
-> ReadPrec [VisibilityRequest]
-> Read 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. 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
$cto :: forall x. Rep VisibilityRequest x -> VisibilityRequest
$cfrom :: forall x. VisibilityRequest -> Rep VisibilityRequest x
Generic, VisibilityRequest -> ()
(VisibilityRequest -> ()) -> NFData VisibilityRequest
forall a. (a -> ()) -> NFData a
rnf :: VisibilityRequest -> ()
$crnf :: VisibilityRequest -> ()
NFData)

-- | Describes the state of a viewport as it appears as its most recent
-- rendering.
data Viewport =
    VP { Viewport -> Int
_vpLeft :: Int
       -- ^ The column offset of left side of the viewport.
       , Viewport -> Int
_vpTop :: Int
       -- ^ The row offset of the top of the viewport.
       , Viewport -> DisplayRegion
_vpSize :: DisplayRegion
       -- ^ The size of the viewport.
       , Viewport -> DisplayRegion
_vpContentSize :: DisplayRegion
       -- ^ The size of the contents of the viewport.
       }
       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
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]
(Int -> ReadS Viewport)
-> ReadS [Viewport]
-> ReadPrec Viewport
-> ReadPrec [Viewport]
-> Read 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. 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
$cto :: forall x. Rep Viewport x -> Viewport
$cfrom :: forall x. Viewport -> Rep Viewport x
Generic, Viewport -> ()
(Viewport -> ()) -> NFData Viewport
forall a. (a -> ()) -> NFData a
rnf :: Viewport -> ()
$crnf :: Viewport -> ()
NFData)

-- | The type of viewports that indicates the direction(s) in which a
-- viewport is scrollable.
data ViewportType = Vertical
                  -- ^ Viewports of this type are scrollable only vertically.
                  | Horizontal
                  -- ^ Viewports of this type are scrollable only horizontally.
                  | Both
                  -- ^ Viewports of this type are scrollable vertically and horizontally.
                  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
showList :: [ViewportType] -> ShowS
$cshowList :: [ViewportType] -> ShowS
show :: ViewportType -> String
$cshow :: ViewportType -> String
showsPrec :: Int -> ViewportType -> ShowS
$cshowsPrec :: Int -> ViewportType -> ShowS
Show, ViewportType -> ViewportType -> Bool
(ViewportType -> ViewportType -> Bool)
-> (ViewportType -> ViewportType -> Bool) -> Eq ViewportType
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 (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
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
$cp1Ord :: forall n. Ord n => Eq (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
/= :: 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 { EventState n -> [(n, ScrollRequest)]
esScrollRequests :: [(n, ScrollRequest)]
                       , EventState n -> Set (CacheInvalidateRequest n)
cacheInvalidateRequests :: S.Set (CacheInvalidateRequest n)
                       , EventState n -> Set n
requestedVisibleNames :: S.Set n
                       }

-- | An extent of a named area: its size, location, and origin.
data Extent n = Extent { Extent n -> n
extentName      :: n
                       , Extent n -> Location
extentUpperLeft :: Location
                       , 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
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)
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
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 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
$cto :: forall n x. Rep (Extent n) x -> Extent n
$cfrom :: forall n x. Extent n -> Rep (Extent n) x
Generic, Extent n -> ()
(Extent n -> ()) -> NFData (Extent n)
forall n. NFData n => Extent n -> ()
forall a. (a -> ()) -> NFData a
rnf :: Extent n -> ()
$crnf :: forall n. NFData n => Extent n -> ()
NFData)

-- | The type of actions to take upon completion of an event handler.
data Next a = Continue a
            | ContinueWithoutRedraw a
            | SuspendAndResume (IO a)
            | Halt a
            deriving a -> Next b -> Next a
(a -> b) -> Next a -> Next b
(forall a b. (a -> b) -> Next a -> Next b)
-> (forall a b. a -> Next b -> Next a) -> Functor Next
forall a b. a -> Next b -> Next a
forall a b. (a -> b) -> Next a -> Next b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Next b -> Next a
$c<$ :: forall a b. a -> Next b -> Next a
fmap :: (a -> b) -> Next a -> Next b
$cfmap :: forall a b. (a -> b) -> Next a -> Next b
Functor

-- | Scrolling direction.
data Direction = Up
               -- ^ Up/left
               | Down
               -- ^ Down/right
               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
showList :: [Direction] -> ShowS
$cshowList :: [Direction] -> ShowS
show :: Direction -> String
$cshow :: Direction -> String
showsPrec :: Int -> Direction -> ShowS
$cshowsPrec :: Int -> Direction -> ShowS
Show, Direction -> Direction -> Bool
(Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool) -> Eq Direction
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]
(Int -> ReadS Direction)
-> ReadS [Direction]
-> ReadPrec Direction
-> ReadPrec [Direction]
-> Read 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. 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
$cto :: forall x. Rep Direction x -> Direction
$cfrom :: forall x. Direction -> Rep Direction x
Generic, Direction -> ()
(Direction -> ()) -> NFData Direction
forall a. (a -> ()) -> NFData a
rnf :: Direction -> ()
$crnf :: Direction -> ()
NFData)

-- | The class of types that behave like terminal locations.
class TerminalLocation a where
    -- | Get the column out of the value
    locationColumnL :: Lens' a Int
    locationColumn :: a -> Int

    -- | Get the row out of the value
    locationRowL :: Lens' a Int
    locationRow :: a -> Int

instance TerminalLocation Location where
    locationColumnL :: (Int -> f Int) -> Location -> f Location
locationColumnL = (Int -> f Int) -> Location -> f Location
forall s t a b. Field1 s t a b => Lens s t a b
_1
    locationColumn :: Location -> Int
locationColumn (Location DisplayRegion
t) = DisplayRegion -> Int
forall a b. (a, b) -> a
fst DisplayRegion
t
    locationRowL :: (Int -> f Int) -> Location -> f Location
locationRowL = (Int -> f Int) -> Location -> f Location
forall s t a b. Field2 s t a b => Lens s t a b
_2
    locationRow :: Location -> Int
locationRow (Location DisplayRegion
t) = DisplayRegion -> Int
forall a b. (a, b) -> b
snd DisplayRegion
t

-- | A cursor location.  These are returned by the rendering process.
data CursorLocation n =
    CursorLocation { CursorLocation n -> Location
cursorLocation :: !Location
                   -- ^ The location
                   , CursorLocation n -> Maybe n
cursorLocationName :: !(Maybe n)
                   -- ^ The name of the widget associated with the location
                   , CursorLocation n -> Bool
cursorLocationVisible :: !Bool
                   -- ^ Whether the cursor should actually be visible
                   }
                   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
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
[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
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 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
$cto :: forall n x. Rep (CursorLocation n) x -> CursorLocation n
$cfrom :: forall n x. CursorLocation n -> Rep (CursorLocation n) x
Generic, CursorLocation n -> ()
(CursorLocation n -> ()) -> NFData (CursorLocation n)
forall n. NFData n => CursorLocation n -> ()
forall a. (a -> ()) -> NFData a
rnf :: CursorLocation n -> ()
$crnf :: forall n. NFData n => CursorLocation n -> ()
NFData)

-- | A border character has four segments, one extending in each direction
-- (horizontally and vertically) from the center of the character.
data BorderSegment = BorderSegment
    { BorderSegment -> Bool
bsAccept :: Bool
    -- ^ Would this segment be willing to be drawn if a neighbor wanted to
    -- connect to it?
    , BorderSegment -> Bool
bsOffer :: Bool
    -- ^ Does this segment want to connect to its neighbor?
    , BorderSegment -> Bool
bsDraw :: Bool
    -- ^ Should this segment be represented visually?
    } deriving (BorderSegment -> BorderSegment -> Bool
(BorderSegment -> BorderSegment -> Bool)
-> (BorderSegment -> BorderSegment -> Bool) -> Eq BorderSegment
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
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
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
$cp1Ord :: Eq 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
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
(Int -> BorderSegment -> ShowS)
-> (BorderSegment -> String)
-> ([BorderSegment] -> ShowS)
-> Show BorderSegment
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. 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
$cto :: forall x. Rep BorderSegment x -> BorderSegment
$cfrom :: forall x. BorderSegment -> Rep BorderSegment x
Generic, BorderSegment -> ()
(BorderSegment -> ()) -> NFData BorderSegment
forall a. (a -> ()) -> NFData a
rnf :: BorderSegment -> ()
$crnf :: BorderSegment -> ()
NFData)

-- | Information about how to redraw a dynamic border character when it abuts
-- another dynamic border character.
data DynBorder = DynBorder
    { DynBorder -> BorderStyle
dbStyle :: BorderStyle
    -- ^ The 'Char's to use when redrawing the border. Also used to filter
    -- connections: only dynamic borders with equal 'BorderStyle's will connect
    -- to each other.
    , DynBorder -> Attr
dbAttr :: Attr
    -- ^ What 'Attr' to use to redraw the border character. Also used to filter
    -- connections: only dynamic borders with equal 'Attr's will connect to
    -- each other.
    , 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
/= :: DynBorder -> DynBorder -> Bool
$c/= :: DynBorder -> DynBorder -> Bool
== :: DynBorder -> DynBorder -> Bool
$c== :: 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
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
(Int -> DynBorder -> ShowS)
-> (DynBorder -> String)
-> ([DynBorder] -> ShowS)
-> Show DynBorder
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. 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
$cto :: forall x. Rep DynBorder x -> DynBorder
$cfrom :: forall x. DynBorder -> Rep DynBorder x
Generic, DynBorder -> ()
(DynBorder -> ()) -> NFData DynBorder
forall a. (a -> ()) -> NFData a
rnf :: DynBorder -> ()
$crnf :: DynBorder -> ()
NFData)

-- | The type of result returned by a widget's rendering function. The
-- result provides the image, cursor positions, and visibility requests
-- that resulted from the rendering process.
data Result n =
    Result { Result n -> Image
image :: Image
           -- ^ The final rendered image for a widget
           , Result n -> [CursorLocation n]
cursors :: [CursorLocation n]
           -- ^ The list of reported cursor positions for the
           -- application to choose from
           , Result n -> [VisibilityRequest]
visibilityRequests :: [VisibilityRequest]
           -- ^ The list of visibility requests made by widgets rendered
           -- while rendering this one (used by viewports)
           , Result n -> [Extent n]
extents :: [Extent n]
           -- Programmer's note: we don't try to maintain the invariant that
           -- the size of the borders closely matches the size of the 'image'
           -- field. Most widgets don't need to care about borders, and so they
           -- use the empty 'BorderMap' that has a degenerate rectangle. Only
           -- border-drawing widgets and the hbox/vbox stuff try to set this
           -- carefully. Even then, in the boxes, we only make sure that the
           -- 'BorderMap' is no larger than the entire concatenation of boxes,
           -- and it's certainly possible for it to be smaller. (Resizing
           -- 'BorderMap's is lossy, so we try to do it as little as possible.)
           -- If you're writing a widget, this should make it easier for you to
           -- do so; but beware this lack of invariant if you are consuming
           -- widgets.
           , Result n -> BorderMap DynBorder
borders :: BorderMap DynBorder
           -- ^ Places where we may rewrite the edge of the image when
           -- placing this widget next to another one.
           }
           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
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)
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
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 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
$cto :: forall n x. Rep (Result n) x -> Result n
$cfrom :: forall n x. Result n -> Rep (Result n) x
Generic, Result n -> ()
(Result n -> ()) -> NFData (Result n)
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 :: Result n
emptyResult = Image
-> [CursorLocation n]
-> [VisibilityRequest]
-> [Extent n]
-> BorderMap DynBorder
-> Result n
forall n.
Image
-> [CursorLocation n]
-> [VisibilityRequest]
-> [Extent n]
-> BorderMap DynBorder
-> Result n
Result Image
emptyImage [] [] [] BorderMap DynBorder
forall a. BorderMap a
BM.empty

-- | The type of events.
data BrickEvent n e = VtyEvent Event
                    -- ^ The event was a Vty event.
                    | AppEvent e
                    -- ^ The event was an application event.
                    | MouseDown n Button [Modifier] Location
                    -- ^ A mouse-down event on the specified region was
                    -- received. The 'n' value is the resource name of
                    -- the clicked widget (see 'clickable').
                    | MouseUp n (Maybe Button) Location
                    -- ^ A mouse-up event on the specified region was
                    -- received. The 'n' value is the resource name of
                    -- the clicked widget (see 'clickable').
                    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
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
(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
/= :: 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, 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
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
$cp1Ord :: forall n e. (Ord e, Ord n) => Eq (BrickEvent n e)
Ord)

data EventRO n = EventRO { EventRO n -> Map n Viewport
eventViewportMap :: M.Map n Viewport
                         , EventRO n -> Vty
eventVtyHandle :: Vty
                         , EventRO n -> [Extent n]
latestExtents :: [Extent n]
                         , EventRO n -> RenderState n
oldState :: RenderState n
                         }

-- | Clickable elements of a scroll bar.
data ClickableScrollbarElement =
    SBHandleBefore
    -- ^ The handle at the beginning (left/top) of the scroll bar.
    | SBHandleAfter
    -- ^ The handle at the end (right/bottom) of the scroll bar.
    | SBBar
    -- ^ The scroll bar itself.
    | SBTroughBefore
    -- ^ The trough before the scroll bar.
    | SBTroughAfter
    -- ^ The trough after the scroll bar.
    deriving (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool
(ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> (ClickableScrollbarElement -> ClickableScrollbarElement -> Bool)
-> Eq ClickableScrollbarElement
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
(Int -> ClickableScrollbarElement -> ShowS)
-> (ClickableScrollbarElement -> String)
-> ([ClickableScrollbarElement] -> ShowS)
-> Show ClickableScrollbarElement
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
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
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
$cp1Ord :: Eq ClickableScrollbarElement
Ord)

-- | The rendering context. This tells widgets how to render: how much
-- space they have in which to render, which attribute they should use
-- to render, which bordering style should be used, and the attribute map
-- available for rendering.
data Context n =
    Context { Context n -> AttrName
ctxAttrName :: AttrName
            , Context n -> Int
availWidth :: Int
            , Context n -> Int
availHeight :: Int
            , Context n -> Int
windowWidth :: Int
            , Context n -> Int
windowHeight :: Int
            , Context n -> BorderStyle
ctxBorderStyle :: BorderStyle
            , Context n -> AttrMap
ctxAttrMap :: AttrMap
            , Context n -> Bool
ctxDynBorders :: Bool
            , Context n -> Maybe VScrollBarOrientation
ctxVScrollBarOrientation :: Maybe VScrollBarOrientation
            , Context n -> Maybe (ScrollbarRenderer n)
ctxVScrollBarRenderer :: Maybe (ScrollbarRenderer n)
            , Context n -> Maybe HScrollBarOrientation
ctxHScrollBarOrientation :: Maybe HScrollBarOrientation
            , Context n -> Maybe (ScrollbarRenderer n)
ctxHScrollBarRenderer :: Maybe (ScrollbarRenderer n)
            , Context n -> Bool
ctxVScrollBarShowHandles :: Bool
            , Context n -> Bool
ctxHScrollBarShowHandles :: Bool
            , Context n -> Maybe (ClickableScrollbarElement -> n -> n)
ctxVScrollBarClickableConstr :: Maybe (ClickableScrollbarElement -> n -> n)
            , Context n -> Maybe (ClickableScrollbarElement -> n -> n)
ctxHScrollBarClickableConstr :: Maybe (ClickableScrollbarElement -> n -> n)
            }

suffixLenses ''RenderState
suffixLenses ''VisibilityRequest
suffixLenses ''CursorLocation
suffixLenses ''Context
suffixLenses ''DynBorder
suffixLenses ''Result
suffixLenses ''BorderSegment
makeLenses ''Viewport