| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Brick.BorderMap
Synopsis
- data BorderMap a
- 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
- empty :: BorderMap a
- emptyCoordinates :: Edges Int -> BorderMap a
- singleton :: Location -> a -> BorderMap a
- insertH :: Location -> Run a -> BorderMap a -> BorderMap a
- insertV :: Location -> Run a -> BorderMap a -> BorderMap a
- insert :: Location -> a -> BorderMap a -> BorderMap a
- unsafeUnion :: BorderMap a -> BorderMap a -> BorderMap a
- coordinates :: BorderMap a -> Edges Int
- bounds :: BorderMap a -> Edges (Int, Int)
- values :: BorderMap a -> Edges (IMap a)
- lookupRow :: Int -> BorderMap a -> IMap a
- lookupCol :: Int -> BorderMap a -> IMap a
- lookupH :: Location -> Run ignored -> BorderMap a -> IMap a
- lookupV :: Location -> Run ignored -> BorderMap a -> IMap a
- lookup :: Location -> BorderMap a -> Maybe a
- setCoordinates :: Edges Int -> BorderMap a -> BorderMap a
- crop :: Edges Int -> BorderMap a -> BorderMap a
- expand :: Edges Int -> BorderMap a -> BorderMap a
- translate :: Location -> BorderMap a -> BorderMap a
Documentation
A BorderMap a is like a Map Location a, except that there is a
 rectangle, and only Locations on the border of this rectangle are
 retained. The BorderMap can be queried for the position and size of the
 rectangle. There are also efficient bulk query and bulk update operations
 for adjacent positions on the border.
Instances
| Functor BorderMap Source # | |
| Eq a => Eq (BorderMap a) Source # | |
| Ord a => Ord (BorderMap a) Source # | |
| Defined in Brick.BorderMap | |
| Read a => Read (BorderMap a) Source # | |
| Show a => Show (BorderMap a) Source # | |
| Generic (BorderMap a) Source # | |
| NFData a => NFData (BorderMap a) Source # | |
| Defined in Brick.BorderMap | |
| type Rep (BorderMap a) Source # | |
| Defined in Brick.BorderMap type Rep (BorderMap a) = D1 ('MetaData "BorderMap" "Brick.BorderMap" "brick-0.62-1e4A8lbF5JHLX9ePazMmE1" 'False) (C1 ('MetaCons "BorderMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "_coordinates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Edges Int)) :*: S1 ('MetaSel ('Just "_values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Edges (IMap a))))) | |
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-0.62-1e4A8lbF5JHLX9ePazMmE1" '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)))) | |
emptyCoordinates :: Edges Int -> BorderMap a Source #
Given a rectangle (specified as the coordinates of the top, left, bottom,
 and right sides), initialize an empty BorderMap.
singleton :: Location -> a -> BorderMap a Source #
A BorderMap that tracks only the given the point (and initially maps it
 to the given value).
insert :: Location -> a -> BorderMap a -> BorderMap a Source #
Insert a single value at the given location.
unsafeUnion :: BorderMap a -> BorderMap a -> BorderMap a Source #
Assumes the two BorderMaps are tracking the same rectangles, but have
 disjoint keys. This property is not checked.
bounds :: BorderMap a -> Edges (Int, Int) Source #
A complementary way to query the edges of the rectangle whose border is
 retained in a BorderMap. For example, if bounds m = b, then a
 Location's column must be between fst (eTop b) and snd (eTop b) to be
 retained. See also coordinates, which is in most cases a more natural
 border query.
values :: BorderMap a -> Edges (IMap a) Source #
Maps giving the values along each edge. Corner values are replicated in all relevant edges.
lookupRow :: Int -> BorderMap a -> IMap a Source #
Look up all values on a given row. The IMap returned maps columns to
 values.
lookupCol :: Int -> BorderMap a -> IMap a Source #
Look up all values on a given column. The IMap returned maps rows to
 values.
setCoordinates :: Edges Int -> BorderMap a -> BorderMap a Source #
Set the rectangle being tracked by this BorderMap, throwing away any
 values that do not lie on this new rectangle.
crop :: Edges Int -> BorderMap a -> BorderMap a Source #
Ensure that the rectangle being tracked by this BorderMap extends no
 farther than the given one.