{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
#endif
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE DeriveGeneric #-}
#endif
#if __GLASGOW_HASKELL__ >= 710
{-# 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 (Generic)
#endif
instance Functor (Entry k) where
fmap f (Entry k v) = Entry k (f v)
instance Foldable (Entry k) where
foldMap f (Entry _ v) = f v
data Prio k v = NoPrio | Prio k v
#if __GLASGOW_HASKELL__ >= 706
deriving (Generic)
#endif
#if MIN_VERSION_base(4,9,0)
instance Ord k => Semigroup (Prio k v) where
(<>) = unionPrio
#endif
instance Ord k => Monoid (Prio k v) where
mempty = NoPrio
#if !(MIN_VERSION_base(4,11,0))
mappend = unionPrio
#endif
unionPrio :: Ord k => Prio k v -> Prio k v -> Prio k v
x `unionPrio` NoPrio = x
NoPrio `unionPrio` y = y
x@(Prio kx _) `unionPrio` y@(Prio ky _)
| kx <= ky = x
| otherwise = y
instance Ord k => Measured (Prio k v) (Entry k v) where
measure (Entry k v) = Prio k v
newtype PQueue k v = PQueue (FingerTree (Prio k v) (Entry k v))
#if __GLASGOW_HASKELL__ >= 706
deriving (Generic)
#endif
instance Ord k => Functor (PQueue k) where
fmap f (PQueue xs) = PQueue (FT.fmap' (fmap f) xs)
instance Ord k => Foldable (PQueue k) where
foldMap f q = case minView q of
Nothing -> mempty
Just (v, q') -> f v `mappend` foldMap f q'
#if MIN_VERSION_base(4,8,0)
null (PQueue q) = FT.null q
#endif
#if MIN_VERSION_base(4,9,0)
instance Ord k => Semigroup (PQueue k v) where
(<>) = union
#endif
instance Ord k => Monoid (PQueue k v) where
mempty = empty
#if !(MIN_VERSION_base(4,11,0))
mappend = union
#endif
instance (Ord k, Eq v) => Eq (PQueue k v) where
xs == ys = assocs xs == assocs ys
instance (Ord k, Ord v) => Ord (PQueue k v) where
compare xs ys = compare (assocs xs) (assocs ys)
instance (Ord k, Show k, Show v) => Show (PQueue k v) where
showsPrec p xs = showParen (p > 10) $
showString "fromList " . shows (assocs xs)
empty :: Ord k => PQueue k v
empty = PQueue FT.empty
singleton :: Ord k => k -> v -> PQueue k v
singleton k v = PQueue (FT.singleton (Entry k v))
insert :: Ord k => k -> v -> PQueue k v -> PQueue k v
insert k v (PQueue q) = PQueue (Entry k v <| q)
add :: Ord k => k -> v -> PQueue k v -> PQueue k v
add k v (PQueue q) = PQueue (q |> Entry k v)
union :: Ord k => PQueue k v -> PQueue k v -> PQueue k v
union (PQueue xs) (PQueue ys) = PQueue (xs >< ys)
fromList :: Ord k => [(k, v)] -> PQueue k v
fromList = foldr (uncurry insert) empty
null :: Ord k => PQueue k v -> Bool
null (PQueue q) = FT.null q
minView :: Ord k => PQueue k v -> Maybe (v, PQueue k v)
minView q = fmap (snd *** id) (minViewWithKey q)
minViewWithKey :: Ord k => PQueue k v -> Maybe ((k, v), PQueue k v)
minViewWithKey (PQueue q)
| FT.null q = Nothing
| otherwise = Just ((k, v), case FT.viewl r of
_ :< r' -> PQueue (l >< r')
_ -> error "can't happen")
where
Prio k v = measure q
(l, r) = FT.split (below k) q
below :: Ord k => k -> Prio k v -> Bool
below _ NoPrio = False
below k (Prio k' _) = k' <= k
assocs :: Ord k => PQueue k v -> [(k, v)]
assocs = unfoldr minViewWithKey