{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.PQueue.Prio.Min
-- Copyright   :  (c) Louis Wasserman 2010
-- License     :  BSD-style
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  portable
--
-- General purpose priority queue.
-- Each element is associated with a /key/, and the priority queue supports
-- viewing and extracting the element with the minimum key.
--
-- A worst-case bound is given for each operation. In some cases, an amortized
-- bound is also specified; these bounds do not hold in a persistent context.
--
-- This implementation is based on a binomial heap augmented with a global root.
-- The spine of the heap is maintained lazily. To force the spine of the heap,
-- use 'seqSpine'.
--
-- We do not guarantee stable behavior.
-- Ties are broken arbitrarily -- that is, if @k1 <= k2@ and @k2 <= k1@, then there
-- are no guarantees about the relative order in which @k1@, @k2@, and their associated
-- elements are returned. (Unlike Data.Map, we allow multiple elements with the
-- same key.)
--
-- This implementation offers a number of methods of the form @xxxU@, where @U@ stands for
-- unordered. No guarantees whatsoever are made on the execution or traversal order of
-- these functions.
-----------------------------------------------------------------------------
module Data.PQueue.Prio.Min (
  MinPQueue,
  -- * Construction
  empty,
  singleton,
  insert,
  insertBehind,
  union,
  unions,
  -- * Query
  null,
  size,
  -- ** Minimum view
  findMin,
  getMin,
  deleteMin,
  deleteFindMin,
  adjustMin,
  adjustMinWithKey,
  updateMin,
  updateMinWithKey,
  minView,
  minViewWithKey,
  -- * Traversal
  -- ** Map
  map,
  mapWithKey,
  mapKeys,
  mapKeysMonotonic,
  -- ** Fold
  foldrWithKey,
  foldlWithKey,
  -- ** Traverse
  traverseWithKey,
  -- * Subsets
  -- ** Indexed
  take,
  drop,
  splitAt,
  -- ** Predicates
  takeWhile,
  takeWhileWithKey,
  dropWhile,
  dropWhileWithKey,
  span,
  spanWithKey,
  break,
  breakWithKey,
  -- *** Filter
  filter,
  filterWithKey,
  partition,
  partitionWithKey,
  mapMaybe,
  mapMaybeWithKey,
  mapEither,
  mapEitherWithKey,
  -- * List operations
  -- ** Conversion from lists
  fromList,
  fromAscList,
  fromDescList,
  -- ** Conversion to lists
  keys,
  elems,
  assocs,
  toAscList,
  toDescList,
  toList,
  -- * Unordered operations
  foldrU,
  foldrWithKeyU,
  foldlU,
  foldlWithKeyU,
  traverseU,
  traverseWithKeyU,
  keysU,
  elemsU,
  assocsU,
  toListU,
  -- * Helper methods
  seqSpine
  )
  where

import qualified Data.List as List
import Data.Maybe (fromMaybe)

#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup((<>)))
#endif

import Data.PQueue.Prio.Internals

import Prelude hiding (map, filter, break, span, takeWhile, dropWhile, splitAt, take, drop, (!!), null)

#ifdef __GLASGOW_HASKELL__
import GHC.Exts (build)
import Text.Read (Lexeme(Ident), lexP, parens, prec,
  readPrec, readListPrec, readListPrecDefault)
#else
build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a]
build f = f (:) []
#endif

(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(c -> d
f .: :: (c -> d) -> (a -> b -> c) -> a -> b -> d
.: a -> b -> c
g) a
x b
y = c -> d
f (a -> b -> c
g a
x b
y)

uncurry' :: (a -> b -> c) -> (a, b) -> c
uncurry' :: (a -> b -> c) -> (a, b) -> c
uncurry' a -> b -> c
f (a
a, b
b) = a -> b -> c
f a
a b
b

infixr 8 .:

#if MIN_VERSION_base(4,9,0)
instance Ord k => Semigroup (MinPQueue k a) where
  <> :: MinPQueue k a -> MinPQueue k a -> MinPQueue k a
(<>) = MinPQueue k a -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
MinPQueue k a -> MinPQueue k a -> MinPQueue k a
union
#endif

instance Ord k => Monoid (MinPQueue k a) where
  mempty :: MinPQueue k a
mempty = MinPQueue k a
forall k a. MinPQueue k a
empty
  mappend :: MinPQueue k a -> MinPQueue k a -> MinPQueue k a
mappend = MinPQueue k a -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
MinPQueue k a -> MinPQueue k a -> MinPQueue k a
union
  mconcat :: [MinPQueue k a] -> MinPQueue k a
mconcat = [MinPQueue k a] -> MinPQueue k a
forall k a. Ord k => [MinPQueue k a] -> MinPQueue k a
unions

instance (Ord k, Show k, Show a) => Show (MinPQueue k a) where
  showsPrec :: Int -> MinPQueue k a -> ShowS
showsPrec Int
p MinPQueue k a
xs = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
    String -> ShowS
showString String
"fromAscList " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(k, a)] -> ShowS
forall a. Show a => a -> ShowS
shows (MinPQueue k a -> [(k, a)]
forall k a. Ord k => MinPQueue k a -> [(k, a)]
toAscList MinPQueue k a
xs)

instance (Read k, Read a) => Read (MinPQueue k a) where
#ifdef __GLASGOW_HASKELL__
  readPrec :: ReadPrec (MinPQueue k a)
readPrec = ReadPrec (MinPQueue k a) -> ReadPrec (MinPQueue k a)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (MinPQueue k a) -> ReadPrec (MinPQueue k a))
-> ReadPrec (MinPQueue k a) -> ReadPrec (MinPQueue k a)
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec (MinPQueue k a) -> ReadPrec (MinPQueue k a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec (MinPQueue k a) -> ReadPrec (MinPQueue k a))
-> ReadPrec (MinPQueue k a) -> ReadPrec (MinPQueue k a)
forall a b. (a -> b) -> a -> b
$ do
    Ident String
"fromAscList" <- ReadPrec Lexeme
lexP
    [(k, a)]
xs <- ReadPrec [(k, a)]
forall a. Read a => ReadPrec a
readPrec
    MinPQueue k a -> ReadPrec (MinPQueue k a)
forall (m :: * -> *) a. Monad m => a -> m a
return ([(k, a)] -> MinPQueue k a
forall k a. [(k, a)] -> MinPQueue k a
fromAscList [(k, a)]
xs)

  readListPrec :: ReadPrec [MinPQueue k a]
readListPrec = ReadPrec [MinPQueue k a]
forall a. Read a => ReadPrec [a]
readListPrecDefault
#else
  readsPrec p = readParen (p > 10) $ \r -> do
    ("fromAscList",s) <- lex r
    (xs,t) <- reads s
    return (fromAscList xs,t)
#endif


-- | The union of a list of queues: (@'unions' == 'List.foldl' 'union' 'empty'@).
unions :: Ord k => [MinPQueue k a] -> MinPQueue k a
unions :: [MinPQueue k a] -> MinPQueue k a
unions = (MinPQueue k a -> MinPQueue k a -> MinPQueue k a)
-> MinPQueue k a -> [MinPQueue k a] -> MinPQueue k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl MinPQueue k a -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
MinPQueue k a -> MinPQueue k a -> MinPQueue k a
union MinPQueue k a
forall k a. MinPQueue k a
empty

-- | /O(1)/. The minimal (key, element) in the queue. Calls 'error' if empty.
findMin :: MinPQueue k a -> (k, a)
findMin :: MinPQueue k a -> (k, a)
findMin = (k, a) -> Maybe (k, a) -> (k, a)
forall a. a -> Maybe a -> a
fromMaybe (String -> (k, a)
forall a. HasCallStack => String -> a
error String
"Error: findMin called on an empty queue") (Maybe (k, a) -> (k, a))
-> (MinPQueue k a -> Maybe (k, a)) -> MinPQueue k a -> (k, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> Maybe (k, a)
forall k a. MinPQueue k a -> Maybe (k, a)
getMin

-- | /O(log n)/. Deletes the minimal (key, element) in the queue. Returns an empty queue
-- if the queue is empty.
deleteMin :: Ord k => MinPQueue k a -> MinPQueue k a
deleteMin :: MinPQueue k a -> MinPQueue k a
deleteMin = (a -> Maybe a) -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
(a -> Maybe a) -> MinPQueue k a -> MinPQueue k a
updateMin (Maybe a -> a -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing)

-- | /O(log n)/. Delete and find the element with the minimum key. Calls 'error' if empty.
deleteFindMin :: Ord k => MinPQueue k a -> ((k, a), MinPQueue k a)
deleteFindMin :: MinPQueue k a -> ((k, a), MinPQueue k a)
deleteFindMin = ((k, a), MinPQueue k a)
-> Maybe ((k, a), MinPQueue k a) -> ((k, a), MinPQueue k a)
forall a. a -> Maybe a -> a
fromMaybe (String -> ((k, a), MinPQueue k a)
forall a. HasCallStack => String -> a
error String
"Error: deleteFindMin called on an empty queue") (Maybe ((k, a), MinPQueue k a) -> ((k, a), MinPQueue k a))
-> (MinPQueue k a -> Maybe ((k, a), MinPQueue k a))
-> MinPQueue k a
-> ((k, a), MinPQueue k a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
forall k a. Ord k => MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
minViewWithKey

-- | /O(1)/. Alter the value at the minimum key. If the queue is empty, does nothing.
adjustMin :: (a -> a) -> MinPQueue k a -> MinPQueue k a
adjustMin :: (a -> a) -> MinPQueue k a -> MinPQueue k a
adjustMin = (k -> a -> a) -> MinPQueue k a -> MinPQueue k a
forall k a. (k -> a -> a) -> MinPQueue k a -> MinPQueue k a
adjustMinWithKey ((k -> a -> a) -> MinPQueue k a -> MinPQueue k a)
-> ((a -> a) -> k -> a -> a)
-> (a -> a)
-> MinPQueue k a
-> MinPQueue k a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a) -> k -> a -> a
forall a b. a -> b -> a
const

-- | /O(log n)/. (Actually /O(1)/ if there's no deletion.) Update the value at the minimum key.
-- If the queue is empty, does nothing.
updateMin :: Ord k => (a -> Maybe a) -> MinPQueue k a -> MinPQueue k a
updateMin :: (a -> Maybe a) -> MinPQueue k a -> MinPQueue k a
updateMin = (k -> a -> Maybe a) -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
(k -> a -> Maybe a) -> MinPQueue k a -> MinPQueue k a
updateMinWithKey ((k -> a -> Maybe a) -> MinPQueue k a -> MinPQueue k a)
-> ((a -> Maybe a) -> k -> a -> Maybe a)
-> (a -> Maybe a)
-> MinPQueue k a
-> MinPQueue k a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Maybe a) -> k -> a -> Maybe a
forall a b. a -> b -> a
const

-- | /O(log n)/. Retrieves the value associated with the minimal key of the queue, and the queue
-- stripped of that element, or 'Nothing' if passed an empty queue.
minView :: Ord k => MinPQueue k a -> Maybe (a, MinPQueue k a)
minView :: MinPQueue k a -> Maybe (a, MinPQueue k a)
minView MinPQueue k a
q = do  ((k
_, a
a), MinPQueue k a
q') <- MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
forall k a. Ord k => MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
minViewWithKey MinPQueue k a
q
                (a, MinPQueue k a) -> Maybe (a, MinPQueue k a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, MinPQueue k a
q')

-- | /O(n)/. Map a function over all values in the queue.
map :: (a -> b) -> MinPQueue k a -> MinPQueue k b
map :: (a -> b) -> MinPQueue k a -> MinPQueue k b
map = (k -> a -> b) -> MinPQueue k a -> MinPQueue k b
forall k a b. (k -> a -> b) -> MinPQueue k a -> MinPQueue k b
mapWithKey ((k -> a -> b) -> MinPQueue k a -> MinPQueue k b)
-> ((a -> b) -> k -> a -> b)
-> (a -> b)
-> MinPQueue k a
-> MinPQueue k b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> k -> a -> b
forall a b. a -> b -> a
const

-- | /O(n)/. @'mapKeys' f q@ is the queue obtained by applying @f@ to each key of @q@.
mapKeys :: Ord k' => (k -> k') -> MinPQueue k a -> MinPQueue k' a
mapKeys :: (k -> k') -> MinPQueue k a -> MinPQueue k' a
mapKeys k -> k'
f MinPQueue k a
q = [(k', a)] -> MinPQueue k' a
forall k a. Ord k => [(k, a)] -> MinPQueue k a
fromList [(k -> k'
f k
k, a
a) | (k
k, a
a) <- MinPQueue k a -> [(k, a)]
forall k a. MinPQueue k a -> [(k, a)]
toListU MinPQueue k a
q]

-- | /O(n log n)/. Traverses the elements of the queue in ascending order by key.
-- (@'traverseWithKey' f q == 'fromAscList' <$> 'traverse' ('uncurry' f) ('toAscList' q)@)
--
-- If you do not care about the /order/ of the traversal, consider using 'traverseWithKeyU'.
traverseWithKey :: (Ord k, Applicative f) => (k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverseWithKey :: (k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverseWithKey k -> a -> f b
f MinPQueue k a
q = case MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
forall k a. Ord k => MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
minViewWithKey MinPQueue k a
q of
  Maybe ((k, a), MinPQueue k a)
Nothing      -> MinPQueue k b -> f (MinPQueue k b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure MinPQueue k b
forall k a. MinPQueue k a
empty
  Just ((k
k, a
a), MinPQueue k a
q')  -> k -> b -> MinPQueue k b -> MinPQueue k b
forall k a. k -> a -> MinPQueue k a -> MinPQueue k a
insertMin k
k (b -> MinPQueue k b -> MinPQueue k b)
-> f b -> f (MinPQueue k b -> MinPQueue k b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> a -> f b
f k
k a
a f (MinPQueue k b -> MinPQueue k b)
-> f (MinPQueue k b) -> f (MinPQueue k b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
forall k (f :: * -> *) a b.
(Ord k, Applicative f) =>
(k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverseWithKey k -> a -> f b
f MinPQueue k a
q'

-- | /O(n)/. Map values and collect the 'Just' results.
mapMaybe :: Ord k => (a -> Maybe b) -> MinPQueue k a -> MinPQueue k b
mapMaybe :: (a -> Maybe b) -> MinPQueue k a -> MinPQueue k b
mapMaybe = (k -> a -> Maybe b) -> MinPQueue k a -> MinPQueue k b
forall k a b.
Ord k =>
(k -> a -> Maybe b) -> MinPQueue k a -> MinPQueue k b
mapMaybeWithKey ((k -> a -> Maybe b) -> MinPQueue k a -> MinPQueue k b)
-> ((a -> Maybe b) -> k -> a -> Maybe b)
-> (a -> Maybe b)
-> MinPQueue k a
-> MinPQueue k b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Maybe b) -> k -> a -> Maybe b
forall a b. a -> b -> a
const

-- | /O(n)/. Map values and separate the 'Left' and 'Right' results.
mapEither :: Ord k => (a -> Either b c) -> MinPQueue k a -> (MinPQueue k b, MinPQueue k c)
mapEither :: (a -> Either b c)
-> MinPQueue k a -> (MinPQueue k b, MinPQueue k c)
mapEither = (k -> a -> Either b c)
-> MinPQueue k a -> (MinPQueue k b, MinPQueue k c)
forall k a b c.
Ord k =>
(k -> a -> Either b c)
-> MinPQueue k a -> (MinPQueue k b, MinPQueue k c)
mapEitherWithKey ((k -> a -> Either b c)
 -> MinPQueue k a -> (MinPQueue k b, MinPQueue k c))
-> ((a -> Either b c) -> k -> a -> Either b c)
-> (a -> Either b c)
-> MinPQueue k a
-> (MinPQueue k b, MinPQueue k c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Either b c) -> k -> a -> Either b c
forall a b. a -> b -> a
const

-- | /O(n)/. Filter all values that satisfy the predicate.
filter :: Ord k => (a -> Bool) -> MinPQueue k a -> MinPQueue k a
filter :: (a -> Bool) -> MinPQueue k a -> MinPQueue k a
filter = (k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
(k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
filterWithKey ((k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a)
-> ((a -> Bool) -> k -> a -> Bool)
-> (a -> Bool)
-> MinPQueue k a
-> MinPQueue k a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> k -> a -> Bool
forall a b. a -> b -> a
const

-- | /O(n)/. Filter all values that satisfy the predicate.
filterWithKey :: Ord k => (k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
filterWithKey :: (k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
filterWithKey k -> a -> Bool
p = (k -> a -> Maybe a) -> MinPQueue k a -> MinPQueue k a
forall k a b.
Ord k =>
(k -> a -> Maybe b) -> MinPQueue k a -> MinPQueue k b
mapMaybeWithKey (\k
k a
a -> if k -> a -> Bool
p k
k a
a then a -> Maybe a
forall a. a -> Maybe a
Just a
a else Maybe a
forall a. Maybe a
Nothing)

-- | /O(n)/. Partition the queue according to a predicate. The first queue contains all elements
-- which satisfy the predicate, the second all elements that fail the predicate.
partition :: Ord k => (a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a)
partition :: (a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a)
partition = (k -> a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a)
forall k a.
Ord k =>
(k -> a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a)
partitionWithKey ((k -> a -> Bool)
 -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a))
-> ((a -> Bool) -> k -> a -> Bool)
-> (a -> Bool)
-> MinPQueue k a
-> (MinPQueue k a, MinPQueue k a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> k -> a -> Bool
forall a b. a -> b -> a
const

-- | /O(n)/. Partition the queue according to a predicate. The first queue contains all elements
-- which satisfy the predicate, the second all elements that fail the predicate.
partitionWithKey :: Ord k => (k -> a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a)
partitionWithKey :: (k -> a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a)
partitionWithKey k -> a -> Bool
p = (k -> a -> Either a a)
-> MinPQueue k a -> (MinPQueue k a, MinPQueue k a)
forall k a b c.
Ord k =>
(k -> a -> Either b c)
-> MinPQueue k a -> (MinPQueue k b, MinPQueue k c)
mapEitherWithKey (\k
k a
a -> if k -> a -> Bool
p k
k a
a then a -> Either a a
forall a b. a -> Either a b
Left a
a else a -> Either a a
forall a b. b -> Either a b
Right a
a)

{-# INLINE take #-}
-- | /O(k log n)/. Takes the first @k@ (key, value) pairs in the queue, or the first @n@ if @k >= n@.
-- (@'take' k q == 'List.take' k ('toAscList' q)@)
take :: Ord k => Int -> MinPQueue k a -> [(k, a)]
take :: Int -> MinPQueue k a -> [(k, a)]
take Int
n = Int -> [(k, a)] -> [(k, a)]
forall a. Int -> [a] -> [a]
List.take Int
n ([(k, a)] -> [(k, a)])
-> (MinPQueue k a -> [(k, a)]) -> MinPQueue k a -> [(k, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> [(k, a)]
forall k a. Ord k => MinPQueue k a -> [(k, a)]
toAscList

-- | /O(k log n)/. Deletes the first @k@ (key, value) pairs in the queue, or returns an empty queue if @k >= n@.
drop :: Ord k => Int -> MinPQueue k a -> MinPQueue k a
drop :: Int -> MinPQueue k a -> MinPQueue k a
drop Int
n0 MinPQueue k a
q0
  | Int
n0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0  = MinPQueue k a
q0
  | Int
n0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= MinPQueue k a -> Int
forall k a. MinPQueue k a -> Int
size MinPQueue k a
q0  = MinPQueue k a
forall k a. MinPQueue k a
empty
  | Bool
otherwise  = Int -> MinPQueue k a -> MinPQueue k a
forall t k a.
(Num t, Ord k, Eq t) =>
t -> MinPQueue k a -> MinPQueue k a
drop' Int
n0 MinPQueue k a
q0
  where
    drop' :: t -> MinPQueue k a -> MinPQueue k a
drop' t
n MinPQueue k a
q
      | t
n t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
0    = MinPQueue k a
q
      | Bool
otherwise = t -> MinPQueue k a -> MinPQueue k a
drop' (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (MinPQueue k a -> MinPQueue k a
forall k a. Ord k => MinPQueue k a -> MinPQueue k a
deleteMin MinPQueue k a
q)

-- | /O(k log n)/. Equivalent to @('take' k q, 'drop' k q)@.
splitAt :: Ord k => Int -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
splitAt :: Int -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
splitAt Int
n MinPQueue k a
q
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0     = ([], MinPQueue k a
q)
  | Bool
otherwise  = Int
n Int -> ([(k, a)], MinPQueue k a) -> ([(k, a)], MinPQueue k a)
`seq` case MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
forall k a. Ord k => MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
minViewWithKey MinPQueue k a
q of
      Just ((k, a)
ka, MinPQueue k a
q') -> let ([(k, a)]
kas, MinPQueue k a
q'') = Int -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
forall k a.
Ord k =>
Int -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
splitAt (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) MinPQueue k a
q' in ((k, a)
ka (k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
: [(k, a)]
kas, MinPQueue k a
q'')
      Maybe ((k, a), MinPQueue k a)
_             -> ([], MinPQueue k a
q)

{-# INLINE takeWhile #-}
-- | Takes the longest possible prefix of elements satisfying the predicate.
-- (@'takeWhile' p q == 'List.takeWhile' (p . 'snd') ('toAscList' q)@)
takeWhile :: Ord k => (a -> Bool) -> MinPQueue k a -> [(k, a)]
takeWhile :: (a -> Bool) -> MinPQueue k a -> [(k, a)]
takeWhile = (k -> a -> Bool) -> MinPQueue k a -> [(k, a)]
forall k a. Ord k => (k -> a -> Bool) -> MinPQueue k a -> [(k, a)]
takeWhileWithKey ((k -> a -> Bool) -> MinPQueue k a -> [(k, a)])
-> ((a -> Bool) -> k -> a -> Bool)
-> (a -> Bool)
-> MinPQueue k a
-> [(k, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> k -> a -> Bool
forall a b. a -> b -> a
const

{-# INLINE takeWhileWithKey #-}
-- | Takes the longest possible prefix of elements satisfying the predicate.
-- (@'takeWhile' p q == 'List.takeWhile' (uncurry p) ('toAscList' q)@)
takeWhileWithKey :: Ord k => (k -> a -> Bool) -> MinPQueue k a -> [(k, a)]
takeWhileWithKey :: (k -> a -> Bool) -> MinPQueue k a -> [(k, a)]
takeWhileWithKey k -> a -> Bool
p0 = ((k, a) -> Bool) -> [(k, a)] -> [(k, a)]
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> [a]
takeWhileFB ((k -> a -> Bool) -> (k, a) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' k -> a -> Bool
p0) ([(k, a)] -> [(k, a)])
-> (MinPQueue k a -> [(k, a)]) -> MinPQueue k a -> [(k, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> [(k, a)]
forall k a. Ord k => MinPQueue k a -> [(k, a)]
toAscList where
  takeWhileFB :: (a -> Bool) -> t a -> [a]
takeWhileFB a -> Bool
p t a
xs = (forall b. (a -> b -> b) -> b -> b) -> [a]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build (\a -> b -> b
c b
n -> (a -> b -> b) -> b -> t a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x b
z -> if a -> Bool
p a
x then a
x a -> b -> b
`c` b
z else b
n) b
n t a
xs)

-- | Removes the longest possible prefix of elements satisfying the predicate.
dropWhile :: Ord k => (a -> Bool) -> MinPQueue k a -> MinPQueue k a
dropWhile :: (a -> Bool) -> MinPQueue k a -> MinPQueue k a
dropWhile = (k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
(k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
dropWhileWithKey ((k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a)
-> ((a -> Bool) -> k -> a -> Bool)
-> (a -> Bool)
-> MinPQueue k a
-> MinPQueue k a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> k -> a -> Bool
forall a b. a -> b -> a
const

-- | Removes the longest possible prefix of elements satisfying the predicate.
dropWhileWithKey :: Ord k => (k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
dropWhileWithKey :: (k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
dropWhileWithKey k -> a -> Bool
p MinPQueue k a
q = case MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
forall k a. Ord k => MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
minViewWithKey MinPQueue k a
q of
  Just ((k
k, a
a), MinPQueue k a
q')
    | k -> a -> Bool
p k
k a
a -> (k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
forall k a.
Ord k =>
(k -> a -> Bool) -> MinPQueue k a -> MinPQueue k a
dropWhileWithKey k -> a -> Bool
p MinPQueue k a
q'
  Maybe ((k, a), MinPQueue k a)
_         -> MinPQueue k a
q

-- | Equivalent to @('takeWhile' p q, 'dropWhile' p q)@.
span :: Ord k => (a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
span :: (a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
span = (k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
forall k a.
Ord k =>
(k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
spanWithKey ((k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a))
-> ((a -> Bool) -> k -> a -> Bool)
-> (a -> Bool)
-> MinPQueue k a
-> ([(k, a)], MinPQueue k a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> k -> a -> Bool
forall a b. a -> b -> a
const

-- | Equivalent to @'span' ('not' . p)@.
break :: Ord k => (a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
break :: (a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
break a -> Bool
p = (a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
forall k a.
Ord k =>
(a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
span (Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p)

-- | Equivalent to @('takeWhileWithKey' p q, 'dropWhileWithKey' p q)@.
spanWithKey :: Ord k => (k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
spanWithKey :: (k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
spanWithKey k -> a -> Bool
p MinPQueue k a
q = case MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
forall k a. Ord k => MinPQueue k a -> Maybe ((k, a), MinPQueue k a)
minViewWithKey MinPQueue k a
q of
  Just (t :: (k, a)
t@(k
k, a
a), MinPQueue k a
q')
    | k -> a -> Bool
p k
k a
a -> let ([(k, a)]
kas, MinPQueue k a
q'') = (k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
forall k a.
Ord k =>
(k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
spanWithKey k -> a -> Bool
p MinPQueue k a
q' in ((k, a)
t (k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
: [(k, a)]
kas, MinPQueue k a
q'')
  Maybe ((k, a), MinPQueue k a)
_         -> ([], MinPQueue k a
q)

-- | Equivalent to @'spanWithKey' (\ k a -> 'not' (p k a)) q@.
breakWithKey :: Ord k => (k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
breakWithKey :: (k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
breakWithKey k -> a -> Bool
p = (k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
forall k a.
Ord k =>
(k -> a -> Bool) -> MinPQueue k a -> ([(k, a)], MinPQueue k a)
spanWithKey (Bool -> Bool
not (Bool -> Bool) -> (k -> a -> Bool) -> k -> a -> Bool
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: k -> a -> Bool
p)

-- | /O(n)/. Build a priority queue from the list of (key, value) pairs.
fromList :: Ord k => [(k, a)] -> MinPQueue k a
fromList :: [(k, a)] -> MinPQueue k a
fromList = ((k, a) -> MinPQueue k a -> MinPQueue k a)
-> MinPQueue k a -> [(k, a)] -> MinPQueue k a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((k -> a -> MinPQueue k a -> MinPQueue k a)
-> (k, a) -> MinPQueue k a -> MinPQueue k a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' k -> a -> MinPQueue k a -> MinPQueue k a
forall k a. Ord k => k -> a -> MinPQueue k a -> MinPQueue k a
insert) MinPQueue k a
forall k a. MinPQueue k a
empty

-- | /O(n)/. Build a priority queue from an ascending list of (key, value) pairs. /The precondition is not checked./
fromAscList :: [(k, a)] -> MinPQueue k a
fromAscList :: [(k, a)] -> MinPQueue k a
fromAscList = ((k, a) -> MinPQueue k a -> MinPQueue k a)
-> MinPQueue k a -> [(k, a)] -> MinPQueue k a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((k -> a -> MinPQueue k a -> MinPQueue k a)
-> (k, a) -> MinPQueue k a -> MinPQueue k a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry' k -> a -> MinPQueue k a -> MinPQueue k a
forall k a. k -> a -> MinPQueue k a -> MinPQueue k a
insertMin) MinPQueue k a
forall k a. MinPQueue k a
empty

-- | /O(n)/. Build a priority queue from a descending list of (key, value) pairs. /The precondition is not checked./
fromDescList :: [(k, a)] -> MinPQueue k a
fromDescList :: [(k, a)] -> MinPQueue k a
fromDescList = (MinPQueue k a -> (k, a) -> MinPQueue k a)
-> MinPQueue k a -> [(k, a)] -> MinPQueue k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\MinPQueue k a
q (k
k, a
a) -> k -> a -> MinPQueue k a -> MinPQueue k a
forall k a. k -> a -> MinPQueue k a -> MinPQueue k a
insertMin k
k a
a MinPQueue k a
q) MinPQueue k a
forall k a. MinPQueue k a
empty

{-# RULES
  "fromList/build" forall (g :: forall b . ((k, a) -> b -> b) -> b -> b) .
    fromList (build g) = g (uncurry' insert) empty;
  "fromAscList/build" forall (g :: forall b . ((k, a) -> b -> b) -> b -> b) .
    fromAscList (build g) = g (uncurry' insertMin) empty;
  #-}

{-# INLINE keys #-}
-- | /O(n log n)/. Return all keys of the queue in ascending order.
keys :: Ord k => MinPQueue k a -> [k]
keys :: MinPQueue k a -> [k]
keys = ((k, a) -> k) -> [(k, a)] -> [k]
forall a b. (a -> b) -> [a] -> [b]
List.map (k, a) -> k
forall a b. (a, b) -> a
fst ([(k, a)] -> [k])
-> (MinPQueue k a -> [(k, a)]) -> MinPQueue k a -> [k]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> [(k, a)]
forall k a. Ord k => MinPQueue k a -> [(k, a)]
toAscList

{-# INLINE elems #-}
-- | /O(n log n)/. Return all elements of the queue in ascending order by key.
elems :: Ord k => MinPQueue k a -> [a]
elems :: MinPQueue k a -> [a]
elems = ((k, a) -> a) -> [(k, a)] -> [a]
forall a b. (a -> b) -> [a] -> [b]
List.map (k, a) -> a
forall a b. (a, b) -> b
snd ([(k, a)] -> [a])
-> (MinPQueue k a -> [(k, a)]) -> MinPQueue k a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> [(k, a)]
forall k a. Ord k => MinPQueue k a -> [(k, a)]
toAscList

-- | /O(n log n)/. Return all (key, value) pairs in ascending order by key.
toAscList :: Ord k => MinPQueue k a -> [(k, a)]
toAscList :: MinPQueue k a -> [(k, a)]
toAscList = (k -> a -> [(k, a)] -> [(k, a)])
-> [(k, a)] -> MinPQueue k a -> [(k, a)]
forall k a b.
Ord k =>
(k -> a -> b -> b) -> b -> MinPQueue k a -> b
foldrWithKey (((k, a) -> [(k, a)] -> [(k, a)]) -> k -> a -> [(k, a)] -> [(k, a)]
forall a b c. ((a, b) -> c) -> a -> b -> c
curry (:)) []

-- | /O(n log n)/. Return all (key, value) pairs in descending order by key.
toDescList :: Ord k => MinPQueue k a -> [(k, a)]
toDescList :: MinPQueue k a -> [(k, a)]
toDescList = ([(k, a)] -> k -> a -> [(k, a)])
-> [(k, a)] -> MinPQueue k a -> [(k, a)]
forall k b a.
Ord k =>
(b -> k -> a -> b) -> b -> MinPQueue k a -> b
foldlWithKey (\[(k, a)]
z k
k a
a -> (k
k, a
a) (k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
: [(k, a)]
z) []

{-# RULES
  "toAscList" toAscList = \q -> build (\c n -> foldrWithKey (curry c) n q);
  "toDescList" toDescList = \q -> build (\c n -> foldlWithKey (\z k a -> (k, a) `c` z) n q);
  "toListU" toListU = \q -> build (\c n -> foldrWithKeyU (curry c) n q);
  #-}

{-# INLINE toList #-}
-- | /O(n log n)/. Equivalent to 'toAscList'.
--
-- If the traversal order is irrelevant, consider using 'toListU'.
toList :: Ord k => MinPQueue k a -> [(k, a)]
toList :: MinPQueue k a -> [(k, a)]
toList = MinPQueue k a -> [(k, a)]
forall k a. Ord k => MinPQueue k a -> [(k, a)]
toAscList

{-# INLINE assocs #-}
-- | /O(n log n)/. Equivalent to 'toAscList'.
assocs :: Ord k => MinPQueue k a -> [(k, a)]
assocs :: MinPQueue k a -> [(k, a)]
assocs = MinPQueue k a -> [(k, a)]
forall k a. Ord k => MinPQueue k a -> [(k, a)]
toAscList

{-# INLINE keysU #-}
-- | /O(n)/. Return all keys of the queue in no particular order.
keysU :: MinPQueue k a -> [k]
keysU :: MinPQueue k a -> [k]
keysU = ((k, a) -> k) -> [(k, a)] -> [k]
forall a b. (a -> b) -> [a] -> [b]
List.map (k, a) -> k
forall a b. (a, b) -> a
fst ([(k, a)] -> [k])
-> (MinPQueue k a -> [(k, a)]) -> MinPQueue k a -> [k]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> [(k, a)]
forall k a. MinPQueue k a -> [(k, a)]
toListU

{-# INLINE elemsU #-}
-- | /O(n)/. Return all elements of the queue in no particular order.
elemsU :: MinPQueue k a -> [a]
elemsU :: MinPQueue k a -> [a]
elemsU = ((k, a) -> a) -> [(k, a)] -> [a]
forall a b. (a -> b) -> [a] -> [b]
List.map (k, a) -> a
forall a b. (a, b) -> b
snd ([(k, a)] -> [a])
-> (MinPQueue k a -> [(k, a)]) -> MinPQueue k a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MinPQueue k a -> [(k, a)]
forall k a. MinPQueue k a -> [(k, a)]
toListU

{-# INLINE assocsU #-}
-- | /O(n)/. Equivalent to 'toListU'.
assocsU :: MinPQueue k a -> [(k, a)]
assocsU :: MinPQueue k a -> [(k, a)]
assocsU = MinPQueue k a -> [(k, a)]
forall k a. MinPQueue k a -> [(k, a)]
toListU

-- | /O(n)/. Returns all (key, value) pairs in the queue in no particular order.
toListU :: MinPQueue k a -> [(k, a)]
toListU :: MinPQueue k a -> [(k, a)]
toListU = (k -> a -> [(k, a)] -> [(k, a)])
-> [(k, a)] -> MinPQueue k a -> [(k, a)]
forall k a b. (k -> a -> b -> b) -> b -> MinPQueue k a -> b
foldrWithKeyU (((k, a) -> [(k, a)] -> [(k, a)]) -> k -> a -> [(k, a)] -> [(k, a)]
forall a b c. ((a, b) -> c) -> a -> b -> c
curry (:)) []

-- | /O(n)/. An unordered right fold over the elements of the queue, in no particular order.
foldrU :: (a -> b -> b) -> b -> MinPQueue k a -> b
foldrU :: (a -> b -> b) -> b -> MinPQueue k a -> b
foldrU = (k -> a -> b -> b) -> b -> MinPQueue k a -> b
forall k a b. (k -> a -> b -> b) -> b -> MinPQueue k a -> b
foldrWithKeyU ((k -> a -> b -> b) -> b -> MinPQueue k a -> b)
-> ((a -> b -> b) -> k -> a -> b -> b)
-> (a -> b -> b)
-> b
-> MinPQueue k a
-> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b -> b) -> k -> a -> b -> b
forall a b. a -> b -> a
const

-- | /O(n)/. An unordered left fold over the elements of the queue, in no particular order.
foldlU :: (b -> a -> b) -> b -> MinPQueue k a -> b
foldlU :: (b -> a -> b) -> b -> MinPQueue k a -> b
foldlU b -> a -> b
f = (b -> k -> a -> b) -> b -> MinPQueue k a -> b
forall b k a. (b -> k -> a -> b) -> b -> MinPQueue k a -> b
foldlWithKeyU ((a -> b) -> k -> a -> b
forall a b. a -> b -> a
const ((a -> b) -> k -> a -> b) -> (b -> a -> b) -> b -> k -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a -> b
f)

-- | /O(n)/. An unordered traversal over a priority queue, in no particular order.
-- While there is no guarantee in which order the elements are traversed, the resulting
-- priority queue will be perfectly valid.
traverseU :: (Applicative f) => (a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverseU :: (a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverseU = (k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
forall (f :: * -> *) k a b.
Applicative f =>
(k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverseWithKeyU ((k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b))
-> ((a -> f b) -> k -> a -> f b)
-> (a -> f b)
-> MinPQueue k a
-> f (MinPQueue k b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f b) -> k -> a -> f b
forall a b. a -> b -> a
const

instance Functor (MinPQueue k) where
  fmap :: (a -> b) -> MinPQueue k a -> MinPQueue k b
fmap = (a -> b) -> MinPQueue k a -> MinPQueue k b
forall a b k. (a -> b) -> MinPQueue k a -> MinPQueue k b
map

instance Ord k => Foldable (MinPQueue k) where
  foldr :: (a -> b -> b) -> b -> MinPQueue k a -> b
foldr   = (k -> a -> b -> b) -> b -> MinPQueue k a -> b
forall k a b.
Ord k =>
(k -> a -> b -> b) -> b -> MinPQueue k a -> b
foldrWithKey ((k -> a -> b -> b) -> b -> MinPQueue k a -> b)
-> ((a -> b -> b) -> k -> a -> b -> b)
-> (a -> b -> b)
-> b
-> MinPQueue k a
-> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b -> b) -> k -> a -> b -> b
forall a b. a -> b -> a
const
  foldl :: (b -> a -> b) -> b -> MinPQueue k a -> b
foldl b -> a -> b
f = (b -> k -> a -> b) -> b -> MinPQueue k a -> b
forall k b a.
Ord k =>
(b -> k -> a -> b) -> b -> MinPQueue k a -> b
foldlWithKey ((a -> b) -> k -> a -> b
forall a b. a -> b -> a
const ((a -> b) -> k -> a -> b) -> (b -> a -> b) -> b -> k -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a -> b
f)

instance Ord k => Traversable (MinPQueue k) where
  traverse :: (a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverse = (k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
forall k (f :: * -> *) a b.
(Ord k, Applicative f) =>
(k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b)
traverseWithKey ((k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b))
-> ((a -> f b) -> k -> a -> f b)
-> (a -> f b)
-> MinPQueue k a
-> f (MinPQueue k b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f b) -> k -> a -> f b
forall a b. a -> b -> a
const