lazy-priority-queue-0.1: Lazy-Spined Monadic Priority Queues

Safe HaskellNone
LanguageHaskell2010

Data.PriorityQueue

Synopsis

Documentation

data PQueue t c a Source #

Instances
(Semigroup c, Alternative (PQueue t c)) => Monad (PQueue t c) Source # 
Instance details

Defined in Data.PriorityQueue

Methods

(>>=) :: PQueue t c a -> (a -> PQueue t c b) -> PQueue t c b #

(>>) :: PQueue t c a -> PQueue t c b -> PQueue t c b #

return :: a -> PQueue t c a #

fail :: String -> PQueue t c a #

Functor (PQueue t c) Source # 
Instance details

Defined in Data.PriorityQueue

Methods

fmap :: (a -> b) -> PQueue t c a -> PQueue t c b #

(<$) :: a -> PQueue t c b -> PQueue t c a #

(Alternative (PQueue t c), Semigroup c) => Applicative (PQueue t c) Source # 
Instance details

Defined in Data.PriorityQueue

Methods

pure :: a -> PQueue t c a #

(<*>) :: PQueue t c (a -> b) -> PQueue t c a -> PQueue t c b #

liftA2 :: (a -> b -> c0) -> PQueue t c a -> PQueue t c b -> PQueue t c c0 #

(*>) :: PQueue t c a -> PQueue t c b -> PQueue t c b #

(<*) :: PQueue t c a -> PQueue t c b -> PQueue t c a #

Foldable (PQueue t c) Source # 
Instance details

Defined in Data.PriorityQueue

Methods

fold :: Monoid m => PQueue t c m -> m #

foldMap :: Monoid m => (a -> m) -> PQueue t c a -> m #

foldr :: (a -> b -> b) -> b -> PQueue t c a -> b #

foldr' :: (a -> b -> b) -> b -> PQueue t c a -> b #

foldl :: (b -> a -> b) -> b -> PQueue t c a -> b #

foldl' :: (b -> a -> b) -> b -> PQueue t c a -> b #

foldr1 :: (a -> a -> a) -> PQueue t c a -> a #

foldl1 :: (a -> a -> a) -> PQueue t c a -> a #

toList :: PQueue t c a -> [a] #

null :: PQueue t c a -> Bool #

length :: PQueue t c a -> Int #

elem :: Eq a => a -> PQueue t c a -> Bool #

maximum :: Ord a => PQueue t c a -> a #

minimum :: Ord a => PQueue t c a -> a #

sum :: Num a => PQueue t c a -> a #

product :: Num a => PQueue t c a -> a #

(Num c, Ord c, Semigroup c) => Alternative (PQueue Pruned c) Source # 
Instance details

Defined in Data.PriorityQueue

Methods

empty :: PQueue Pruned c a #

(<|>) :: PQueue Pruned c a -> PQueue Pruned c a -> PQueue Pruned c a #

some :: PQueue Pruned c a -> PQueue Pruned c [a] #

many :: PQueue Pruned c a -> PQueue Pruned c [a] #

(Num c, Ord c, Semigroup c) => Alternative (PQueue Branching c) Source # 
Instance details

Defined in Data.PriorityQueue

(Show c, Show a) => Show (PQueue t c a) Source # 
Instance details

Defined in Data.PriorityQueue

Methods

showsPrec :: Int -> PQueue t c a -> ShowS #

show :: PQueue t c a -> String #

showList :: [PQueue t c a] -> ShowS #

data Branching Source #

Instances
(Num c, Ord c, Semigroup c) => Alternative (PQueue Branching c) Source # 
Instance details

Defined in Data.PriorityQueue

data Pruned Source #

Instances
(Num c, Ord c, Semigroup c) => Alternative (PQueue Pruned c) Source # 
Instance details

Defined in Data.PriorityQueue

Methods

empty :: PQueue Pruned c a #

(<|>) :: PQueue Pruned c a -> PQueue Pruned c a -> PQueue Pruned c a #

some :: PQueue Pruned c a -> PQueue Pruned c [a] #

many :: PQueue Pruned c a -> PQueue Pruned c [a] #

branchable :: PQueue Pruned c a -> PQueue t c a Source #

Relax the Pruned phantom constraint, allowing the queue to become Branching.

prune :: PQueue t c a -> PQueue Pruned c a Source #

Prune away all stored values except the one with the least penalty, making the queue Pruned.

pruneAbove :: (Semigroup c, Num c, Ord c) => c -> PQueue t c a -> PQueue t c a Source #

Prune away all stored values more expensive than the given cost.

pruneAlternativesAbove :: (Semigroup c, Num c, Ord c) => c -> PQueue t c a -> PQueue t c a Source #

Prune away all stored values more expensive than the given cost and a less expensive alternative value.

mapWithCost :: Monoid c => (c -> a -> b) -> PQueue t c a -> PQueue t c b Source #

Maps each item contained in the queue, supplying the item's cost as first argument

filter :: (a -> Bool) -> PQueue t c a -> PQueue t c a Source #

Filter away from the queue the values that the argument function maps to False

foldPeers :: (a -> a -> a) -> PQueue t c a -> PQueue t c a Source #

Fold together all stored values that share the same priority.

canonical :: Semigroup c => PQueue t c a -> PQueue t c a Source #

Minimize the queue structure. This operation forces the entire spine of the queue and its every level.

pruneSubsets :: (a -> b -> Maybe (a, b)) -> a -> PQueue t c b -> PQueue t c b Source #

Assuming the stored values belong to a cancellative monoid, prune away all extraneous values and factors using the supplied function that calculates the sum and difference of the two values, if there is any difference, and the monoid null. > fold (pruneSubsets plusDiff mempty pq) == fold pq > where plusDiff u a > | gcd u a == a = Nothing > | d a - gcd u a = Just (u < d, d)

strip :: (Ord c, Num c) => PQueue Pruned c a -> PQueue t c b -> PQueue t c b Source #

Subtract the first argument cost GCD from the cost of every value in the second argument

stripCommon :: (Ord c, Num c, Functor f, Foldable f, Alternative (PQueue t c)) => f (PQueue t c a) -> (PQueue Pruned c (a -> a), f (PQueue t c a)) Source #

Returns the pair of the GCD of all the penalties and the penalties without the GCD > gcd * rest == f > where (gcd, rest) = stripCommon f

cost :: (Semigroup c, Num c, Ord c) => c -> PQueue Branching c () Source #

Imposes the given cost on the current computation branch. > cost k = withCost k (pure ())

leastCost :: Monoid c => PQueue t c a -> Maybe c Source #

Returns Just the minimal cost present in the queue, Nothing if the queue is empty.

withCost :: (Semigroup c, Num c, Ord c) => c -> PQueue t c a -> PQueue t c a Source #

withCost k adds a penalty of k to each value in the queue.