{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Safe #-}
module Data.RangeSet.IntMap (
RIntSet
, (\\)
, null
, isFull
, size
, member
, notMember
, lookupLT
, lookupGT
, lookupLE
, lookupGE
, containsRange
, isSubsetOf
, valid
, empty
, full
, singleton
, singletonRange
, insert
, insertRange
, delete
, deleteRange
, union
, difference
, intersection
, split
, splitMember
, findMin
, findMax
, complement
, elems
, toList
, fromList
, fromAscList
, toAscList
, toRangeList
, fromRangeList
, fromRList
, toRList
, fromNormalizedRangeList
) where
import Prelude hiding (filter, foldl, foldr, map, null)
import Control.DeepSeq (NFData (..))
import qualified Data.Foldable as Fold
import Data.Functor ((<$>))
import qualified Data.IntMap.Strict as Map
import Data.Monoid (Monoid (..), getSum)
import Data.Semigroup (Semigroup (..))
import Data.Typeable (Typeable)
import Data.RangeSet.Internal
import qualified Data.RangeSet.List as RList
newtype RIntSet = RSet (Map.IntMap Int)
deriving (Eq, Ord, Typeable)
instance Show RIntSet where
showsPrec d x = showParen (d > 10)
$ showString "fromRangeList "
. showsPrec 11 (toRangeList x)
instance Semigroup RIntSet where
(<>) = union
instance Monoid RIntSet where
mempty = empty
mappend = union
instance NFData RIntSet where
rnf (RSet xs) = rnf xs
infixl 9 \\
(\\) :: RIntSet -> RIntSet -> RIntSet
m1 \\ m2 = difference m1 m2
null :: RIntSet -> Bool
null (RSet m) = Map.null m
isFull :: RIntSet -> Bool
isFull = (==) full
size :: RIntSet -> Int
size (RSet xm) = getSum $ Map.foldMapWithKey rangeSize xm
contains' :: Int -> Int -> RIntSet -> Bool
contains' x y (RSet xm) = Fold.any ((y <=) . snd) $ Map.lookupLE x xm
member :: Int -> RIntSet -> Bool
member x = contains' x x
notMember :: Int -> RIntSet -> Bool
notMember a r = not $ member a r
lookupLT :: Int -> RIntSet -> Maybe Int
lookupLT x (RSet xm) = min (pred x) . snd <$> Map.lookupLT x xm
lookupGT :: Int -> RIntSet -> Maybe Int
lookupGT x (RSet xm)
| Just (_, b) <- Map.lookupLE x xm, x < b = Just (succ x)
| otherwise = fst <$> Map.lookupGT x xm
lookupLE :: Int -> RIntSet -> Maybe Int
lookupLE x (RSet xm) = min x . snd <$> Map.lookupLE x xm
lookupGE :: Int -> RIntSet -> Maybe Int
lookupGE x (RSet xm)
| Just (_, b) <- Map.lookupLE x xm, x <= b = Just x
| otherwise = fst <$> Map.lookupGT x xm
containsRange :: (Int, Int) -> RIntSet -> Bool
containsRange (x,y) s
| x <= y = contains' x y s
| otherwise = True
isSubsetOf :: RIntSet -> RIntSet -> Bool
isSubsetOf x y = isSubsetRangeList (toRangeList x) (toRangeList y)
empty :: RIntSet
empty = RSet Map.empty
full :: RIntSet
full = singletonRange' minBound maxBound
singletonRange' :: Int -> Int -> RIntSet
singletonRange' x y = RSet $ Map.singleton x y
singleton :: Int -> RIntSet
singleton x = singletonRange' x x
singletonRange :: (Int, Int) -> RIntSet
singletonRange (x, y) | x > y = empty
| otherwise = singletonRange' x y
insertRange' :: Int -> Int -> RIntSet -> RIntSet
insertRange' x y s = unRangeList $ insertRangeList x y $ toRangeList s
insert :: Int -> RIntSet -> RIntSet
insert x = insertRange' x x
insertRange :: (Int, Int) -> RIntSet -> RIntSet
insertRange (x, y) set
| x > y = set
| otherwise = insertRange' x y set
deleteRange' :: Int -> Int -> RIntSet -> RIntSet
deleteRange' x y s = unRangeList $ deleteRangeList x y $ toRangeList s
delete :: Int -> RIntSet -> RIntSet
delete x = deleteRange' x x
deleteRange :: (Int, Int) -> RIntSet -> RIntSet
deleteRange (x, y) set
| x > y = set
| otherwise = deleteRange' x y set
union :: RIntSet -> RIntSet -> RIntSet
union x y = unRangeList $ unionRangeList (toRangeList x) (toRangeList y)
difference :: RIntSet -> RIntSet -> RIntSet
difference x y = unRangeList $ differenceRangeList (toRangeList x) (toRangeList y)
intersection :: RIntSet -> RIntSet -> RIntSet
intersection x y = unRangeList $ intersectRangeList (toRangeList x) (toRangeList y)
complement :: RIntSet -> RIntSet
complement = unRangeList . complementRangeList . toRangeList
split :: Int -> RIntSet -> (RIntSet, RIntSet)
split x s = (l, r) where (l, _, r) = splitMember x s
splitMember :: Int -> RIntSet -> (RIntSet, Bool, RIntSet)
splitMember x (RSet xm)
| Just y <- xv = (RSet ml, True, RSet $ insertIf (x < y) (succ x) y mr)
| Just ((u,v), ml') <- Map.maxViewWithKey ml =
if v < x
then (RSet ml, False, RSet mr)
else (RSet $ insertIf (u < x) u (pred x) ml', True, RSet $ insertIf (x < v) (succ x) v mr)
| otherwise = (RSet ml , False, RSet xm)
where
(ml, xv, mr) = Map.splitLookup x xm
insertIf False _ _ = id
insertIf True a b = Map.insert a b
findMin :: RIntSet -> Int
findMin (RSet m) = fst $ Map.findMin m
findMax :: RIntSet -> Int
findMax (RSet m) = snd $ Map.findMax m
unRangeList :: [(Int, Int)] -> RIntSet
unRangeList = RSet . Map.fromDistinctAscList
elems :: RIntSet -> [Int]
elems = toAscList
toList :: RIntSet -> [Int]
toList (RSet xm) = Map.foldMapWithKey enumFromTo xm
fromList :: [Int] -> RIntSet
fromList = unRangeList . fromElemList
fromAscList :: [Int] -> RIntSet
fromAscList = unRangeList . fromAscElemList
toAscList :: RIntSet -> [Int]
toAscList (RSet xm) = Map.foldrWithKey (\a -> (++) . enumFromTo a) [] xm
toRangeList :: RIntSet -> [(Int, Int)]
toRangeList (RSet xs) = Map.toAscList xs
fromRangeList :: [(Int, Int)] -> RIntSet
fromRangeList = unRangeList . normalizeRangeList
fromRList :: RList.RSet Int -> RIntSet
fromRList = fromNormalizedRangeList . RList.toRangeList
toRList :: RIntSet -> RList.RSet Int
toRList = RList.fromNormalizedRangeList . toRangeList
fromNormalizedRangeList :: [(Int, Int)] -> RIntSet
fromNormalizedRangeList = RSet . Map.fromDistinctAscList
valid :: RIntSet -> Bool
valid = validRangeList . toRangeList