{-# LANGUAGE CPP, TypeFamilies #-}
module Data.SortedList (
    
    SortedList
    
  , toSortedList
  , fromSortedList
    
  , singleton
  , repeat
  , replicate
  , iterate
    
  , uncons
    
  , insert
    
  , delete
    
  , take
  , drop
  , splitAt
  , takeWhile
  , dropWhile
  , span
    
  , partition
  , filter
  , filterLT
  , filterGT
  , filterLE
  , filterGE
    
#if !MIN_VERSION_base(4,8,0)
  , null
#endif
  , elemOrd
  , findIndices
    
  , map
  , mapDec
    
  , unfoldr
    
#if MIN_VERSION_base(4,6,0)
  , reverse, reverseDown
#endif
    
  , nub
  , intersect
  , union
  ) where
import Prelude hiding
  ( take, drop, splitAt, filter
  , repeat, replicate, iterate
  , null, map, reverse
  , span, takeWhile, dropWhile
#if !MIN_VERSION_base(4,8,0)
  , foldr, foldl
#endif
    )
import qualified Data.List as List
import Control.DeepSeq (NFData (..))
import Data.Foldable (Foldable (..))
#if MIN_VERSION_base(4,5,0) && !MIN_VERSION_base(4,9,0)
import Data.Monoid ((<>))
#endif
#if MIN_VERSION_base(4,6,0)
import Data.Ord (Down (..))
#endif
#if MIN_VERSION_base(4,7,0)
import qualified GHC.Exts as Exts
#endif
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid (..))
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup (..))
#endif
newtype SortedList a = SortedList [a] deriving (Eq, Ord)
instance Show a => Show (SortedList a) where
  show = show . fromSortedList
instance NFData a => NFData (SortedList a) where
  {-# INLINE rnf #-}
  rnf (SortedList xs) = rnf xs
#if MIN_VERSION_base(4,7,0)
instance Ord a => Exts.IsList (SortedList a) where
  type (Item (SortedList a)) = a
  fromList = toSortedList
  toList = fromSortedList
#endif
#if !MIN_VERSION_base(4,8,0)
null :: SortedList a -> Bool
null = List.null . fromSortedList
#endif
uncons :: SortedList a -> Maybe (a, SortedList a)
uncons (SortedList []) = Nothing
uncons (SortedList (x:xs)) = Just (x, SortedList xs)
toSortedList :: Ord a => [a] -> SortedList a
toSortedList = SortedList . List.sort
fromSortedList :: SortedList a -> [a]
fromSortedList (SortedList xs) = xs
mergeSortedLists :: Ord a => [a] -> [a] -> [a]
mergeSortedLists xs [] = xs
mergeSortedLists [] ys = ys
mergeSortedLists (x:xs) (y:ys) =
  if x <= y
     then x : mergeSortedLists xs (y:ys)
     else y : mergeSortedLists (x:xs) ys
#if MIN_VERSION_base(4,9,0)
instance Ord a => Semigroup (SortedList a) where
  SortedList xs <> SortedList ys = SortedList $ mergeSortedLists xs ys
instance Ord a => Monoid (SortedList a) where
  mempty = SortedList []
  mappend = (<>)
#else
instance Ord a => Monoid (SortedList a) where
  mempty = SortedList []
  mappend (SortedList xs) (SortedList ys) = SortedList $ mergeSortedLists xs ys
#endif
singleton :: a -> SortedList a
singleton x = SortedList [x]
repeat :: a -> SortedList a
repeat = SortedList . List.repeat
replicate :: Int -> a -> SortedList a
replicate n = SortedList . List.replicate n
unfoldr :: Ord a => (b -> Maybe (a,b)) -> b -> SortedList a
unfoldr f e = SortedList $
  let g (prev,acc) = do
        (curr,acc') <- f acc
        if prev <= curr
           then Just (curr, (curr, acc'))
           else Nothing
  in  case f e of
        Just (x0,e') -> x0 : List.unfoldr g (x0,e')
        _ -> []
iterate :: Ord a => (a -> a) -> a -> SortedList a
iterate f = unfoldr $ \x -> Just (x, f x)
insert :: Ord a => a -> SortedList a -> SortedList a
#if MIN_VERSION_base(4,5,0)
insert x xs = singleton x <> xs
#else
insert x xs = mappend (singleton x) xs
#endif
delete :: Eq a => a -> SortedList a -> SortedList a
{-# INLINE delete #-}
delete x (SortedList xs) = SortedList $ List.delete x xs
take :: Int -> SortedList a -> SortedList a
take n = fst . splitAt n
drop :: Int -> SortedList a -> SortedList a
drop n = snd . splitAt n
splitAt :: Int -> SortedList a -> (SortedList a, SortedList a)
splitAt n (SortedList xs) =
  let (ys,zs) = List.splitAt n xs
  in  (SortedList ys, SortedList zs)
partition :: (a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
partition f (SortedList xs) =
  let (ys,zs) = List.partition f xs
  in  (SortedList ys, SortedList zs)
filter :: (a -> Bool) -> SortedList a -> SortedList a
filter f = fst . partition f
filterLT :: Ord a => a -> SortedList a -> SortedList a
filterLT a (SortedList l) = SortedList $ go l
  where
    go (x:xs) = if x < a then x : go xs else []
    go [] = []
filterGT :: Ord a => a -> SortedList a -> SortedList a
filterGT a (SortedList l) = SortedList $ go l
  where
    go (x:xs) = if a < x then x : xs else go xs
    go [] = []
filterLE :: Ord a => a -> SortedList a -> SortedList a
filterLE a (SortedList l) = SortedList $ go l
  where
    go (x:xs) = if x <= a then x : go xs else []
    go [] = []
filterGE :: Ord a => a -> SortedList a -> SortedList a
filterGE a (SortedList l) = SortedList $ go l
  where
    go (x:xs) = if a <= x then x : xs else go xs
    go [] = []
elemOrd :: Ord a => a -> SortedList a -> Bool
elemOrd a (SortedList l) = go l
    where
      go (x:xs) =
        case compare a x of
          GT -> go xs
          EQ -> True
          _  -> False
      go _ = False
nub :: Eq a => SortedList a -> SortedList a
nub (SortedList l) = SortedList $ go l
  where
    go (x:y:xs) = if x == y then go (x:xs) else x : go (y:xs)
    go xs = xs
instance Foldable SortedList where
  {-# INLINE foldr #-}
  foldr f e (SortedList xs) = foldr f e xs
#if MIN_VERSION_base(4,8,0)
  {-# INLINE toList #-}
  toList = fromSortedList
  minimum (SortedList xs) =
    case xs of
      x : _ -> x
      _ -> error "SortedList.minimum: empty list"
  maximum (SortedList xs) =
    case xs of
      [] -> error "SortedList.maximum: empty list"
      _ -> last xs
#endif
map :: Ord b => (a -> b) -> SortedList a -> SortedList b
{-# INLINE[1] map #-}
map f = foldr (insert . f) mempty
mapDec :: Ord b => (a -> b) -> SortedList a -> SortedList b
{-# INLINE[1] mapDec #-}
mapDec f = foldl (\xs x -> insert (f x) xs) mempty
{-# RULES
"SortedList:map/map" forall f g xs. map f (map g xs) = map (f . g) xs
"SortedList:map/id"  forall xs.     map id xs = xs
"SortedList:mapDec/mapDec" forall f g xs. mapDec f (map g xs) = mapDec (f . g) xs
"SortedList:mapDec/map" forall f g xs. mapDec f (map g xs) = map (f . g) xs
"SortedList:map/mapDec" forall f g xs. map f (mapDec g xs) = map (f . g) xs
"SortedList:mapDec/id"  forall xs.     mapDec id xs = xs
  #-}
#if MIN_VERSION_base(4,6,0)
reverse :: SortedList a -> SortedList (Down a)
{-# INLINE[2] reverse #-}
reverse = SortedList . List.reverse . fmap Down . fromSortedList
{-# RULES
"SortedList:map/Down" forall xs. map Down xs = reverse xs
  #-}
reverseDown :: SortedList (Down a) -> SortedList a
{-# INLINE[2] reverseDown #-}
reverseDown = SortedList . List.reverse . fmap unDown . fromSortedList
  where
    unDown (Down a) = a
#endif
span :: (a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
span f (SortedList xs) =
  let (ys,zs) = List.span f xs
  in  (SortedList ys, SortedList zs)
takeWhile :: (a -> Bool) -> SortedList a -> SortedList a
takeWhile f = fst . span f
dropWhile :: (a -> Bool) -> SortedList a -> SortedList a
dropWhile f = snd . span f
findIndices :: (a -> Bool) -> SortedList a -> SortedList Int
findIndices f (SortedList xs) = SortedList $ List.findIndices f xs
intersect :: Ord a => SortedList a -> SortedList a -> SortedList a
intersect xs ys =
  let SortedList xs' = xs
      SortedList ys' = nub ys
      go [] _  = []
      go _  [] = []
      go pp@(p:ps) qq@(q:qs) =
        case p `compare` q of
          LT ->     go ps qq
          EQ -> p : go ps qq
          GT ->     go pp qs
  in  SortedList $ go xs' ys'
union :: Ord a => SortedList a -> SortedList a -> SortedList a
union xs ys = xs `mappend` foldl (flip delete) (nub ys) xs