{-# LANGUAGE CPP #-}
module Data.PQueue.Prio.Min (
MinPQueue,
empty,
singleton,
insert,
insertBehind,
union,
unions,
null,
size,
findMin,
getMin,
deleteMin,
deleteFindMin,
adjustMin,
adjustMinA,
adjustMinWithKey,
adjustMinWithKeyA,
updateMin,
updateMinA,
updateMinWithKey,
updateMinWithKeyA,
minView,
minViewWithKey,
map,
mapWithKey,
mapKeys,
mapKeysMonotonic,
foldrWithKey,
foldlWithKey,
traverseWithKey,
mapMWithKey,
take,
drop,
splitAt,
takeWhile,
takeWhileWithKey,
dropWhile,
dropWhileWithKey,
span,
spanWithKey,
break,
breakWithKey,
filter,
filterWithKey,
partition,
partitionWithKey,
mapMaybe,
mapMaybeWithKey,
mapEither,
mapEitherWithKey,
fromList,
fromAscList,
fromDescList,
keys,
elems,
assocs,
toAscList,
toDescList,
toList,
foldrU,
foldMapWithKeyU,
foldrWithKeyU,
foldlU,
foldlU',
foldlWithKeyU,
foldlWithKeyU',
traverseU,
traverseWithKeyU,
keysU,
elemsU,
assocsU,
toListU,
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)
#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 .:
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 ([Char] -> (k, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"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
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)
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 ([Char] -> ((k, a), MinPQueue k a)
forall a. HasCallStack => [Char] -> a
error [Char]
"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
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
adjustMinA :: Applicative f => (a -> f a) -> MinPQueue k a -> f (MinPQueue k a)
adjustMinA :: (a -> f a) -> MinPQueue k a -> f (MinPQueue k a)
adjustMinA = (k -> a -> f a) -> MinPQueue k a -> f (MinPQueue k a)
forall (f :: * -> *) k a.
Applicative f =>
(k -> a -> f a) -> MinPQueue k a -> f (MinPQueue k a)
adjustMinWithKeyA ((k -> a -> f a) -> MinPQueue k a -> f (MinPQueue k a))
-> ((a -> f a) -> k -> a -> f a)
-> (a -> f a)
-> MinPQueue k a
-> f (MinPQueue k a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f a) -> k -> a -> f a
forall a b. a -> b -> a
const
adjustMinWithKeyA :: Applicative f => (k -> a -> f a) -> MinPQueue k a -> f (MinPQueue k a)
adjustMinWithKeyA :: (k -> a -> f a) -> MinPQueue k a -> f (MinPQueue k a)
adjustMinWithKeyA = (MinPQueue k a -> MinPQueue k a)
-> (k -> a -> f a) -> MinPQueue k a -> f (MinPQueue k a)
forall (f :: * -> *) k a r.
Applicative f =>
(MinPQueue k a -> r) -> (k -> a -> f a) -> MinPQueue k a -> f r
adjustMinWithKeyA' MinPQueue k a -> MinPQueue k a
forall a. a -> a
id
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
updateMinA :: (Applicative f, Ord k) => (a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a)
updateMinA :: (a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a)
updateMinA = (k -> a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a)
forall (f :: * -> *) k a.
(Applicative f, Ord k) =>
(k -> a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a)
updateMinWithKeyA ((k -> a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a))
-> ((a -> f (Maybe a)) -> k -> a -> f (Maybe a))
-> (a -> f (Maybe a))
-> MinPQueue k a
-> f (MinPQueue k a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f (Maybe a)) -> k -> a -> f (Maybe a)
forall a b. a -> b -> a
const
updateMinWithKeyA :: (Applicative f, Ord k) => (k -> a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a)
updateMinWithKeyA :: (k -> a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a)
updateMinWithKeyA = (MinPQueue k a -> MinPQueue k a)
-> (k -> a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a)
forall (f :: * -> *) k a r.
(Applicative f, Ord k) =>
(MinPQueue k a -> r)
-> (k -> a -> f (Maybe a)) -> MinPQueue k a -> f r
updateMinWithKeyA' MinPQueue k a -> MinPQueue k a
forall a. a -> a
id
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')
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
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]
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
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
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
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)
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
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 #-}
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
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)
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 #-}
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 #-}
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)
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
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
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
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)
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)
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)
fromDescList :: [(k, a)] -> MinPQueue k a
{-# INLINE fromDescList #-}
fromDescList :: [(k, a)] -> MinPQueue k a
fromDescList [(k, a)]
xs = (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 [(k, a)]
xs
{-# INLINE keys #-}
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 #-}
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
{-# INLINE toList #-}
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 #-}
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 #-}
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 #-}
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 #-}
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
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)
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)
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