{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Safe               #-}
module Data.RangeSet.List (
  
  RSet
  
  , (\\)
  
  , 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
  , fromNormalizedRangeList
  , toSet
  ) where
import           Prelude hiding (filter, foldl, foldr, map, null)
import qualified Prelude
import           Control.DeepSeq (NFData (..))
import           Data.Foldable   (foldMap)
import           Data.Hashable   (Hashable (..))
import           Data.Maybe      (isJust)
import           Data.Monoid     (Monoid (..), getSum)
import           Data.Semigroup  (Semigroup (..))
import qualified Data.Set        as Set
import           Data.Typeable   (Typeable)
import Data.RangeSet.Internal
newtype RSet a = RSet [(a, a)]
  deriving (Eq, Ord, Typeable)
instance Show a => Show (RSet a) where
  showsPrec d x = showParen (d > 10)
    $ showString "fromRangeList "
    . showsPrec 11 (toRangeList x)
instance (Ord a, Enum a) => Semigroup (RSet a) where
    (<>) = union
instance (Ord a, Enum a) => Monoid (RSet a) where
    mempty  = empty
    mappend = union
instance Hashable a => Hashable (RSet a) where
    hashWithSalt salt (RSet xs) = hashWithSalt salt xs
instance NFData a => NFData (RSet a) where
    rnf (RSet xs) = rnf xs
infixl 9 \\ 
(\\) :: (Ord a, Enum a) => RSet a -> RSet a -> RSet a
m1 \\ m2 = difference m1 m2
null :: RSet a -> Bool
null = Prelude.null . toRangeList
isFull :: (Eq a, Bounded a) => RSet a -> Bool
isFull = (==) full
size :: Enum a => RSet a -> Int
size (RSet xs) = getSum $ foldMap (uncurry rangeSize) xs
member :: Ord a => a -> RSet a -> Bool
member x (RSet xs) = f xs where
  f ((a,b):s)
    | x < a = False
    | x <= b = True
    | otherwise = f s
  f [] = False
notMember :: Ord a => a -> RSet a -> Bool
notMember a r = not $ member a r
lookupLT :: (Ord a, Enum a) => a -> RSet a -> Maybe a
lookupLT x (RSet xs) = f Nothing xs where
  f l ((a,b):s)
    | x <= a = l
    | x <= b || pred x == b = Just (pred x)
    | otherwise = f (Just b) s
  f l [] = l
lookupGT :: (Ord a, Enum a) => a -> RSet a -> Maybe a
lookupGT x (RSet xs) = f xs where
  f ((a,b):s)
    | x < a = Just a
    | x < b = Just (succ x)
    | otherwise = f s
  f [] = Nothing
lookupLE :: Ord a => a -> RSet a -> Maybe a
lookupLE x (RSet xs) = f Nothing xs where
  f l ((a,b):s)
    | x < a = l
    | x <= b = Just x
    | otherwise = f (Just b) s
  f l [] = l
lookupGE :: Ord a => a -> RSet a -> Maybe a
lookupGE x (RSet xs) = f xs where
  f ((a,b):s)
    | x <= a = Just a
    | x <= b = Just x
    | otherwise = f s
  f [] = Nothing
containsRange :: Ord a => (a, a) -> RSet a -> Bool
containsRange (x,y) (RSet xs)
  | x <= y = isJust $ rangeIsSubsetList x y xs
  | otherwise = True
isSubsetOf :: Ord a => RSet a -> RSet a -> Bool
isSubsetOf (RSet xs) (RSet ys) = isSubsetRangeList xs ys
empty :: RSet a
empty = RSet []
full :: Bounded a => RSet a
full = singletonRange' minBound maxBound
singletonRange' :: a -> a -> RSet a
singletonRange' x y = RSet [(x, y)]
singleton :: a -> RSet a
singleton x = singletonRange' x x
singletonRange :: Ord a => (a, a) -> RSet a
singletonRange (x, y) | x > y     = empty
                      | otherwise = singletonRange' x y
insert :: (Ord a, Enum a) => a -> RSet a -> RSet a
insert x (RSet xs) = RSet $ insertRangeList x x xs
insertRange :: (Ord a, Enum a) => (a, a) -> RSet a -> RSet a
insertRange (x, y) set@(RSet xs)
  | x > y      = set
  | otherwise  = RSet $ insertRangeList x y xs
delete :: (Ord a, Enum a) => a -> RSet a -> RSet a
delete x (RSet xs) = RSet $ deleteRangeList x x xs
deleteRange :: (Ord a, Enum a) => (a, a) -> RSet a -> RSet a
deleteRange (x, y) set@(RSet xs)
  | x > y      = set
  | otherwise  = RSet $ deleteRangeList x y xs
union :: (Ord a, Enum a) => RSet a -> RSet a -> RSet a
union (RSet xs) (RSet ys) = RSet $ unionRangeList xs ys
difference :: (Ord a, Enum a) => RSet a -> RSet a -> RSet a
difference (RSet xs) (RSet ys) = RSet $ differenceRangeList xs ys
intersection :: (Ord a) => RSet a -> RSet a -> RSet a
intersection (RSet xs) (RSet ys) = RSet $ intersectRangeList xs ys
complement :: (Ord a, Enum a, Bounded a) => RSet a -> RSet a
complement (RSet xs) = RSet $ complementRangeList xs
split :: (Ord a, Enum a) => a -> RSet a -> (RSet a, RSet a)
split x s = (l, r) where (l, _, r) = splitMember x s
splitMember :: (Ord a, Enum a) => a -> RSet a -> (RSet a, Bool, RSet a)
splitMember x (RSet xs) = f xs where
  f s@(r@(a,b):s') = case compare x a of
    LT -> (empty, False, RSet s)
    EQ -> (empty, True, RSet xs')
    GT
      | x <= b -> (RSet [(a, pred x)], True, RSet xs')
      | otherwise -> push r $ f s'
    where
    xs'
      | x < b = (succ x,b):s'
      | otherwise = s'
  f [] = (empty, False, empty)
  push r (RSet ls, b, RSet rs) = (RSet (r:ls), b, RSet rs)
findMin :: RSet a -> a
findMin (RSet ((x, _) : _))  = x
findMin _                    = error "RangeSet.List.findMin: empty set"
findMax :: RSet a -> a
findMax (RSet rs) = findMax' rs
  where findMax' [(_, x)]  = x
        findMax' (_:xs)    = findMax' xs
        findMax' _         = error "RangeSet.List.findMax: empty set"
elems :: Enum a => RSet a -> [a]
elems = toAscList
toList :: Enum a => RSet a -> [a]
toList (RSet xs) = concatMap (uncurry enumFromTo) xs
fromList :: (Ord a, Enum a) => [a] -> RSet a
fromList = RSet . fromElemList
fromAscList :: (Ord a, Enum a) => [a] -> RSet a
fromAscList = RSet . fromAscElemList
toAscList :: Enum a => RSet a -> [a]
toAscList = toList
toRangeList :: RSet a -> [(a, a)]
toRangeList (RSet xs) = xs
fromRangeList :: (Ord a, Enum a) => [(a, a)] -> RSet a
fromRangeList = RSet . normalizeRangeList
toSet :: Enum a => RSet a -> Set.Set a
toSet = Set.fromDistinctAscList . toAscList
fromNormalizedRangeList :: [(a, a)] -> RSet a
fromNormalizedRangeList = RSet
valid :: (Ord a, Enum a, Bounded a) => RSet a -> Bool
valid (RSet xs) = validRangeList xs