module Yi.Region
( Region
, emptyRegion
, regionIsEmpty
, mkRegion, mkRegion', mkSizeRegion
, regionStart
, regionEnd
, regionSize
, regionDirection
, inRegion, nearRegion
, includedRegion
, fmapRegion
, intersectRegion
, unionRegion
, regionFirst, regionLast, regionsOverlap
) where
import Yi.Buffer.Basic
import Yi.Utils
import Data.Typeable
import Data.Binary
import GHC.Generics (Generic)
#ifdef TESTING
import Test.QuickCheck
#endif
data Region = Region
{ regionDirection :: !Direction
, regionStart, regionEnd :: !Point
} deriving (Typeable, Generic)
instance Binary Region
#ifdef TESTING
instance Arbitrary Region where
arbitrary = sized $ \size -> do
x0 :: Int <- arbitrary
return $ mkRegion (fromIntegral x0) (fromIntegral (x0 + size))
#endif
instance Show Region where
show r = show (regionStart r) ++
(case regionDirection r of
Forward -> " -> "
Backward -> " <- "
) ++
show (regionEnd r)
regionFirst :: Region -> Point
regionFirst (Region Forward p _) = p
regionFirst (Region Backward _ p) = p
regionLast :: Region -> Point
regionLast (Region Forward _ p) = p
regionLast (Region Backward p _) = p
fmapRegion :: (Point -> Point) -> Region -> Region
fmapRegion f (Region d x y) = Region d (f x) (f y)
regionSize :: Region -> Size
regionSize r = regionEnd r ~- regionStart r
intersectRegion :: Region -> Region -> Region
intersectRegion (Region _ x1 y1) (Region _ x2 y2) = ordRegion (max x1 x2) (min y1 y2)
unionRegion :: Region -> Region -> Region
unionRegion (Region _ x1 y1) (Region _ x2 y2) = mkRegion (min x1 x2) (max y1 y2)
ordRegion :: Point -> Point -> Region
ordRegion x y = if x < y then Region Forward x y else emptyRegion
mkRegion :: Point -> Point -> Region
mkRegion x y = if x <= y then Region Forward x y else Region Backward y x
mkRegion' :: Direction -> Point -> Point -> Region
mkRegion' d x y = if x <= y then Region d x y else Region d y x
mkSizeRegion :: Point -> Size -> Region
mkSizeRegion x s = mkRegion x (x +~ s)
emptyRegion :: Region
emptyRegion = Region Forward 0 0
inRegion :: Point -> Region -> Bool
p `inRegion` (Region _ start stop) = start <= p && p < stop
nearRegion :: Point -> Region -> Bool
p `nearRegion` (Region _ start stop) = start <= p && p <= stop
includedRegion :: Region -> Region -> Bool
r0 `includedRegion` r = regionStart r <= regionStart r0 && regionEnd r0 <= regionEnd r
regionIsEmpty :: Region -> Bool
regionIsEmpty (Region _ start stop) = start >= stop
regionsOverlap :: Bool -> Region -> Region -> Bool
regionsOverlap border (Region _ x1 y1) (Region _ x2 y2) =
cmp x2 y1 y2 || cmp x2 x1 y2 ||
cmp x1 y2 y1 || cmp x1 x2 y1
where
cmp a b c = a <= b && if border then b <=c else b < c