| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Brick.Types
Description
Basic types used by this library.
Synopsis
- data Widget n = Widget {}
- data Location = Location {}
- locL :: Lens' Location (Int, Int)
- class TerminalLocation a where- locationColumnL :: Lens' a Int
- locationColumn :: a -> Int
- locationRowL :: Lens' a Int
- locationRow :: a -> Int
 
- data CursorLocation n = CursorLocation {- cursorLocation :: !Location
- cursorLocationName :: !(Maybe n)
- cursorLocationVisible :: !Bool
 
- cursorLocationL :: forall n. Lens' (CursorLocation n) Location
- cursorLocationNameL :: forall n n. Lens (CursorLocation n) (CursorLocation n) (Maybe n) (Maybe n)
- data Viewport = VP {}
- data ViewportType- = Vertical
- | Horizontal
- | Both
 
- vpSize :: Lens' Viewport DisplayRegion
- vpTop :: Lens' Viewport Int
- vpLeft :: Lens' Viewport Int
- vpContentSize :: Lens' Viewport DisplayRegion
- data VScrollBarOrientation
- data HScrollBarOrientation
- data ScrollbarRenderer n = ScrollbarRenderer {}
- data ClickableScrollbarElement
- data EventM n s a
- data BrickEvent n e
- nestEventM :: a -> EventM n a b -> EventM n s (a, b)
- nestEventM' :: a -> EventM n a b -> EventM n s a
- type RenderM n a = ReaderT (Context n) (State (RenderState n)) a
- getContext :: RenderM n (Context n)
- data Context n
- attrL :: forall r n. Getting r (Context n) Attr
- availWidthL :: forall n. Lens' (Context n) Int
- availHeightL :: forall n. Lens' (Context n) Int
- windowWidthL :: forall n. Lens' (Context n) Int
- windowHeightL :: forall n. Lens' (Context n) Int
- ctxVScrollBarOrientationL :: forall n. Lens' (Context n) (Maybe VScrollBarOrientation)
- ctxVScrollBarRendererL :: forall n. Lens' (Context n) (Maybe (ScrollbarRenderer n))
- ctxHScrollBarOrientationL :: forall n. Lens' (Context n) (Maybe HScrollBarOrientation)
- ctxHScrollBarRendererL :: forall n. Lens' (Context n) (Maybe (ScrollbarRenderer n))
- ctxAttrMapL :: forall n. Lens' (Context n) AttrMap
- ctxAttrNameL :: forall n. Lens' (Context n) AttrName
- ctxBorderStyleL :: forall n. Lens' (Context n) BorderStyle
- ctxDynBordersL :: forall n. Lens' (Context n) Bool
- data Result n = Result {- image :: !Image
- cursors :: ![CursorLocation n]
- visibilityRequests :: ![VisibilityRequest]
- extents :: ![Extent n]
- borders :: !(BorderMap DynBorder)
 
- emptyResult :: Result n
- lookupAttrName :: AttrName -> RenderM n Attr
- data Extent n = Extent {- extentName :: !n
- extentUpperLeft :: !Location
- extentSize :: !(Int, Int)
 
- imageL :: forall n. Lens' (Result n) Image
- cursorsL :: forall n. Lens' (Result n) [CursorLocation n]
- visibilityRequestsL :: forall n. Lens' (Result n) [VisibilityRequest]
- extentsL :: forall n. Lens' (Result n) [Extent n]
- data VisibilityRequest = VR {}
- vrPositionL :: Lens' VisibilityRequest Location
- vrSizeL :: Lens' VisibilityRequest DisplayRegion
- suffixLenses :: Name -> DecsQ
- suffixLensesWith :: String -> LensRules -> Name -> DecsQ
- bordersL :: forall n. Lens' (Result n) (BorderMap DynBorder)
- data DynBorder = DynBorder {}
- dbStyleL :: Lens' DynBorder BorderStyle
- dbAttrL :: Lens' DynBorder Attr
- dbSegmentsL :: Lens' DynBorder (Edges BorderSegment)
- data BorderSegment = BorderSegment {}
- bsAcceptL :: Lens' BorderSegment Bool
- bsOfferL :: Lens' BorderSegment Bool
- bsDrawL :: Lens' BorderSegment Bool
- data Edges a = Edges {}
- eTopL :: forall a. Lens' (Edges a) a
- eBottomL :: forall a. Lens' (Edges a) a
- eRightL :: forall a. Lens' (Edges a) a
- eLeftL :: forall a. Lens' (Edges a) a
- data Size
- data Direction
- data RenderState n
- get :: MonadState s m => m s
- gets :: MonadState s m => (s -> a) -> m a
- put :: MonadState s m => s -> m ()
- modify :: MonadState s m => (s -> s) -> m ()
- zoom :: Zoom m n s t => LensLike' (Zoomed m c) t s -> m c -> n c
The Widget type
The type of widgets.
Location types and lenses
A terminal screen location.
Instances
| Eq Location Source # | |
| Ord Location Source # | |
| Defined in Brick.Types.Common | |
| Read Location Source # | |
| Show Location Source # | |
| Generic Location Source # | |
| Semigroup Location Source # | |
| Monoid Location Source # | |
| NFData Location Source # | |
| Defined in Brick.Types.Common | |
| TerminalLocation Location Source # | |
| Defined in Brick.Types.Internal | |
| Field1 Location Location Int Int Source # | |
| Field2 Location Location Int Int Source # | |
| type Rep Location Source # | |
| Defined in Brick.Types.Common | |
class TerminalLocation a where Source #
The class of types that behave like terminal locations.
Methods
locationColumnL :: Lens' a Int Source #
Get the column out of the value
locationColumn :: a -> Int Source #
locationRowL :: Lens' a Int Source #
Get the row out of the value
locationRow :: a -> Int Source #
Instances
| TerminalLocation Location Source # | |
| Defined in Brick.Types.Internal | |
| TerminalLocation (CursorLocation n) Source # | |
| Defined in Brick.Types Methods locationColumnL :: Lens' (CursorLocation n) Int Source # locationColumn :: CursorLocation n -> Int Source # locationRowL :: Lens' (CursorLocation n) Int Source # locationRow :: CursorLocation n -> Int Source # | |
data CursorLocation n Source #
A cursor location. These are returned by the rendering process.
Constructors
| CursorLocation | |
| Fields 
 | |
Instances
cursorLocationL :: forall n. Lens' (CursorLocation n) Location Source #
cursorLocationNameL :: forall n n. Lens (CursorLocation n) (CursorLocation n) (Maybe n) (Maybe n) Source #
Viewports
Describes the state of a viewport as it appears as its most recent rendering.
Constructors
| VP | |
| Fields 
 | |
Instances
| Read Viewport Source # | |
| Show Viewport Source # | |
| Generic Viewport Source # | |
| NFData Viewport Source # | |
| Defined in Brick.Types.Internal | |
| type Rep Viewport Source # | |
| Defined in Brick.Types.Internal type Rep Viewport = D1 ('MetaData "Viewport" "Brick.Types.Internal" "brick-1.1-GopzZYLAsVW2RDaydXwkeZ" 'False) (C1 ('MetaCons "VP" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_vpLeft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_vpTop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "_vpSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DisplayRegion) :*: S1 ('MetaSel ('Just "_vpContentSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DisplayRegion)))) | |
data ViewportType Source #
The type of viewports that indicates the direction(s) in which a viewport is scrollable.
Constructors
| 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. | 
Instances
| Eq ViewportType Source # | |
| Defined in Brick.Types.Internal | |
| Show ViewportType Source # | |
| Defined in Brick.Types.Internal Methods showsPrec :: Int -> ViewportType -> ShowS # show :: ViewportType -> String # showList :: [ViewportType] -> ShowS # | |
data VScrollBarOrientation Source #
Orientations for vertical scroll bars.
Instances
| Eq VScrollBarOrientation Source # | |
| Defined in Brick.Types.Internal Methods (==) :: VScrollBarOrientation -> VScrollBarOrientation -> Bool # (/=) :: VScrollBarOrientation -> VScrollBarOrientation -> Bool # | |
| Show VScrollBarOrientation Source # | |
| Defined in Brick.Types.Internal Methods showsPrec :: Int -> VScrollBarOrientation -> ShowS # show :: VScrollBarOrientation -> String # showList :: [VScrollBarOrientation] -> ShowS # | |
data HScrollBarOrientation Source #
Orientations for horizontal scroll bars.
Instances
| Eq HScrollBarOrientation Source # | |
| Defined in Brick.Types.Internal Methods (==) :: HScrollBarOrientation -> HScrollBarOrientation -> Bool # (/=) :: HScrollBarOrientation -> HScrollBarOrientation -> Bool # | |
| Show HScrollBarOrientation Source # | |
| Defined in Brick.Types.Internal Methods showsPrec :: Int -> HScrollBarOrientation -> ShowS # show :: HScrollBarOrientation -> String # showList :: [HScrollBarOrientation] -> ShowS # | |
data ScrollbarRenderer n Source #
A scroll bar renderer.
Constructors
| ScrollbarRenderer | |
| Fields 
 | |
data ClickableScrollbarElement Source #
Clickable elements of a scroll bar.
Constructors
| 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. | 
Instances
Event-handling types and functions
The monad in which event handlers run.
Instances
| MonadState s (EventM n s) Source # | |
| Monad (EventM n s) Source # | |
| Functor (EventM n s) Source # | |
| Applicative (EventM n s) Source # | |
| Defined in Brick.Types.EventM | |
| MonadIO (EventM n s) Source # | |
| Defined in Brick.Types.EventM | |
| MonadThrow (EventM n s) Source # | |
| Defined in Brick.Types.EventM | |
| MonadCatch (EventM n s) Source # | |
| MonadMask (EventM n s) Source # | |
| Defined in Brick.Types.EventM Methods mask :: ((forall a. EventM n s a -> EventM n s a) -> EventM n s b) -> EventM n s b # uninterruptibleMask :: ((forall a. EventM n s a -> EventM n s a) -> EventM n s b) -> EventM n s b # generalBracket :: EventM n s a -> (a -> ExitCase b -> EventM n s c) -> (a -> EventM n s b) -> EventM n s (b, c) # | |
| Zoom (EventM n s) (EventM n t) s t Source # | |
| type Zoomed (EventM n s) Source # | |
| Defined in Brick.Types.EventM | |
data BrickEvent n e Source #
The type of events.
Constructors
| 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  | 
| MouseUp n (Maybe Button) Location | A mouse-up event on the specified region was
 received. The  | 
Instances
| (Eq e, Eq n) => Eq (BrickEvent n e) Source # | |
| Defined in Brick.Types.Internal Methods (==) :: BrickEvent n e -> BrickEvent n e -> Bool # (/=) :: BrickEvent n e -> BrickEvent n e -> Bool # | |
| (Ord e, Ord n) => Ord (BrickEvent n e) Source # | |
| Defined in Brick.Types.Internal Methods compare :: 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 # max :: BrickEvent n e -> BrickEvent n e -> BrickEvent n e # min :: BrickEvent n e -> BrickEvent n e -> BrickEvent n e # | |
| (Show e, Show n) => Show (BrickEvent n e) Source # | |
| Defined in Brick.Types.Internal Methods showsPrec :: Int -> BrickEvent n e -> ShowS # show :: BrickEvent n e -> String # showList :: [BrickEvent n e] -> ShowS # | |
Arguments
| :: a | The initial state to use in the nested action. | 
| -> EventM n a b | The action to run. | 
| -> EventM n s (a, b) | 
Given a state value and an EventM that mutates that state, run
 the specified action and return both the resulting modified state and
 the result of the action itself.
Arguments
| :: a | The initial state to use in the nested action. | 
| -> EventM n a b | The action to run. | 
| -> EventM n s a | 
Given a state value and an EventM that mutates that state, run
 the specified action and return resulting modified state.
Rendering infrastructure
type RenderM n a = ReaderT (Context n) (State (RenderState n)) a Source #
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.
getContext :: RenderM n (Context n) Source #
Get the current rendering context.
The rendering context
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.
attrL :: forall r n. Getting r (Context n) Attr Source #
The rendering context's current drawing attribute.
ctxVScrollBarOrientationL :: forall n. Lens' (Context n) (Maybe VScrollBarOrientation) Source #
ctxVScrollBarRendererL :: forall n. Lens' (Context n) (Maybe (ScrollbarRenderer n)) Source #
ctxHScrollBarOrientationL :: forall n. Lens' (Context n) (Maybe HScrollBarOrientation) Source #
ctxHScrollBarRendererL :: forall n. Lens' (Context n) (Maybe (ScrollbarRenderer n)) Source #
ctxBorderStyleL :: forall n. Lens' (Context n) BorderStyle Source #
Rendering results
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.
Constructors
| Result | |
| Fields 
 | |
Instances
| Read n => Read (Result n) Source # | |
| Show n => Show (Result n) Source # | |
| Generic (Result n) Source # | |
| NFData n => NFData (Result n) Source # | |
| Defined in Brick.Types.Internal | |
| type Rep (Result n) Source # | |
| Defined in Brick.Types.Internal type Rep (Result n) = D1 ('MetaData "Result" "Brick.Types.Internal" "brick-1.1-GopzZYLAsVW2RDaydXwkeZ" 'False) (C1 ('MetaCons "Result" 'PrefixI 'True) ((S1 ('MetaSel ('Just "image") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Image) :*: S1 ('MetaSel ('Just "cursors") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [CursorLocation n])) :*: (S1 ('MetaSel ('Just "visibilityRequests") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [VisibilityRequest]) :*: (S1 ('MetaSel ('Just "extents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Extent n]) :*: S1 ('MetaSel ('Just "borders") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BorderMap DynBorder)))))) | |
emptyResult :: Result n Source #
lookupAttrName :: AttrName -> RenderM n Attr Source #
Given an attribute name, obtain the attribute for the attribute name by consulting the context's attribute map.
An extent of a named area: its size, location, and origin.
Constructors
| Extent | |
| Fields 
 | |
Instances
| Read n => Read (Extent n) Source # | |
| Show n => Show (Extent n) Source # | |
| Generic (Extent n) Source # | |
| NFData n => NFData (Extent n) Source # | |
| Defined in Brick.Types.Internal | |
| type Rep (Extent n) Source # | |
| Defined in Brick.Types.Internal type Rep (Extent n) = D1 ('MetaData "Extent" "Brick.Types.Internal" "brick-1.1-GopzZYLAsVW2RDaydXwkeZ" 'False) (C1 ('MetaCons "Extent" 'PrefixI 'True) (S1 ('MetaSel ('Just "extentName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 n) :*: (S1 ('MetaSel ('Just "extentUpperLeft") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Location) :*: S1 ('MetaSel ('Just "extentSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Int, Int))))) | |
Rendering result lenses
visibilityRequestsL :: forall n. Lens' (Result n) [VisibilityRequest] Source #
Visibility requests
data VisibilityRequest Source #
Constructors
| VR | |
| Fields | |
Instances
Making lenses
suffixLenses :: Name -> DecsQ Source #
A template haskell function to build lenses for a record type. This
 function differs from the makeLenses function in that
 it does not require the record fields to be prefixed with underscores
 and it adds an L suffix to lens names to make it clear that they
 are lenses.
suffixLensesWith :: String -> LensRules -> Name -> DecsQ Source #
A more general version of suffixLenses that allows customization
 of the lens-building rules and allows customization of the suffix.
Dynamic borders
Information about how to redraw a dynamic border character when it abuts another dynamic border character.
Constructors
| DynBorder | |
| Fields 
 | |
Instances
| Eq DynBorder Source # | |
| Read DynBorder Source # | |
| Show DynBorder Source # | |
| Generic DynBorder Source # | |
| NFData DynBorder Source # | |
| Defined in Brick.Types.Internal | |
| type Rep DynBorder Source # | |
| Defined in Brick.Types.Internal type Rep DynBorder = D1 ('MetaData "DynBorder" "Brick.Types.Internal" "brick-1.1-GopzZYLAsVW2RDaydXwkeZ" 'False) (C1 ('MetaCons "DynBorder" 'PrefixI 'True) (S1 ('MetaSel ('Just "dbStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BorderStyle) :*: (S1 ('MetaSel ('Just "dbAttr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Just "dbSegments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Edges BorderSegment))))) | |
data BorderSegment Source #
A border character has four segments, one extending in each direction (horizontally and vertically) from the center of the character.
Constructors
| BorderSegment | |
Instances
Instances
| Monad Edges Source # | |
| Functor Edges Source # | |
| Applicative Edges Source # | |
| Eq a => Eq (Edges a) Source # | |
| Ord a => Ord (Edges a) Source # | |
| Read a => Read (Edges a) Source # | |
| Show a => Show (Edges a) Source # | |
| Generic (Edges a) Source # | |
| NFData a => NFData (Edges a) Source # | |
| Defined in Brick.Types.Common | |
| type Rep (Edges a) Source # | |
| Defined in Brick.Types.Common type Rep (Edges a) = D1 ('MetaData "Edges" "Brick.Types.Common" "brick-1.1-GopzZYLAsVW2RDaydXwkeZ" 'False) (C1 ('MetaCons "Edges" 'PrefixI 'True) ((S1 ('MetaSel ('Just "eTop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "eBottom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :*: (S1 ('MetaSel ('Just "eLeft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "eRight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) | |
Miscellaneous
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.
Constructors
| 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. | 
Scrolling direction.
Renderer internals (for benchmarking)
data RenderState n Source #
Instances
| (Ord n, Read n) => Read (RenderState n) Source # | |
| Defined in Brick.Types.Internal Methods readsPrec :: Int -> ReadS (RenderState n) # readList :: ReadS [RenderState n] # readPrec :: ReadPrec (RenderState n) # readListPrec :: ReadPrec [RenderState n] # | |
| Show n => Show (RenderState n) Source # | |
| Defined in Brick.Types.Internal Methods showsPrec :: Int -> RenderState n -> ShowS # show :: RenderState n -> String # showList :: [RenderState n] -> ShowS # | |
| Generic (RenderState n) Source # | |
| Defined in Brick.Types.Internal Associated Types type Rep (RenderState n) :: Type -> Type # Methods from :: RenderState n -> Rep (RenderState n) x # to :: Rep (RenderState n) x -> RenderState n # | |
| NFData n => NFData (RenderState n) Source # | |
| Defined in Brick.Types.Internal Methods rnf :: RenderState n -> () # | |
| type Rep (RenderState n) Source # | |
| Defined in Brick.Types.Internal | |
Re-exports for convenience
get :: MonadState s m => m s #
Return the state from the internals of the monad.
gets :: MonadState s m => (s -> a) -> m a #
Gets specific component of the state, using a projection function supplied.
put :: MonadState s m => s -> m () #
Replace the state inside the monad.
modify :: MonadState s m => (s -> s) -> m () #
Monadic state transformer.
Maps an old state to a new state inside a state monad. The old state is thrown away.
     Main> :t modify ((+1) :: Int -> Int)
     modify (...) :: (MonadState Int a) => a ()This says that modify (+1) acts over any
    Monad that is a member of the MonadState class,
    with an Int state.
zoom :: Zoom m n s t => LensLike' (Zoomed m c) t s -> m c -> n c infixr 2 #
When you're in a state monad, this function lets you operate on a part of your state. For instance, if your state was a record containing a position field, after zooming position would become your whole state (and when you modify it, the bigger structure would be modified as well).
(Your State / StateT or RWS / RWST can be anywhere in the stack, but you can't use zoom with arbitrary MonadState because it doesn't provide any methods to change the type of the state. See this issue for details.)
For the sake of the example, let's define some types first:
data Position = Position {
  _x, _y :: Int }
data Player = Player {
  _position :: Position,
  ... }
data Game = Game {
  _player :: Player,
  _obstacles :: [Position],
  ... }
concat <$> mapM makeLenses [''Position, ''Player, ''Game]
Now, here's an action that moves the player north-east:
moveNE ::StateGame () moveNE = do player.position.x+=1 player.position.y+=1
With zoom, you can use player.position to focus just on a part of the state:
moveNE ::StateGame () moveNE = dozoom(player.position) $ do x+=1 y+=1
You can just as well use it for retrieving things out of the state:
getCoords ::StateGame (Int, Int) getCoords =zoom(player.position) ((,)<$>usex<*>usey)
Or more explicitly:
getCoords =zoom(player.position) $ do x' <-usex y' <-usey return (x', y')
When you pass a traversal to zoom, it'll work as a loop. For instance, here we move all obstacles:
moveObstaclesNE ::StateGame () moveObstaclesNE = dozoom(obstacles.each) $ do x+=1 y+=1
If the action returns a result, all results would be combined with <> – the same way they're combined when ^. is passed a traversal. In this example, moveObstaclesNE returns a list of old coordinates of obstacles in addition to moving them:
moveObstaclesNE = do xys <-zoom(obstacles.each) $ do -- Get old coordinates. x' <-usex y' <-usey -- Update them. x.=x' + 1 y.=y' + 1 -- Return a single-element list with old coordinates. return [(x', y')] ...
Finally, you might need to write your own instances of Zoom if you use newtyped transformers in your monad stack. This can be done as follows:
import Lens.Micro.Mtl.Internal type instanceZoomed(MyStateT s m) =Zoomed(StateT s m) instance Monad m =>Zoom(MyStateT s m) (MyStateT t m) s t wherezooml (MyStateT m) = MyStateT (zooml m)
Orphan instances
| TerminalLocation (CursorLocation n) Source # | |
| Methods locationColumnL :: Lens' (CursorLocation n) Int Source # locationColumn :: CursorLocation n -> Int Source # locationRowL :: Lens' (CursorLocation n) Int Source # locationRow :: CursorLocation n -> Int Source # | |