{-# LANGUAGE CPP, TypeFamilies #-}

-- | This module defines a type for sorted lists, together
--   with several functions to create and use values of that
--   type. Many operations are optimized to take advantage
--   of the list being sorted.
module Data.SortedList (
    -- * Type
    SortedList
    -- * List conversions
  , toSortedList
  , fromSortedList
    -- * Construction
  , singleton
  , repeat
  , replicate
  , iterate
    -- * Deconstruction
  , uncons
    -- * Inserting
  , insert
    -- * Deleting
  , delete
    -- * Sublists
  , take
  , drop
  , splitAt
  , takeWhile
  , dropWhile
  , span
    -- ** Filtering
  , partition
  , filter
  , filterLT
  , filterGT
  , filterLE
  , filterGE
    -- * Queries
#if !MIN_VERSION_base(4,8,0)
  , null
#endif
  , elemOrd
  , findIndices
    -- * @map@ function
  , map
  , mapDec
    -- * Unfolding
  , unfoldr
    -- * Others
#if MIN_VERSION_base(4,6,0)
  , reverse, reverseDown
#endif
    -- * Set operations
  , 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

-- | Type of sorted lists. Any (non-bottom) value of this type
--   is a sorted list. Use the 'Monoid' instance to merge sorted
--   lists.
newtype SortedList a = SortedList [a] deriving (SortedList a -> SortedList a -> Bool
forall a. Eq a => SortedList a -> SortedList a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortedList a -> SortedList a -> Bool
$c/= :: forall a. Eq a => SortedList a -> SortedList a -> Bool
== :: SortedList a -> SortedList a -> Bool
$c== :: forall a. Eq a => SortedList a -> SortedList a -> Bool
Eq, SortedList a -> SortedList a -> Bool
SortedList a -> SortedList a -> Ordering
SortedList a -> SortedList a -> SortedList a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (SortedList a)
forall a. Ord a => SortedList a -> SortedList a -> Bool
forall a. Ord a => SortedList a -> SortedList a -> Ordering
forall a. Ord a => SortedList a -> SortedList a -> SortedList a
min :: SortedList a -> SortedList a -> SortedList a
$cmin :: forall a. Ord a => SortedList a -> SortedList a -> SortedList a
max :: SortedList a -> SortedList a -> SortedList a
$cmax :: forall a. Ord a => SortedList a -> SortedList a -> SortedList a
>= :: SortedList a -> SortedList a -> Bool
$c>= :: forall a. Ord a => SortedList a -> SortedList a -> Bool
> :: SortedList a -> SortedList a -> Bool
$c> :: forall a. Ord a => SortedList a -> SortedList a -> Bool
<= :: SortedList a -> SortedList a -> Bool
$c<= :: forall a. Ord a => SortedList a -> SortedList a -> Bool
< :: SortedList a -> SortedList a -> Bool
$c< :: forall a. Ord a => SortedList a -> SortedList a -> Bool
compare :: SortedList a -> SortedList a -> Ordering
$ccompare :: forall a. Ord a => SortedList a -> SortedList a -> Ordering
Ord)

instance Show a => Show (SortedList a) where
  show :: SortedList a -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SortedList a -> [a]
fromSortedList

instance NFData a => NFData (SortedList a) where
  {-# INLINE rnf #-}
  rnf :: SortedList a -> ()
rnf (SortedList [a]
xs) = forall a. NFData a => a -> ()
rnf [a]
xs

#if MIN_VERSION_base(4,7,0)
instance Ord a => Exts.IsList (SortedList a) where
  type (Item (SortedList a)) = a
  fromList :: [Item (SortedList a)] -> SortedList a
fromList = forall a. Ord a => [a] -> SortedList a
toSortedList
  toList :: SortedList a -> [Item (SortedList a)]
toList = forall a. SortedList a -> [a]
fromSortedList
#endif

#if !MIN_VERSION_base(4,8,0)
-- | Check if a sorted list is empty.
--
--   /This function dissappears in @base@ version 4.8.0.0 in favor of @null@/
--   /from "Data.Foldable"./
null :: SortedList a -> Bool
null = List.null . fromSortedList
#endif

-- | /O(1)/. Decompose a sorted list into its minimal element and the rest.
--   If the list is empty, it returns 'Nothing'.
uncons :: SortedList a -> Maybe (a, SortedList a)
uncons :: forall a. SortedList a -> Maybe (a, SortedList a)
uncons (SortedList []) = forall a. Maybe a
Nothing
uncons (SortedList (a
x:[a]
xs)) = forall a. a -> Maybe a
Just (a
x, forall a. [a] -> SortedList a
SortedList [a]
xs)

-- | Create a 'SortedList' by sorting a regular list.
toSortedList :: Ord a => [a] -> SortedList a
toSortedList :: forall a. Ord a => [a] -> SortedList a
toSortedList = forall a. [a] -> SortedList a
SortedList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
List.sort

-- | /O(1)/. Create a list from a 'SortedList'. The returned list
--   is guaranteed to be sorted.
fromSortedList :: SortedList a -> [a]
fromSortedList :: forall a. SortedList a -> [a]
fromSortedList (SortedList [a]
xs) = [a]
xs

-- | Merge two sorted lists. This assumes that both input lists
--   are sorted.
mergeSortedLists :: Ord a => [a] -> [a] -> [a]
mergeSortedLists :: forall a. Ord a => [a] -> [a] -> [a]
mergeSortedLists [a]
xs [] = [a]
xs
mergeSortedLists [] [a]
ys = [a]
ys
mergeSortedLists (a
x:[a]
xs) (a
y:[a]
ys) =
  if a
x forall a. Ord a => a -> a -> Bool
<= a
y
     then a
x forall a. a -> [a] -> [a]
: forall a. Ord a => [a] -> [a] -> [a]
mergeSortedLists [a]
xs (a
yforall a. a -> [a] -> [a]
:[a]
ys)
     else a
y forall a. a -> [a] -> [a]
: forall a. Ord a => [a] -> [a] -> [a]
mergeSortedLists (a
xforall a. a -> [a] -> [a]
:[a]
xs) [a]
ys

#if MIN_VERSION_base(4,9,0)
instance Ord a => Semigroup (SortedList a) where
  SortedList [a]
xs <> :: SortedList a -> SortedList a -> SortedList a
<> SortedList [a]
ys = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> [a] -> [a]
mergeSortedLists [a]
xs [a]
ys
instance Ord a => Monoid (SortedList a) where
  mempty :: SortedList a
mempty = forall a. [a] -> SortedList a
SortedList []
  mappend :: SortedList a -> SortedList a -> SortedList a
mappend = forall a. Semigroup a => a -> a -> a
(<>)
#else
instance Ord a => Monoid (SortedList a) where
  mempty = SortedList []
  mappend (SortedList xs) (SortedList ys) = SortedList $ mergeSortedLists xs ys
#endif

-- | /O(1)/. Create a sorted list with only one element.
singleton :: a -> SortedList a
singleton :: forall a. a -> SortedList a
singleton a
x = forall a. [a] -> SortedList a
SortedList [a
x]

-- | An infinite list with all its elements equal to the given
--   argument.
repeat :: a -> SortedList a
repeat :: forall a. a -> SortedList a
repeat = forall a. [a] -> SortedList a
SortedList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a]
List.repeat

-- | Replicate a given number of times a single element.
replicate :: Int -> a -> SortedList a
replicate :: forall a. Int -> a -> SortedList a
replicate Int
n = forall a. [a] -> SortedList a
SortedList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> a -> [a]
List.replicate Int
n

-- | Dual (sort of) to 'foldr' for sorted lists. It builds a sorted list from
--   a generator function and an initial element. The generator function is
--   applied to the initial element, and then it will produce either 'Nothing'
--   - meaning that the list building must stop - or 'Just' applied to the
--   value that is going to be added to the list, and a new accumulator to be fed
--   to the generator function. The list building will stop prematurely if the
--   generator function happens to create an element for the list that is strictly
--   smaller than the previous value.
unfoldr :: Ord a => (b -> Maybe (a,b)) -> b -> SortedList a
unfoldr :: forall a b. Ord a => (b -> Maybe (a, b)) -> b -> SortedList a
unfoldr b -> Maybe (a, b)
f b
e = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$
  let g :: (a, b) -> Maybe (a, (a, b))
g (a
prev,b
acc) = do
        (a
curr,b
acc') <- b -> Maybe (a, b)
f b
acc
        if a
prev forall a. Ord a => a -> a -> Bool
<= a
curr
           then forall a. a -> Maybe a
Just (a
curr, (a
curr, b
acc'))
           else forall a. Maybe a
Nothing
  in  case b -> Maybe (a, b)
f b
e of
        Just (a
x0,b
e') -> a
x0 forall a. a -> [a] -> [a]
: forall b a. (b -> Maybe (a, b)) -> b -> [a]
List.unfoldr (a, b) -> Maybe (a, (a, b))
g (a
x0,b
e')
        Maybe (a, b)
_ -> []

-- | Create a sorted list by repeatedly applying the same
--   function to an element, until the image by that function
--   is stricly less than its argument. In other words:
--
-- > iterate f x = [x, f x, f (f x), ... ]
--
--   With the list ending whenever
--   @f (f (... (f (f x)) ...)) < f (... (f (f x)) ...)@.
--   If this never happens, the list will be infinite.
--
--   By definition:
--
-- > iterate f = unfoldr (\x -> Just (x, f x))
--
iterate :: Ord a => (a -> a) -> a -> SortedList a
iterate :: forall a. Ord a => (a -> a) -> a -> SortedList a
iterate a -> a
f = forall a b. Ord a => (b -> Maybe (a, b)) -> b -> SortedList a
unfoldr forall a b. (a -> b) -> a -> b
$ \a
x -> forall a. a -> Maybe a
Just (a
x, a -> a
f a
x)

-- | /O(n)/. Insert a new element in a sorted list.
insert :: Ord a => a -> SortedList a -> SortedList a
#if MIN_VERSION_base(4,5,0)
insert :: forall a. Ord a => a -> SortedList a -> SortedList a
insert a
x SortedList a
xs = forall a. a -> SortedList a
singleton a
x forall a. Semigroup a => a -> a -> a
<> SortedList a
xs
#else
insert x xs = mappend (singleton x) xs
#endif

-- | Delete the first occurrence of the given element.
delete :: Ord a => a -> SortedList a -> SortedList a
{-# INLINE delete #-}
delete :: forall a. Ord a => a -> SortedList a -> SortedList a
delete a
a (SortedList [a]
l) = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ [a] -> [a]
go [a]
l
  where
    go :: [a] -> [a]
go (a
x:[a]
xs) =
      case a
x forall a. Ord a => a -> a -> Ordering
`compare` a
a of
        Ordering
LT -> a
x forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
xs
        Ordering
GT -> a
x forall a. a -> [a] -> [a]
: [a]
xs
        Ordering
EQ -> [a]
xs
    go [] = []

-- | Extract the prefix with the given length from a sorted list.
take :: Int -> SortedList a -> SortedList a
take :: forall a. Int -> SortedList a -> SortedList a
take Int
n = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> SortedList a -> (SortedList a, SortedList a)
splitAt Int
n

-- | Drop the given number of elements from a sorted list, starting
--   from the smallest and following ascending order.
drop :: Int -> SortedList a -> SortedList a
drop :: forall a. Int -> SortedList a -> SortedList a
drop Int
n = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> SortedList a -> (SortedList a, SortedList a)
splitAt Int
n

-- | Split a sorted list in two sublists, with the first one having
--   length equal to the given argument, except when the length of the
--   list is less than that.
splitAt :: Int -> SortedList a -> (SortedList a, SortedList a)
splitAt :: forall a. Int -> SortedList a -> (SortedList a, SortedList a)
splitAt Int
n (SortedList [a]
xs) =
  let ([a]
ys,[a]
zs) = forall a. Int -> [a] -> ([a], [a])
List.splitAt Int
n [a]
xs
  in  (forall a. [a] -> SortedList a
SortedList [a]
ys, forall a. [a] -> SortedList a
SortedList [a]
zs)

-- | /O(n)/. Divide a sorted list into two lists, one with all the elements
--   that satisfy the given predicate, and another list with the rest of
--   elements.
partition :: (a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
partition :: forall a.
(a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
partition a -> Bool
f (SortedList [a]
xs) =
  let ([a]
ys,[a]
zs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.partition a -> Bool
f [a]
xs
  in  (forall a. [a] -> SortedList a
SortedList [a]
ys, forall a. [a] -> SortedList a
SortedList [a]
zs)

-- | /O(n)/. Extract the elements of a list that satisfy the predicate.
filter :: (a -> Bool) -> SortedList a -> SortedList a
filter :: forall a. (a -> Bool) -> SortedList a -> SortedList a
filter a -> Bool
f = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
partition a -> Bool
f

-- | /O(n)/. Select only elements that are strictly less than the argument.
filterLT :: Ord a => a -> SortedList a -> SortedList a
filterLT :: forall a. Ord a => a -> SortedList a -> SortedList a
filterLT a
a (SortedList [a]
l) = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ [a] -> [a]
go [a]
l
  where
    go :: [a] -> [a]
go (a
x:[a]
xs) = if a
x forall a. Ord a => a -> a -> Bool
< a
a then a
x forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
xs else []
    go [] = []

-- | /O(n)/. Select only elements that are strictly greater than the argument.
filterGT :: Ord a => a -> SortedList a -> SortedList a
filterGT :: forall a. Ord a => a -> SortedList a -> SortedList a
filterGT a
a (SortedList [a]
l) = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ [a] -> [a]
go [a]
l
  where
    go :: [a] -> [a]
go (a
x:[a]
xs) = if a
a forall a. Ord a => a -> a -> Bool
< a
x then a
x forall a. a -> [a] -> [a]
: [a]
xs else [a] -> [a]
go [a]
xs
    go [] = []

-- | /O(n)/. Select only elements less or equal to the argument.
filterLE :: Ord a => a -> SortedList a -> SortedList a
filterLE :: forall a. Ord a => a -> SortedList a -> SortedList a
filterLE a
a (SortedList [a]
l) = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ [a] -> [a]
go [a]
l
  where
    go :: [a] -> [a]
go (a
x:[a]
xs) = if a
x forall a. Ord a => a -> a -> Bool
<= a
a then a
x forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
xs else []
    go [] = []

-- | /O(n)/. Select only elements greater or equal to the argument.
filterGE :: Ord a => a -> SortedList a -> SortedList a
filterGE :: forall a. Ord a => a -> SortedList a -> SortedList a
filterGE a
a (SortedList [a]
l) = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ [a] -> [a]
go [a]
l
  where
    go :: [a] -> [a]
go (a
x:[a]
xs) = if a
a forall a. Ord a => a -> a -> Bool
<= a
x then a
x forall a. a -> [a] -> [a]
: [a]
xs else [a] -> [a]
go [a]
xs
    go [] = []

-- | /O(n)/. An efficient implementation of 'elem', using the 'Ord'
--   instance of the elements in a sorted list. It only traverses
--   the whole list if the requested element is greater than all
--   the elements in the sorted list.
elemOrd :: Ord a => a -> SortedList a -> Bool
elemOrd :: forall a. Ord a => a -> SortedList a -> Bool
elemOrd a
a (SortedList [a]
l) = [a] -> Bool
go [a]
l
    where
      go :: [a] -> Bool
go (a
x:[a]
xs) =
        case forall a. Ord a => a -> a -> Ordering
compare a
a a
x of
          Ordering
GT -> [a] -> Bool
go [a]
xs
          Ordering
EQ -> Bool
True
          Ordering
_  -> Bool
False
      go [a]
_ = Bool
False

-- | /O(n)/. Remove duplicate elements from a sorted list.
nub :: Eq a => SortedList a -> SortedList a
nub :: forall a. Eq a => SortedList a -> SortedList a
nub (SortedList [a]
l) = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ forall {a}. Eq a => [a] -> [a]
go [a]
l
  where
    go :: [a] -> [a]
go (a
x:a
y:[a]
xs) = if a
x forall a. Eq a => a -> a -> Bool
== a
y then [a] -> [a]
go (a
xforall a. a -> [a] -> [a]
:[a]
xs) else a
x forall a. a -> [a] -> [a]
: [a] -> [a]
go (a
yforall a. a -> [a] -> [a]
:[a]
xs)
    go [a]
xs = [a]
xs

instance Foldable SortedList where
  {-# INLINE foldr #-}
  foldr :: forall a b. (a -> b -> b) -> b -> SortedList a -> b
foldr a -> b -> b
f b
e (SortedList [a]
xs) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> b -> b
f b
e [a]
xs
#if MIN_VERSION_base(4,8,0)
  {-# INLINE toList #-}
  toList :: forall a. SortedList a -> [a]
toList = forall a. SortedList a -> [a]
fromSortedList
  minimum :: forall a. Ord a => SortedList a -> a
minimum (SortedList [a]
xs) =
    case [a]
xs of
      a
x : [a]
_ -> a
x
      [a]
_ -> forall a. HasCallStack => String -> a
error String
"SortedList.minimum: empty list"
  maximum :: forall a. Ord a => SortedList a -> a
maximum (SortedList [a]
xs) =
    case [a]
xs of
      [] -> forall a. HasCallStack => String -> a
error String
"SortedList.maximum: empty list"
      [a]
_ -> forall a. [a] -> a
last [a]
xs
#endif

-- | Map a function over all the elements of a sorted list.
--   Note that 'map' will hang if the argument is an infinite list.
--
--   Even though 'SortedList' can't be made an instance of 'Functor',
--   'map' /does/ hold the 'Functor' laws (for finite lists).
--   We can't however write an instance because of the 'Ord' instance requirement on the type of
--   the elements of the result list. Therefore, while 'SortedList'
--   is not a functor type in general, it is when restricted to elements of
--   orderable types (for finite lists).
--
--   The complexity range goes from /O(n)/ (if the function is monotonically increasing)
--   to /O(n²)/ (if the function is monotonically decreasing). These are the best
--   and worst case scenarios. We provide an alternative ('mapDec') where monotonically
--   decreasing functions are the best case scenario.
map :: Ord b => (a -> b) -> SortedList a -> SortedList b
{-# INLINE[1] map #-}
map :: forall b a. Ord b => (a -> b) -> SortedList a -> SortedList b
map a -> b
f = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a. Ord a => a -> SortedList a -> SortedList a
insert forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) forall a. Monoid a => a
mempty

-- | Just like 'map', but favoring functions that are monotonically decreasing instead
--   of those that are monotonically increasing.
mapDec :: Ord b => (a -> b) -> SortedList a -> SortedList b
{-# INLINE[1] mapDec #-}
mapDec :: forall b a. Ord b => (a -> b) -> SortedList a -> SortedList b
mapDec a -> b
f = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\SortedList b
xs a
x -> forall a. Ord a => a -> SortedList a -> SortedList a
insert (a -> b
f a
x) SortedList b
xs) forall a. Monoid a => a
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)

-- | /O(n)/. Reverse a sorted list. The result uses 'Down', thus it is a sorted
--   list as well. The following equality holds for any sorted list @xs@:
--
-- > map Down xs = reverse xs
--
--   /Only available from @base@ version 4.6.0.0./
reverse :: SortedList a -> SortedList (Down a)
{-# INLINE[2] reverse #-}
reverse :: forall a. SortedList a -> SortedList (Down a)
reverse = forall a. [a] -> SortedList a
SortedList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
List.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Down a
Down forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SortedList a -> [a]
fromSortedList

{-# RULES
"SortedList:map/Down" forall xs. map Down xs = reverse xs
  #-}

-- | /O(n)/. Reverse a sorted list with elements embedded in the 'Down' type.
--
--   /Only available from @base@ version 4.6.0.0./
reverseDown :: SortedList (Down a) -> SortedList a
{-# INLINE[2] reverseDown #-}
reverseDown :: forall a. SortedList (Down a) -> SortedList a
reverseDown = forall a. [a] -> SortedList a
SortedList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
List.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a}. Down a -> a
unDown forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SortedList a -> [a]
fromSortedList
  where
    unDown :: Down a -> a
unDown (Down a
a) = a
a

#endif

-- | Return the longest prefix of a sorted list of elements that satisfy the given condition,
--   and the rest of the list.
span :: (a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
span :: forall a.
(a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
span a -> Bool
f (SortedList [a]
xs) =
  let ([a]
ys,[a]
zs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.span a -> Bool
f [a]
xs
  in  (forall a. [a] -> SortedList a
SortedList [a]
ys, forall a. [a] -> SortedList a
SortedList [a]
zs)

-- | Return the longest prefix of a sorted list of elements that satisfy the given condition.
takeWhile :: (a -> Bool) -> SortedList a -> SortedList a
takeWhile :: forall a. (a -> Bool) -> SortedList a -> SortedList a
takeWhile a -> Bool
f = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
span a -> Bool
f

-- | Return the suffix remaining after dropping the longest prefix of elements that satisfy
--   the given condition.
dropWhile :: (a -> Bool) -> SortedList a -> SortedList a
dropWhile :: forall a. (a -> Bool) -> SortedList a -> SortedList a
dropWhile a -> Bool
f = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(a -> Bool) -> SortedList a -> (SortedList a, SortedList a)
span a -> Bool
f

-- | /O(n)/. Return the indices of all elements in a sorted list that satisfy the given condition.
findIndices :: (a -> Bool) -> SortedList a -> SortedList Int
findIndices :: forall a. (a -> Bool) -> SortedList a -> SortedList Int
findIndices a -> Bool
f (SortedList [a]
xs) = forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [Int]
List.findIndices a -> Bool
f [a]
xs

-- | /O(n+m)/. Intersection of sorted lists. If the first list contains duplicates, so will the result.
intersect :: Ord a => SortedList a -> SortedList a -> SortedList a
intersect :: forall a. Ord a => SortedList a -> SortedList a -> SortedList a
intersect SortedList a
xs SortedList a
ys =
  let SortedList [a]
xs' = SortedList a
xs
      SortedList [a]
ys' = forall a. Eq a => SortedList a -> SortedList a
nub SortedList a
ys
      go :: [a] -> [a] -> [a]
go [] [a]
_  = []
      go [a]
_  [] = []
      go pp :: [a]
pp@(a
p:[a]
ps) qq :: [a]
qq@(a
q:[a]
qs) =
        case a
p forall a. Ord a => a -> a -> Ordering
`compare` a
q of
          Ordering
LT ->     [a] -> [a] -> [a]
go [a]
ps [a]
qq
          Ordering
EQ -> a
p forall a. a -> [a] -> [a]
: [a] -> [a] -> [a]
go [a]
ps [a]
qq
          Ordering
GT ->     [a] -> [a] -> [a]
go [a]
pp [a]
qs
  in  forall a. [a] -> SortedList a
SortedList forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> [a] -> [a]
go [a]
xs' [a]
ys'

-- | Union of sorted lists.
--   Duplicates, and elements of the first list, are removed from the the second list,
--   but if the first list contains duplicates, so will the result.
union :: Ord a => SortedList a -> SortedList a -> SortedList a
union :: forall a. Ord a => SortedList a -> SortedList a -> SortedList a
union SortedList a
xs SortedList a
ys = SortedList a
xs forall a. Monoid a => a -> a -> a
`mappend` forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => a -> SortedList a -> SortedList a
delete) (forall a. Eq a => SortedList a -> SortedList a
nub SortedList a
ys) SortedList a
xs