cabal-install-solver-3.8.1.0: The command-line interface for Cabal and Hackage.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Solver.Modular.WeightedPSQ

Synopsis

Documentation

data WeightedPSQ w k v Source #

An association list that is sorted by weight.

Each element has a key (k), value (v), and weight (w). All operations that add elements or modify weights stably sort the elements by weight.

Instances

Instances details
Functor (WeightedPSQ w k) Source # 
Instance details

Defined in Distribution.Solver.Modular.WeightedPSQ

Methods

fmap :: (a -> b) -> WeightedPSQ w k a -> WeightedPSQ w k b #

(<$) :: a -> WeightedPSQ w k b -> WeightedPSQ w k a #

Foldable (WeightedPSQ w k) Source # 
Instance details

Defined in Distribution.Solver.Modular.WeightedPSQ

Methods

fold :: Monoid m => WeightedPSQ w k m -> m #

foldMap :: Monoid m => (a -> m) -> WeightedPSQ w k a -> m #

foldMap' :: Monoid m => (a -> m) -> WeightedPSQ w k a -> m #

foldr :: (a -> b -> b) -> b -> WeightedPSQ w k a -> b #

foldr' :: (a -> b -> b) -> b -> WeightedPSQ w k a -> b #

foldl :: (b -> a -> b) -> b -> WeightedPSQ w k a -> b #

foldl' :: (b -> a -> b) -> b -> WeightedPSQ w k a -> b #

foldr1 :: (a -> a -> a) -> WeightedPSQ w k a -> a #

foldl1 :: (a -> a -> a) -> WeightedPSQ w k a -> a #

toList :: WeightedPSQ w k a -> [a] #

null :: WeightedPSQ w k a -> Bool #

length :: WeightedPSQ w k a -> Int #

elem :: Eq a => a -> WeightedPSQ w k a -> Bool #

maximum :: Ord a => WeightedPSQ w k a -> a #

minimum :: Ord a => WeightedPSQ w k a -> a #

sum :: Num a => WeightedPSQ w k a -> a #

product :: Num a => WeightedPSQ w k a -> a #

Traversable (WeightedPSQ w k) Source # 
Instance details

Defined in Distribution.Solver.Modular.WeightedPSQ

Methods

traverse :: Applicative f => (a -> f b) -> WeightedPSQ w k a -> f (WeightedPSQ w k b) #

sequenceA :: Applicative f => WeightedPSQ w k (f a) -> f (WeightedPSQ w k a) #

mapM :: Monad m => (a -> m b) -> WeightedPSQ w k a -> m (WeightedPSQ w k b) #

sequence :: Monad m => WeightedPSQ w k (m a) -> m (WeightedPSQ w k a) #

(Eq w, Eq k, Eq v) => Eq (WeightedPSQ w k v) Source # 
Instance details

Defined in Distribution.Solver.Modular.WeightedPSQ

Methods

(==) :: WeightedPSQ w k v -> WeightedPSQ w k v -> Bool #

(/=) :: WeightedPSQ w k v -> WeightedPSQ w k v -> Bool #

(Show w, Show k, Show v) => Show (WeightedPSQ w k v) Source # 
Instance details

Defined in Distribution.Solver.Modular.WeightedPSQ

Methods

showsPrec :: Int -> WeightedPSQ w k v -> ShowS #

show :: WeightedPSQ w k v -> String #

showList :: [WeightedPSQ w k v] -> ShowS #

fromList :: Ord w => [(w, k, v)] -> WeightedPSQ w k v Source #

O(N log N).

toList :: WeightedPSQ w k v -> [(w, k, v)] Source #

O(1). Return the elements in order.

keys :: WeightedPSQ w k v -> [k] Source #

O(N). Return the keys in order.

weights :: WeightedPSQ w k v -> [w] Source #

O(N). Return the weights in order.

isZeroOrOne :: WeightedPSQ w k v -> Bool Source #

O(1). Return True if the WeightedPSQ contains zero or one elements.

filter :: (v -> Bool) -> WeightedPSQ k w v -> WeightedPSQ k w v Source #

O(N).

lookup :: Eq k => k -> WeightedPSQ w k v -> Maybe v Source #

O(N). Return the value associated with the first occurrence of the give key, if it exists.

mapWithKey :: (k -> v1 -> v2) -> WeightedPSQ w k v1 -> WeightedPSQ w k v2 Source #

O(N). Update the values.

mapWeightsWithKey :: Ord w2 => (k -> w1 -> w2) -> WeightedPSQ w1 k v -> WeightedPSQ w2 k v Source #

O(N log N). Update the weights.

traverseWithKey :: Applicative f => (k -> v -> f v') -> WeightedPSQ w k v -> f (WeightedPSQ w k v') Source #

O(N). Traverse and update values in some applicative functor.

union :: Ord w => WeightedPSQ w k v -> WeightedPSQ w k v -> WeightedPSQ w k v Source #

O((N + M) log (N + M)). Combine two WeightedPSQs, preserving all elements. Elements from the first WeightedPSQ come before elements in the second when they have the same weight.

takeUntil :: forall w k v. (v -> Bool) -> WeightedPSQ w k v -> WeightedPSQ w k v Source #

O(N). Return the prefix of values ending with the first element that satisfies p, or all elements if none satisfy p.