make empty BorderMaps even emptier (issue 370)

The BorderMap module provides a notion of an empty map. Previously, this
was accidentally conflating two kinds of emptiness: an map that doesn't
track points, and a map that tracks a point (or multiple points) but
doesn't associate it with anything. This meant that the empty map was
not a unit for the union operation, which seems like a natural
expectation.

This has been resolved by revising the empty map to be the one that
tracks no points. Callers that expected that behavior were left alone,
while callers that expected the other behavior were fixed to use
`emptyCoordinates`.
This commit is contained in:
Daniel Wagner 2022-06-19 14:51:22 -04:00
parent 6ccdd8c1f1
commit 539a594c27
2 changed files with 14 additions and 5 deletions

View File

@ -7,7 +7,7 @@ module Brick.BorderMap
( BorderMap
, Edges(..)
, eTopL, eBottomL, eRightL, eLeftL
, empty, emptyCoordinates, singleton
, empty, clear, emptyCoordinates, singleton
, insertH, insertV, insert
, unsafeUnion
, coordinates, bounds
@ -54,14 +54,23 @@ data BorderMap a = BorderMap
emptyCoordinates :: Edges Int -> BorderMap a
emptyCoordinates cs = BorderMap { _coordinates = cs, _values = pure IM.empty }
-- | An empty 'BorderMap' that only tracks the point (0,0).
-- | An empty 'BorderMap' that tracks the same points as the input.
clear :: BorderMap a -> BorderMap b
clear = emptyCoordinates . coordinates
-- | An empty 'BorderMap' that does not track any points.
empty :: BorderMap a
empty = emptyCoordinates (pure 0)
empty = emptyCoordinates Edges
{ eTop = 0
, eBottom = -1
, eLeft = 0
, eRight = -1
}
-- | A 'BorderMap' that tracks only the given the point (and initially maps it
-- to the given value).
singleton :: Location -> a -> BorderMap a
singleton l v = translate l . insert origin v $ empty
singleton l v = translate l . insert origin v . emptyCoordinates $ pure 0
{-# INLINE coordinates #-}
-- | The positions of the edges of the rectangle whose border is retained in a

View File

@ -194,7 +194,7 @@ separateBorders p = Widget (hSize p) (vSize p) $
--
-- Frozen borders cannot be thawed.
freezeBorders :: Widget n -> Widget n
freezeBorders p = Widget (hSize p) (vSize p) $ (bordersL .~ BM.empty) <$> render p
freezeBorders p = Widget (hSize p) (vSize p) $ (bordersL %~ BM.clear) <$> render p
-- | The empty widget.
emptyWidget :: Widget n