Agda-2.5.1.1: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell98

Agda.Utils.Bag

Contents

Description

A simple overlay over Data.Map to manage unordered sets with duplicates.

Synopsis

Documentation

newtype Bag a Source #

A set with duplicates. Faithfully stores elements which are equal with regard to (==).

Constructors

Bag 

Fields

Instances

Foldable Bag Source # 

Methods

fold :: Monoid m => Bag m -> m #

foldMap :: Monoid m => (a -> m) -> Bag a -> m #

foldr :: (a -> b -> b) -> b -> Bag a -> b #

foldr' :: (a -> b -> b) -> b -> Bag a -> b #

foldl :: (b -> a -> b) -> b -> Bag a -> b #

foldl' :: (b -> a -> b) -> b -> Bag a -> b #

foldr1 :: (a -> a -> a) -> Bag a -> a #

foldl1 :: (a -> a -> a) -> Bag a -> a #

toList :: Bag a -> [a] #

null :: Bag a -> Bool #

length :: Bag a -> Int #

elem :: Eq a => a -> Bag a -> Bool #

maximum :: Ord a => Bag a -> a #

minimum :: Ord a => Bag a -> a #

sum :: Num a => Bag a -> a #

product :: Num a => Bag a -> a #

Eq a => Eq (Bag a) Source # 

Methods

(==) :: Bag a -> Bag a -> Bool #

(/=) :: Bag a -> Bag a -> Bool #

Ord a => Ord (Bag a) Source # 

Methods

compare :: Bag a -> Bag a -> Ordering #

(<) :: Bag a -> Bag a -> Bool #

(<=) :: Bag a -> Bag a -> Bool #

(>) :: Bag a -> Bag a -> Bool #

(>=) :: Bag a -> Bag a -> Bool #

max :: Bag a -> Bag a -> Bag a #

min :: Bag a -> Bag a -> Bag a #

Show a => Show (Bag a) Source # 

Methods

showsPrec :: Int -> Bag a -> ShowS #

show :: Bag a -> String #

showList :: [Bag a] -> ShowS #

Ord a => Monoid (Bag a) Source # 

Methods

mempty :: Bag a #

mappend :: Bag a -> Bag a -> Bag a #

mconcat :: [Bag a] -> Bag a #

(Ord a, Arbitrary a) => Arbitrary (Bag a) Source # 

Methods

arbitrary :: Gen (Bag a) #

shrink :: Bag a -> [Bag a] #

Null (Bag a) Source # 

Methods

empty :: Bag a Source #

null :: Bag a -> Bool Source #

Query

null :: Bag a -> Bool Source #

size :: Bag a -> Int Source #

(!) :: Ord a => Bag a -> a -> [a] Source #

bag ! a finds all elements equal to a.

member :: Ord a => a -> Bag a -> Bool Source #

notMember :: Ord a => a -> Bag a -> Bool Source #

count :: Ord a => a -> Bag a -> Int Source #

Return the multiplicity of the given element.

Construction

singleton :: a -> Bag a Source #

union :: Ord a => Bag a -> Bag a -> Bag a Source #

unions :: Ord a => [Bag a] -> Bag a Source #

insert :: Ord a => a -> Bag a -> Bag a Source #

insert a b = union b (singleton a)

fromList :: Ord a => [a] -> Bag a Source #

fromList = unions . map singleton

Destruction

groups :: Bag a -> [[a]] Source #

Returns the elements of the bag, grouped by equality (==).

toList :: Bag a -> [a] Source #

Returns the bag, with duplicates.

keys :: Bag a -> [a] Source #

Returns the bag without duplicates.

elems :: Bag a -> [a] Source #

Returns the bag, with duplicates.

toAscList :: Bag a -> [a] Source #

Traversal

map :: Ord b => (a -> b) -> Bag a -> Bag b Source #

traverse' :: forall a b m. (Applicative m, Ord b) => (a -> m b) -> Bag a -> m (Bag b) Source #

Instances

Properties

prop_count_insert :: Ord a => a -> Bag a -> Bool Source #

prop_size_union :: Ord a => Bag a -> Bag a -> Bool Source #

prop_map_compose :: (Ord b, Ord c) => (b -> c) -> (a -> b) -> Bag a -> Bool Source #

All tests

tests :: IO Bool Source #

All tests as collected by quickCheckAll.

Using quickCheckAll is convenient and superior to the manual enumeration of tests, since the name of the property is added automatically.