{-# 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
, Context(..)
, EventState(..)
, EventRO(..)
, Next(..)
, Result(..)
, Extent(..)
, Edges(..)
, eTopL, eBottomL, eRightL, eLeftL
, BorderSegment(..)
, bsAcceptL, bsOfferL, bsDrawL
, DynBorder(..)
, dbStyleL, dbAttrL, dbSegmentsL
, CacheInvalidateRequest(..)
, BrickEvent(..)
, rsScrollRequestsL
, viewportMapL
, clickableNamesL
, renderCacheL
, observedNamesL
, vpSize
, vpLeft
, vpTop
, imageL
, cursorsL
, extentsL
, bordersL
, visibilityRequestsL
, emptyResult
)
where
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
#endif
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 (Read, Show, Generic, NFData)
data VisibilityRequest =
VR { vrPosition :: Location
, vrSize :: DisplayRegion
}
deriving (Show, Eq, Read, Generic, NFData)
data Viewport =
VP { _vpLeft :: Int
, _vpTop :: Int
, _vpSize :: DisplayRegion
}
deriving (Show, Read, Generic, NFData)
data ViewportType = Vertical
| Horizontal
| Both
deriving (Show, Eq)
data CacheInvalidateRequest n =
InvalidateSingle n
| InvalidateEntire
deriving (Ord, Eq)
data EventState n = ES { esScrollRequests :: [(n, ScrollRequest)]
, cacheInvalidateRequests :: S.Set (CacheInvalidateRequest n)
}
data Extent n = Extent { extentName :: n
, extentUpperLeft :: Location
, extentSize :: (Int, Int)
, extentOffset :: Location
}
deriving (Show, Read, Generic, NFData)
data Next a = Continue a
| SuspendAndResume (IO a)
| Halt a
deriving Functor
data Direction = Up
| Down
deriving (Show, Eq, Read, Generic, NFData)
class TerminalLocation a where
locationColumnL :: Lens' a Int
locationColumn :: a -> Int
locationRowL :: Lens' a Int
locationRow :: a -> Int
instance TerminalLocation Location where
locationColumnL = _1
locationColumn (Location t) = fst t
locationRowL = _2
locationRow (Location t) = snd t
data CursorLocation n =
CursorLocation { cursorLocation :: !Location
, cursorLocationName :: !(Maybe n)
}
deriving (Read, Show, Generic, NFData)
data BorderSegment = BorderSegment
{ bsAccept :: Bool
, bsOffer :: Bool
, bsDraw :: Bool
} deriving (Eq, Ord, Read, Show, Generic, NFData)
suffixLenses ''BorderSegment
data DynBorder = DynBorder
{ dbStyle :: BorderStyle
, dbAttr :: Attr
, dbSegments :: Edges BorderSegment
} deriving (Eq, Read, Show, Generic, NFData)
suffixLenses ''DynBorder
data Result n =
Result { image :: Image
, cursors :: [CursorLocation n]
, visibilityRequests :: [VisibilityRequest]
, extents :: [Extent n]
, borders :: BorderMap DynBorder
}
deriving (Show, Read, Generic, NFData)
suffixLenses ''Result
emptyResult :: Result n
emptyResult = Result emptyImage [] [] [] BM.empty
data BrickEvent n e = VtyEvent Event
| AppEvent e
| MouseDown n Button [Modifier] Location
| MouseUp n (Maybe Button) Location
deriving (Show, Eq, Ord)
data RenderState n =
RS { viewportMap :: M.Map n Viewport
, rsScrollRequests :: [(n, ScrollRequest)]
, observedNames :: !(S.Set n)
, renderCache :: M.Map n (Result n)
, clickableNames :: [n]
} deriving (Read, Show, Generic, NFData)
data EventRO n = EventRO { eventViewportMap :: M.Map n Viewport
, eventVtyHandle :: Vty
, latestExtents :: [Extent n]
, oldState :: RenderState n
}
data Context =
Context { ctxAttrName :: AttrName
, availWidth :: Int
, availHeight :: Int
, ctxBorderStyle :: BorderStyle
, ctxAttrMap :: AttrMap
, ctxDynBorders :: Bool
}
deriving Show
suffixLenses ''RenderState
suffixLenses ''VisibilityRequest
suffixLenses ''CursorLocation
makeLenses ''Viewport