{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Brick.Types
(
Widget(..)
, Location(..)
, locL
, TerminalLocation(..)
, CursorLocation(..)
, cursorLocationL
, cursorLocationNameL
, Viewport(..)
, ViewportType(..)
, vpSize
, vpTop
, vpLeft
, EventM(..)
, Next
, BrickEvent(..)
, handleEventLensed
, RenderM
, getContext
, Context(ctxAttrName, availWidth, availHeight, ctxBorderStyle, ctxAttrMap, ctxDynBorders)
, attrL
, availWidthL
, availHeightL
, ctxAttrMapL
, ctxAttrNameL
, ctxBorderStyleL
, ctxDynBordersL
, Result(..)
, emptyResult
, lookupAttrName
, Extent(..)
, imageL
, cursorsL
, visibilityRequestsL
, extentsL
, VisibilityRequest(..)
, vrPositionL
, vrSizeL
, suffixLenses
, bordersL
, DynBorder(..)
, dbStyleL, dbAttrL, dbSegmentsL
, BorderSegment(..)
, bsAcceptL, bsOfferL, bsDrawL
, Edges(..)
, eTopL, eBottomL, eRightL, eLeftL
, Size(..)
, Padding(..)
, Direction(..)
)
where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
import Data.Monoid (Monoid(..))
#endif
import Lens.Micro (_1, _2, to, (^.), (&), (.~), Lens')
import Lens.Micro.Type (Getting)
import Control.Monad.Trans.State.Lazy
import Control.Monad.Trans.Reader
import Graphics.Vty (Attr)
import Control.Monad.IO.Class
import Brick.Types.TH
import Brick.Types.Internal
import Brick.AttrMap (AttrName, attrMapLookup)
data Padding = Pad Int
| Max
handleEventLensed :: a
-> Lens' a b
-> (e -> b -> EventM n b)
-> e
-> EventM n a
handleEventLensed v target handleEvent ev = do
newB <- handleEvent ev (v^.target)
return $ v & target .~ newB
newtype EventM n a =
EventM { runEventM :: ReaderT (EventRO n) (StateT (EventState n) IO) a
}
deriving (Functor, Applicative, Monad, MonadIO)
data Size = Fixed
| Greedy
deriving (Show, Eq, Ord)
data Widget n =
Widget { hSize :: Size
, vSize :: Size
, render :: RenderM n (Result n)
}
type RenderM n a = ReaderT Context (State (RenderState n)) a
getContext :: RenderM n Context
getContext = ask
suffixLenses ''Context
attrL :: forall r. Getting r Context Attr
attrL = to (\c -> attrMapLookup (c^.ctxAttrNameL) (c^.ctxAttrMapL))
instance TerminalLocation (CursorLocation n) where
locationColumnL = cursorLocationL._1
locationColumn = locationColumn . cursorLocation
locationRowL = cursorLocationL._2
locationRow = locationRow . cursorLocation
lookupAttrName :: AttrName -> RenderM n Attr
lookupAttrName n = do
c <- getContext
return $ attrMapLookup n (c^.ctxAttrMapL)