sets-0.0.6.2: Ducktyped set interface for Haskell containers.

Safe HaskellNone
LanguageHaskell2010

Data.Set.Ordered.Unique.With

Contents

Description

Orient the ordering of your set by a different index, by first supplying a function (a -> k) to weigh each element. This module simply leverages Data.Map, and does not use a novel data type.

Note: This data type can only have one element per distinguished weight. For oriented multisets, use Data.Set.Ordered.Many.With.SetsWith.

Synopsis

Documentation

newtype SetWith k a Source #

Constructors

SetWith 

Fields

Instances
Ord k => HasInsert a (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

insert :: a -> SetWith k a -> SetWith k a Source #

Ord k => HasDelete a (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

delete :: a -> SetWith k a -> SetWith k a Source #

Foldable (SetWith k) Source # 
Instance details

Defined in Data.Set.Ordered.Unique.With

Methods

fold :: Monoid m => SetWith k m -> m #

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

foldr :: (a -> b -> b) -> b -> SetWith k a -> b #

foldr' :: (a -> b -> b) -> b -> SetWith k a -> b #

foldl :: (b -> a -> b) -> b -> SetWith k a -> b #

foldl' :: (b -> a -> b) -> b -> SetWith k a -> b #

foldr1 :: (a -> a -> a) -> SetWith k a -> a #

foldl1 :: (a -> a -> a) -> SetWith k a -> a #

toList :: SetWith k a -> [a] #

null :: SetWith k a -> Bool #

length :: SetWith k a -> Int #

elem :: Eq a => a -> SetWith k a -> Bool #

maximum :: Ord a => SetWith k a -> a #

minimum :: Ord a => SetWith k a -> a #

sum :: Num a => SetWith k a -> a #

product :: Num a => SetWith k a -> a #

(Semigroup k, Ord k) => Semigroup (SetWith k a) Source # 
Instance details

Defined in Data.Set.Ordered.Unique.With

Methods

(<>) :: SetWith k a -> SetWith k a -> SetWith k a #

sconcat :: NonEmpty (SetWith k a) -> SetWith k a #

stimes :: Integral b => b -> SetWith k a -> SetWith k a #

(Monoid k, Ord k) => Monoid (SetWith k a) Source # 
Instance details

Defined in Data.Set.Ordered.Unique.With

Methods

mempty :: SetWith k a #

mappend :: SetWith k a -> SetWith k a -> SetWith k a #

mconcat :: [SetWith k a] -> SetWith k a #

(Ord k, Eq a) => CanBeProperSubset (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

isProperSubsetOf :: SetWith k a -> SetWith k a -> Bool Source #

(Ord k, Eq a) => CanBeSubset (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

isSubsetOf :: SetWith k a -> SetWith k a -> Bool Source #

HasSize (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

size :: SetWith k a -> Int Source #

Ord k => HasDifference (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

difference :: SetWith k a -> SetWith k a -> SetWith k a Source #

Ord k => HasIntersection (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

intersection :: SetWith k a -> SetWith k a -> SetWith k a Source #

Ord k => HasUnion (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

union :: SetWith k a -> SetWith k a -> SetWith k a Source #

Ord k => HasSingletonWith (a -> k) a (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

singletonWith :: (a -> k) -> a -> SetWith k a Source #

HasEmptyWith (a -> k) (SetWith k a) Source # 
Instance details

Defined in Data.Set.Class

Methods

emptyWith :: (a -> k) -> SetWith k a Source #

Operators

(\\) :: Ord k => SetWith k a -> SetWith k a -> SetWith k a Source #

Query

size :: SetWith k a -> Int Source #

member :: Ord k => a -> SetWith k a -> Bool Source #

notMember :: Ord k => a -> SetWith k a -> Bool Source #

lookupLT :: Ord k => a -> SetWith k a -> Maybe a Source #

lookupGT :: Ord k => a -> SetWith k a -> Maybe a Source #

lookupLE :: Ord k => a -> SetWith k a -> Maybe a Source #

lookupGE :: Ord k => a -> SetWith k a -> Maybe a Source #

isSubsetOf :: (Eq a, Ord k) => SetWith k a -> SetWith k a -> Bool Source #

isProperSubsetOf :: (Eq a, Ord k) => SetWith k a -> SetWith k a -> Bool Source #

Construction

empty :: (a -> k) -> SetWith k a Source #

singleton :: Ord k => (a -> k) -> a -> SetWith k a Source #

insert :: Ord k => a -> SetWith k a -> SetWith k a Source #

delete :: Ord k => a -> SetWith k a -> SetWith k a Source #

Combine

union :: Ord k => SetWith k a -> SetWith k a -> SetWith k a Source #

unions :: Ord k => (a -> k) -> [SetWith k a] -> SetWith k a Source #

difference :: Ord k => SetWith k a -> SetWith k a -> SetWith k a Source #

intersection :: Ord k => SetWith k a -> SetWith k a -> SetWith k a Source #

Filter

filter :: (a -> Bool) -> SetWith k a -> SetWith k a Source #

partition :: (a -> Bool) -> SetWith k a -> (SetWith k a, SetWith k a) Source #

split :: Ord k => a -> SetWith k a -> (SetWith k a, SetWith k a) Source #

splitMember :: Ord k => a -> SetWith k a -> (SetWith k a, Bool, SetWith k a) Source #

splitRoot :: SetWith k a -> [SetWith k a] Source #

Indexed

lookupIndex :: Ord k => a -> SetWith k a -> Maybe Int Source #

findIndex :: Ord k => a -> SetWith k a -> Int Source #

elemAt :: Int -> SetWith k a -> a Source #

deleteAt :: Int -> SetWith k a -> SetWith k a Source #

Map

map :: (a -> b) -> (b -> a) -> SetWith k a -> SetWith k b Source #

mapMaybe :: (a -> Maybe b) -> (b -> a) -> SetWith k a -> SetWith k b Source #

Folds

foldr :: (a -> b -> b) -> b -> SetWith k a -> b Source #

foldl :: (b -> a -> b) -> b -> SetWith k a -> b Source #

Strict Folds

foldr' :: (a -> b -> b) -> b -> SetWith k a -> b Source #

foldl' :: (b -> a -> b) -> b -> SetWith k a -> b Source #

Legacy Fold

fold :: (a -> b -> b) -> b -> SetWith k a -> b Source #

Min/Max

findMin :: SetWith k a -> a Source #

findMax :: SetWith k a -> a Source #

deleteFindMin :: SetWith k a -> (a, SetWith k a) Source #

deleteFindMax :: SetWith k a -> (a, SetWith k a) Source #

minView :: SetWith k a -> Maybe (a, SetWith k a) Source #

maxView :: SetWith k a -> Maybe (a, SetWith k a) Source #

Conversion

elems :: SetWith k a -> [a] Source #

toList :: SetWith k a -> (a -> k, [a]) Source #

fromList :: (Ord k, Foldable f) => (a -> k) -> f a -> SetWith k a Source #

Ordered List

toAscList :: SetWith k a -> [a] Source #

toDescList :: SetWith k a -> [a] Source #

fromAscList :: Eq k => (a -> k) -> [a] -> SetWith k a Source #

fromDistinctAscList :: (a -> k) -> [a] -> SetWith k a Source #

Debugging

showTree :: (Show k, Show a) => SetWith k a -> String Source #

showTreeWith :: (k -> a -> String) -> Bool -> Bool -> SetWith k a -> String Source #