#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 710
#endif
module Data.IntervalMap.FingerTree (
Interval(..), low, high, point,
IntervalMap, empty, singleton, insert, union,
search, intersections, dominators,
bounds, leastView, splitAfter
) where
import qualified Data.FingerTree as FT
import Data.FingerTree (FingerTree, Measured(..), ViewL(..), (<|), (><))
import Prelude hiding (null)
#if MIN_VERSION_base(4,8,0)
import qualified Prelude (null)
#else
import Control.Applicative ((<$>))
import Data.Foldable (Foldable(foldMap))
import Data.Monoid
import Data.Traversable (Traversable(traverse))
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup
#endif
import Data.Foldable (toList)
data Interval v = Interval v v
deriving (Eq, Ord, Show)
low :: Interval v -> v
low (Interval lo _) = lo
high :: Interval v -> v
high (Interval _ hi) = hi
point :: v -> Interval v
point v = Interval v v
data Node v a = Node (Interval v) a
deriving (Eq, Ord, Show)
instance Functor (Node v) where
fmap f (Node i x) = Node i (f x)
instance Foldable (Node v) where
foldMap f (Node _ x) = f x
instance Traversable (Node v) where
traverse f (Node i x) = Node i <$> f x
data IntInterval v = NoInterval | IntInterval (Interval v) v
#if MIN_VERSION_base(4,9,0)
instance Ord v => Semigroup (IntInterval v) where
(<>) = intervalUnion
#endif
instance Ord v => Monoid (IntInterval v) where
mempty = NoInterval
#if !(MIN_VERSION_base(4,11,0))
mappend = intervalUnion
#endif
intervalUnion :: Ord v => IntInterval v -> IntInterval v -> IntInterval v
NoInterval `intervalUnion` i = i
i `intervalUnion` NoInterval = i
IntInterval _ hi1 `intervalUnion` IntInterval int2 hi2 =
IntInterval int2 (max hi1 hi2)
instance (Ord v) => Measured (IntInterval v) (Node v a) where
measure (Node i _) = IntInterval i (high i)
newtype IntervalMap v a =
IntervalMap (FingerTree (IntInterval v) (Node v a))
instance Functor (IntervalMap v) where
fmap f (IntervalMap t) = IntervalMap (FT.unsafeFmap (fmap f) t)
instance Foldable (IntervalMap v) where
foldMap f (IntervalMap t) = foldMap (foldMap f) t
#if MIN_VERSION_base(4,8,0)
null (IntervalMap t) = FT.null t
#endif
instance Traversable (IntervalMap v) where
traverse f (IntervalMap t) =
IntervalMap <$> FT.unsafeTraverse (traverse f) t
instance (Eq v, Eq a) => Eq (IntervalMap v a) where
IntervalMap xs == IntervalMap ys = toList xs == toList ys
instance (Ord v, Ord a) => Ord (IntervalMap v a) where
compare (IntervalMap xs) (IntervalMap ys) = compare (toList xs) (toList ys)
instance (Show v, Show a) => Show (IntervalMap v a) where
showsPrec p (IntervalMap ns)
| FT.null ns = showString "empty"
| otherwise =
showParen (p > 0) (showIntervals (toList ns))
where
showIntervals [] = showString "empty"
showIntervals (Node i x:ixs) =
showString "insert " . showsPrec 11 i .
showChar ' ' . showsPrec 11 x .
showString " $ " . showIntervals ixs
#if MIN_VERSION_base(4,9,0)
instance (Ord v) => Semigroup (IntervalMap v a) where
(<>) = union
#endif
instance (Ord v) => Monoid (IntervalMap v a) where
mempty = empty
#if !(MIN_VERSION_base(4,11,0))
mappend = union
#endif
empty :: (Ord v) => IntervalMap v a
empty = IntervalMap FT.empty
singleton :: (Ord v) => Interval v -> a -> IntervalMap v a
singleton i x = IntervalMap (FT.singleton (Node i x))
insert :: (Ord v) => Interval v -> a -> IntervalMap v a -> IntervalMap v a
insert (Interval lo hi) _ m | lo > hi = m
insert i x (IntervalMap t) = IntervalMap (l >< Node i x <| r)
where
(l, r) = FT.split larger t
larger (IntInterval k _) = k >= i
larger NoInterval = error "larger NoInterval"
union :: (Ord v) => IntervalMap v a -> IntervalMap v a -> IntervalMap v a
union (IntervalMap xs) (IntervalMap ys) = IntervalMap (merge1 xs ys)
where
merge1 as bs = case FT.viewl as of
EmptyL -> bs
a@(Node i _) :< as' -> l >< a <| merge2 as' r
where
(l, r) = FT.split larger bs
larger (IntInterval k _) = k >= i
larger NoInterval = error "larger NoInterval"
merge2 as bs = case FT.viewl bs of
EmptyL -> as
b@(Node i _) :< bs' -> l >< b <| merge1 r bs'
where
(l, r) = FT.split larger as
larger (IntInterval k _) = k > i
larger NoInterval = error "larger NoInterval"
intersections :: (Ord v) => Interval v -> IntervalMap v a -> [(Interval v, a)]
intersections i = inRange (low i) (high i)
dominators :: (Ord v) => Interval v -> IntervalMap v a -> [(Interval v, a)]
dominators i = inRange (high i) (low i)
search :: (Ord v) => v -> IntervalMap v a -> [(Interval v, a)]
search p = inRange p p
inRange :: (Ord v) => v -> v -> IntervalMap v a -> [(Interval v, a)]
inRange lo hi (IntervalMap t) = matches (FT.takeUntil (greater hi) t)
where
matches xs = case FT.viewl (FT.dropUntil (atleast lo) xs) of
EmptyL -> []
Node i x :< xs' -> (i, x) : matches xs'
bounds :: (Ord v) => IntervalMap v a -> Maybe (Interval v)
bounds (IntervalMap t) = case measure t of
NoInterval -> Nothing
IntInterval _ hi -> case FT.viewl t of
EmptyL -> Nothing
Node (Interval lo _) _ FT.:< _ -> Just (Interval lo hi)
leastView :: Ord v =>
IntervalMap v a -> Maybe ((Interval v, a), IntervalMap v a)
leastView (IntervalMap t) = case FT.viewl t of
EmptyL -> Nothing
Node i a FT.:< t' -> Just ((i, a), IntervalMap t')
splitAfter :: Ord v =>
v -> IntervalMap v a -> (IntervalMap v a, IntervalMap v a)
splitAfter k (IntervalMap t) = (IntervalMap before, IntervalMap after)
where
(before, after) = FT.split (greater k) t
atleast :: (Ord v) => v -> IntInterval v -> Bool
atleast k (IntInterval _ hi) = k <= hi
atleast _ NoInterval = error "atleast NoInterval"
greater :: (Ord v) => v -> IntInterval v -> Bool
greater k (IntInterval i _) = low i > k
greater _ NoInterval = error "greater NoInterval"