{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
#endif
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE DeriveGeneric #-}
#endif
#if __GLASGOW_HASKELL__ >= 710 && __GLASGOW_HASKELL__ < 802
{-# LANGUAGE AutoDeriveTypeable #-}
#endif
module Data.PriorityQueue.FingerTree (
PQueue,
empty,
singleton,
union,
insert,
add,
fromList,
null,
minView,
minViewWithKey
) where
import qualified Data.FingerTree as FT
import Data.FingerTree (FingerTree, (<|), (|>), (><), ViewL(..), Measured(..))
import Prelude hiding (null)
#if MIN_VERSION_base(4,6,0)
import GHC.Generics
#endif
#if MIN_VERSION_base(4,8,0)
import qualified Prelude (null)
#else
import Data.Foldable (Foldable(foldMap))
import Data.Monoid
#endif
#if (MIN_VERSION_base(4,9,0)) && !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Control.Arrow ((***))
import Data.List (unfoldr)
data Entry k v = Entry k v
#if __GLASGOW_HASKELL__ >= 706
deriving ((forall x. Entry k v -> Rep (Entry k v) x)
-> (forall x. Rep (Entry k v) x -> Entry k v)
-> Generic (Entry k v)
forall x. Rep (Entry k v) x -> Entry k v
forall x. Entry k v -> Rep (Entry k v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k v x. Rep (Entry k v) x -> Entry k v
forall k v x. Entry k v -> Rep (Entry k v) x
$cto :: forall k v x. Rep (Entry k v) x -> Entry k v
$cfrom :: forall k v x. Entry k v -> Rep (Entry k v) x
Generic)
#endif
instance Functor (Entry k) where
fmap :: (a -> b) -> Entry k a -> Entry k b
fmap a -> b
f (Entry k
k a
v) = k -> b -> Entry k b
forall k v. k -> v -> Entry k v
Entry k
k (a -> b
f a
v)
instance Foldable (Entry k) where
foldMap :: (a -> m) -> Entry k a -> m
foldMap a -> m
f (Entry k
_ a
v) = a -> m
f a
v
data Prio k v = NoPrio | Prio k v
#if __GLASGOW_HASKELL__ >= 706
deriving ((forall x. Prio k v -> Rep (Prio k v) x)
-> (forall x. Rep (Prio k v) x -> Prio k v) -> Generic (Prio k v)
forall x. Rep (Prio k v) x -> Prio k v
forall x. Prio k v -> Rep (Prio k v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k v x. Rep (Prio k v) x -> Prio k v
forall k v x. Prio k v -> Rep (Prio k v) x
$cto :: forall k v x. Rep (Prio k v) x -> Prio k v
$cfrom :: forall k v x. Prio k v -> Rep (Prio k v) x
Generic)
#endif
#if MIN_VERSION_base(4,9,0)
instance Ord k => Semigroup (Prio k v) where
<> :: Prio k v -> Prio k v -> Prio k v
(<>) = Prio k v -> Prio k v -> Prio k v
forall k v. Ord k => Prio k v -> Prio k v -> Prio k v
unionPrio
#endif
instance Ord k => Monoid (Prio k v) where
mempty :: Prio k v
mempty = Prio k v
forall k v. Prio k v
NoPrio
#if !(MIN_VERSION_base(4,11,0))
mappend = unionPrio
#endif
unionPrio :: Ord k => Prio k v -> Prio k v -> Prio k v
Prio k v
x unionPrio :: Prio k v -> Prio k v -> Prio k v
`unionPrio` Prio k v
NoPrio = Prio k v
x
Prio k v
NoPrio `unionPrio` Prio k v
y = Prio k v
y
x :: Prio k v
x@(Prio k
kx v
_) `unionPrio` y :: Prio k v
y@(Prio k
ky v
_)
| k
kx k -> k -> Bool
forall a. Ord a => a -> a -> Bool
<= k
ky = Prio k v
x
| Bool
otherwise = Prio k v
y
instance Ord k => Measured (Prio k v) (Entry k v) where
measure :: Entry k v -> Prio k v
measure (Entry k
k v
v) = k -> v -> Prio k v
forall k v. k -> v -> Prio k v
Prio k
k v
v
newtype PQueue k v = PQueue (FingerTree (Prio k v) (Entry k v))
#if __GLASGOW_HASKELL__ >= 706
deriving ((forall x. PQueue k v -> Rep (PQueue k v) x)
-> (forall x. Rep (PQueue k v) x -> PQueue k v)
-> Generic (PQueue k v)
forall x. Rep (PQueue k v) x -> PQueue k v
forall x. PQueue k v -> Rep (PQueue k v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k v x. Rep (PQueue k v) x -> PQueue k v
forall k v x. PQueue k v -> Rep (PQueue k v) x
$cto :: forall k v x. Rep (PQueue k v) x -> PQueue k v
$cfrom :: forall k v x. PQueue k v -> Rep (PQueue k v) x
Generic)
#endif
instance Ord k => Functor (PQueue k) where
fmap :: (a -> b) -> PQueue k a -> PQueue k b
fmap a -> b
f (PQueue FingerTree (Prio k a) (Entry k a)
xs) = FingerTree (Prio k b) (Entry k b) -> PQueue k b
forall k v. FingerTree (Prio k v) (Entry k v) -> PQueue k v
PQueue ((Entry k a -> Entry k b)
-> FingerTree (Prio k a) (Entry k a)
-> FingerTree (Prio k b) (Entry k b)
forall v1 a1 v2 a2.
(Measured v1 a1, Measured v2 a2) =>
(a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2
FT.fmap' ((a -> b) -> Entry k a -> Entry k b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) FingerTree (Prio k a) (Entry k a)
xs)
instance Ord k => Foldable (PQueue k) where
foldMap :: (a -> m) -> PQueue k a -> m
foldMap a -> m
f PQueue k a
q = case PQueue k a -> Maybe (a, PQueue k a)
forall k v. Ord k => PQueue k v -> Maybe (v, PQueue k v)
minView PQueue k a
q of
Maybe (a, PQueue k a)
Nothing -> m
forall a. Monoid a => a
mempty
Just (a
v, PQueue k a
q') -> a -> m
f a
v m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (a -> m) -> PQueue k a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f PQueue k a
q'
#if MIN_VERSION_base(4,8,0)
null :: PQueue k a -> Bool
null (PQueue FingerTree (Prio k a) (Entry k a)
q) = FingerTree (Prio k a) (Entry k a) -> Bool
forall v a. FingerTree v a -> Bool
FT.null FingerTree (Prio k a) (Entry k a)
q
#endif
#if MIN_VERSION_base(4,9,0)
instance Ord k => Semigroup (PQueue k v) where
<> :: PQueue k v -> PQueue k v -> PQueue k v
(<>) = PQueue k v -> PQueue k v -> PQueue k v
forall k v. Ord k => PQueue k v -> PQueue k v -> PQueue k v
union
#endif
instance Ord k => Monoid (PQueue k v) where
mempty :: PQueue k v
mempty = PQueue k v
forall k v. Ord k => PQueue k v
empty
#if !(MIN_VERSION_base(4,11,0))
mappend = union
#endif
instance (Ord k, Eq v) => Eq (PQueue k v) where
PQueue k v
xs == :: PQueue k v -> PQueue k v -> Bool
== PQueue k v
ys = PQueue k v -> [(k, v)]
forall k v. Ord k => PQueue k v -> [(k, v)]
assocs PQueue k v
xs [(k, v)] -> [(k, v)] -> Bool
forall a. Eq a => a -> a -> Bool
== PQueue k v -> [(k, v)]
forall k v. Ord k => PQueue k v -> [(k, v)]
assocs PQueue k v
ys
instance (Ord k, Ord v) => Ord (PQueue k v) where
compare :: PQueue k v -> PQueue k v -> Ordering
compare PQueue k v
xs PQueue k v
ys = [(k, v)] -> [(k, v)] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (PQueue k v -> [(k, v)]
forall k v. Ord k => PQueue k v -> [(k, v)]
assocs PQueue k v
xs) (PQueue k v -> [(k, v)]
forall k v. Ord k => PQueue k v -> [(k, v)]
assocs PQueue k v
ys)
instance (Ord k, Show k, Show v) => Show (PQueue k v) where
showsPrec :: Int -> PQueue k v -> ShowS
showsPrec Int
p PQueue k v
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
"fromList " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(k, v)] -> ShowS
forall a. Show a => a -> ShowS
shows (PQueue k v -> [(k, v)]
forall k v. Ord k => PQueue k v -> [(k, v)]
assocs PQueue k v
xs)
empty :: Ord k => PQueue k v
empty :: PQueue k v
empty = FingerTree (Prio k v) (Entry k v) -> PQueue k v
forall k v. FingerTree (Prio k v) (Entry k v) -> PQueue k v
PQueue FingerTree (Prio k v) (Entry k v)
forall v a. Measured v a => FingerTree v a
FT.empty
singleton :: Ord k => k -> v -> PQueue k v
singleton :: k -> v -> PQueue k v
singleton k
k v
v = FingerTree (Prio k v) (Entry k v) -> PQueue k v
forall k v. FingerTree (Prio k v) (Entry k v) -> PQueue k v
PQueue (Entry k v -> FingerTree (Prio k v) (Entry k v)
forall v a. Measured v a => a -> FingerTree v a
FT.singleton (k -> v -> Entry k v
forall k v. k -> v -> Entry k v
Entry k
k v
v))
insert :: Ord k => k -> v -> PQueue k v -> PQueue k v
insert :: k -> v -> PQueue k v -> PQueue k v
insert k
k v
v (PQueue FingerTree (Prio k v) (Entry k v)
q) = FingerTree (Prio k v) (Entry k v) -> PQueue k v
forall k v. FingerTree (Prio k v) (Entry k v) -> PQueue k v
PQueue (k -> v -> Entry k v
forall k v. k -> v -> Entry k v
Entry k
k v
v Entry k v
-> FingerTree (Prio k v) (Entry k v)
-> FingerTree (Prio k v) (Entry k v)
forall v a. Measured v a => a -> FingerTree v a -> FingerTree v a
<| FingerTree (Prio k v) (Entry k v)
q)
add :: Ord k => k -> v -> PQueue k v -> PQueue k v
add :: k -> v -> PQueue k v -> PQueue k v
add k
k v
v (PQueue FingerTree (Prio k v) (Entry k v)
q) = FingerTree (Prio k v) (Entry k v) -> PQueue k v
forall k v. FingerTree (Prio k v) (Entry k v) -> PQueue k v
PQueue (FingerTree (Prio k v) (Entry k v)
q FingerTree (Prio k v) (Entry k v)
-> Entry k v -> FingerTree (Prio k v) (Entry k v)
forall v a. Measured v a => FingerTree v a -> a -> FingerTree v a
|> k -> v -> Entry k v
forall k v. k -> v -> Entry k v
Entry k
k v
v)
union :: Ord k => PQueue k v -> PQueue k v -> PQueue k v
union :: PQueue k v -> PQueue k v -> PQueue k v
union (PQueue FingerTree (Prio k v) (Entry k v)
xs) (PQueue FingerTree (Prio k v) (Entry k v)
ys) = FingerTree (Prio k v) (Entry k v) -> PQueue k v
forall k v. FingerTree (Prio k v) (Entry k v) -> PQueue k v
PQueue (FingerTree (Prio k v) (Entry k v)
xs FingerTree (Prio k v) (Entry k v)
-> FingerTree (Prio k v) (Entry k v)
-> FingerTree (Prio k v) (Entry k v)
forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
>< FingerTree (Prio k v) (Entry k v)
ys)
fromList :: Ord k => [(k, v)] -> PQueue k v
fromList :: [(k, v)] -> PQueue k v
fromList = ((k, v) -> PQueue k v -> PQueue k v)
-> PQueue k v -> [(k, v)] -> PQueue k v
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((k -> v -> PQueue k v -> PQueue k v)
-> (k, v) -> PQueue k v -> PQueue k v
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry k -> v -> PQueue k v -> PQueue k v
forall k v. Ord k => k -> v -> PQueue k v -> PQueue k v
insert) PQueue k v
forall k v. Ord k => PQueue k v
empty
null :: Ord k => PQueue k v -> Bool
null :: PQueue k v -> Bool
null (PQueue FingerTree (Prio k v) (Entry k v)
q) = FingerTree (Prio k v) (Entry k v) -> Bool
forall v a. FingerTree v a -> Bool
FT.null FingerTree (Prio k v) (Entry k v)
q
minView :: Ord k => PQueue k v -> Maybe (v, PQueue k v)
minView :: PQueue k v -> Maybe (v, PQueue k v)
minView PQueue k v
q = (((k, v), PQueue k v) -> (v, PQueue k v))
-> Maybe ((k, v), PQueue k v) -> Maybe (v, PQueue k v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((k, v) -> v
forall a b. (a, b) -> b
snd ((k, v) -> v)
-> (PQueue k v -> PQueue k v)
-> ((k, v), PQueue k v)
-> (v, PQueue k v)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** PQueue k v -> PQueue k v
forall a. a -> a
id) (PQueue k v -> Maybe ((k, v), PQueue k v)
forall k v. Ord k => PQueue k v -> Maybe ((k, v), PQueue k v)
minViewWithKey PQueue k v
q)
minViewWithKey :: Ord k => PQueue k v -> Maybe ((k, v), PQueue k v)
minViewWithKey :: PQueue k v -> Maybe ((k, v), PQueue k v)
minViewWithKey (PQueue FingerTree (Prio k v) (Entry k v)
q)
| FingerTree (Prio k v) (Entry k v) -> Bool
forall v a. FingerTree v a -> Bool
FT.null FingerTree (Prio k v) (Entry k v)
q = Maybe ((k, v), PQueue k v)
forall a. Maybe a
Nothing
| Bool
otherwise = ((k, v), PQueue k v) -> Maybe ((k, v), PQueue k v)
forall a. a -> Maybe a
Just ((k
k, v
v), case FingerTree (Prio k v) (Entry k v)
-> ViewL (FingerTree (Prio k v)) (Entry k v)
forall v a.
Measured v a =>
FingerTree v a -> ViewL (FingerTree v) a
FT.viewl FingerTree (Prio k v) (Entry k v)
r of
Entry k v
_ :< FingerTree (Prio k v) (Entry k v)
r' -> FingerTree (Prio k v) (Entry k v) -> PQueue k v
forall k v. FingerTree (Prio k v) (Entry k v) -> PQueue k v
PQueue (FingerTree (Prio k v) (Entry k v)
l FingerTree (Prio k v) (Entry k v)
-> FingerTree (Prio k v) (Entry k v)
-> FingerTree (Prio k v) (Entry k v)
forall v a.
Measured v a =>
FingerTree v a -> FingerTree v a -> FingerTree v a
>< FingerTree (Prio k v) (Entry k v)
r')
ViewL (FingerTree (Prio k v)) (Entry k v)
_ -> String -> PQueue k v
forall a. HasCallStack => String -> a
error String
"can't happen")
where
Prio k
k v
v = FingerTree (Prio k v) (Entry k v) -> Prio k v
forall v a. Measured v a => a -> v
measure FingerTree (Prio k v) (Entry k v)
q
(FingerTree (Prio k v) (Entry k v)
l, FingerTree (Prio k v) (Entry k v)
r) = (Prio k v -> Bool)
-> FingerTree (Prio k v) (Entry k v)
-> (FingerTree (Prio k v) (Entry k v),
FingerTree (Prio k v) (Entry k v))
forall v a.
Measured v a =>
(v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a)
FT.split (k -> Prio k v -> Bool
forall k v. Ord k => k -> Prio k v -> Bool
below k
k) FingerTree (Prio k v) (Entry k v)
q
below :: Ord k => k -> Prio k v -> Bool
below :: k -> Prio k v -> Bool
below k
_ Prio k v
NoPrio = Bool
False
below k
k (Prio k
k' v
_) = k
k' k -> k -> Bool
forall a. Ord a => a -> a -> Bool
<= k
k
assocs :: Ord k => PQueue k v -> [(k, v)]
assocs :: PQueue k v -> [(k, v)]
assocs = (PQueue k v -> Maybe ((k, v), PQueue k v))
-> PQueue k v -> [(k, v)]
forall b a. (b -> Maybe (a, b)) -> b -> [a]
unfoldr PQueue k v -> Maybe ((k, v), PQueue k v)
forall k v. Ord k => PQueue k v -> Maybe ((k, v), PQueue k v)
minViewWithKey