{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
module Brick.BorderMap
( BorderMap
, Edges(..)
, eTopL, eBottomL, eRightL, eLeftL
, empty, emptyCoordinates, singleton
, insertH, insertV, insert
, unsafeUnion
, coordinates, bounds
, values
, lookupRow, lookupCol, lookupH, lookupV, lookup
, setCoordinates, crop, expand
, translate
) where
import Brick.Types.Common (Edges(..), Location(..), eTopL, eBottomL, eRightL, eLeftL, origin)
import Control.Applicative (liftA2)
import Data.IMap (IMap, Run(Run))
import Prelude hiding (lookup)
import qualified Data.IMap as IM
neighbors :: Edges a -> Edges (a, a)
neighbors (Edges vt vb vl vr) = Edges horiz horiz vert vert where
horiz = (vl, vr)
vert = (vt, vb)
data BorderMap a = BorderMap
{ _coordinates :: Edges Int
, _values :: Edges (IMap a)
} deriving (Eq, Ord, Show, Functor)
emptyCoordinates :: Edges Int -> BorderMap a
emptyCoordinates cs = BorderMap { _coordinates = cs, _values = pure IM.empty }
empty :: BorderMap a
empty = emptyCoordinates (pure 0)
singleton :: Location -> a -> BorderMap a
singleton l v = translate l . insert origin v $ empty
{-# INLINE coordinates #-}
coordinates :: BorderMap a -> Edges Int
coordinates = _coordinates
bounds :: BorderMap a -> Edges (Int, Int)
bounds = neighbors . coordinates
{-# INLINE values #-}
values :: BorderMap a -> Edges (IMap a)
values = _values
insertH :: Location -> Run a -> BorderMap a -> BorderMap a
insertH = insertDirAgnostic (Edges insertPar insertPar insertPerp insertPerp) . swapLoc
where
swapLoc (Location (col, row)) = Location (row, col)
insertV :: Location -> Run a -> BorderMap a -> BorderMap a
insertV = insertDirAgnostic (Edges insertPerp insertPerp insertPar insertPar)
insertDirAgnostic
:: Edges (Location -> Run a -> Int -> (Int, Int) -> IMap a -> IMap a)
-> Location -> Run a -> BorderMap a -> BorderMap a
insertDirAgnostic insertions l r m =
m { _values = insertions <*> pure l <*> pure r <*> coordinates m <*> bounds m <*> _values m }
insertPar, insertPerp :: Location -> Run a -> Int -> (Int, Int) -> IMap a -> IMap a
insertPar (Location (kPar, kPerp)) r herePar (loPerp, hiPerp)
| kPar == herePar && loPerp <= kPerp + IM.len r - 1 && kPerp <= hiPerp
= IM.insert beg r { IM.len = end - beg + 1 }
| otherwise = id
where
beg = max kPerp loPerp
end = min (kPerp + IM.len r - 1) hiPerp
insertPerp (Location (kPar, kPerp)) r herePerp (loPar, hiPar)
| loPar <= kPar && kPar <= hiPar && kPerp <= herePerp && herePerp <= kPerp + IM.len r - 1
= IM.insert kPar r { IM.len = 1 }
| otherwise = id
insert :: Location -> a -> BorderMap a -> BorderMap a
insert l = insertV l . Run 1
lookupRow :: Int -> BorderMap a -> IMap a
lookupRow row m
| row == eTop (coordinates m) = eTop (_values m)
| row == eBottom (coordinates m) = eBottom (_values m)
| otherwise = IM.fromList
$ [(eLeft (coordinates m), Run 1 a) | Just a <- [IM.lookup row (eLeft (_values m))]]
++ [(eRight (coordinates m), Run 1 a) | Just a <- [IM.lookup row (eRight (_values m))]]
lookupCol :: Int -> BorderMap a -> IMap a
lookupCol col m
| col == eLeft (coordinates m) = eLeft (_values m)
| col == eRight (coordinates m) = eRight (_values m)
| otherwise = IM.fromList
$ [(eTop (coordinates m), Run 1 a) | Just a <- [IM.lookup col (eTop (_values m))]]
++ [(eBottom (coordinates m), Run 1 a) | Just a <- [IM.lookup col (eBottom (_values m))]]
lookupH :: Location -> Run ignored -> BorderMap a -> IMap a
lookupH (Location (col, row)) r = IM.restrict col r . lookupRow row
lookupV :: Location -> Run ignored -> BorderMap a -> IMap a
lookupV (Location (col, row)) r = IM.restrict row r . lookupCol col
lookup :: Location -> BorderMap a -> Maybe a
lookup (Location (col, row)) = IM.lookup row . lookupCol col
setCoordinates :: Edges Int -> BorderMap a -> BorderMap a
setCoordinates coordinates' m = BorderMap
{ _values = values'
, _coordinates = coordinates'
}
where
bounds' = neighbors coordinates'
values' = pure gc
<*> _coordinates m
<*> coordinates'
<*> bounds'
<*> _values m
<*> Edges { eTop = lookupRow, eBottom = lookupRow, eLeft = lookupCol, eRight = lookupCol }
gc oldPar newPar (loPerp, hiPerp) imPar lookupPerp
| oldPar == newPar = IM.restrict loPerp (Run (hiPerp-loPerp+1) ()) imPar
| otherwise = lookupPerp newPar m
crop :: Edges Int -> BorderMap a -> BorderMap a
crop cs m = setCoordinates (shrink <*> cs <*> coordinates m) m where
shrink = Edges
{ eTop = max
, eBottom = min
, eLeft = max
, eRight = min
}
expand :: Edges Int -> BorderMap a -> BorderMap a
expand cs m = setCoordinates (grow <*> cs <*> coordinates m) m where
grow = Edges
{ eTop = min
, eBottom = max
, eLeft = min
, eRight = max
}
translate :: Location -> BorderMap a -> BorderMap a
translate (Location (0, 0)) m = m
translate (Location (c, r)) m = BorderMap
{ _coordinates = liftA2 (+) cOffsets (_coordinates m)
, _values = liftA2 IM.addToKeys vOffsets (_values m)
}
where
cOffsets = Edges { eTop = r, eBottom = r, eLeft = c, eRight = c }
vOffsets = Edges { eTop = c, eBottom = c, eLeft = r, eRight = r }
unsafeUnion :: BorderMap a -> BorderMap a -> BorderMap a
unsafeUnion m m' = m { _values = liftA2 IM.unsafeUnion (_values m) (_values m') }