Agda-2.6.3.20230930: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.Utils.Bag

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

  • bag :: Map a [a]

    The list contains all occurrences of a (not just the duplicates!). Hence, the invariant: the list is never empty.

Instances

Instances details
Foldable Bag Source # 
Instance details

Defined in Agda.Utils.Bag

Methods

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

foldMap :: Monoid m => (a -> m) -> Bag a -> 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

Null (Bag a) Source # 
Instance details

Defined in Agda.Utils.Null

Methods

empty :: Bag a Source #

null :: Bag a -> Bool Source #

Ord a => Monoid (Bag a) Source # 
Instance details

Defined in Agda.Utils.Bag

Methods

mempty :: Bag a

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

mconcat :: [Bag a] -> Bag a

Ord a => Semigroup (Bag a) Source # 
Instance details

Defined in Agda.Utils.Bag

Methods

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

sconcat :: NonEmpty (Bag a) -> Bag a

stimes :: Integral b => b -> Bag a -> Bag a

Show a => Show (Bag a) Source # 
Instance details

Defined in Agda.Utils.Bag

Methods

showsPrec :: Int -> Bag a -> ShowS

show :: Bag a -> String

showList :: [Bag a] -> ShowS

Eq a => Eq (Bag a) Source # 
Instance details

Defined in Agda.Utils.Bag

Methods

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

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

Ord a => Ord (Bag a) Source # 
Instance details

Defined in Agda.Utils.Bag

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

Query

null :: Bag a -> Bool Source #

Is the bag empty?

size :: Bag a -> Int Source #

Number of elements in the bag. Duplicates count. O(n).

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

(bag ! a) finds all elements equal to a. O(log n). Total function, returns [] if none are.

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

O(log n).

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

O(log n).

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

Return the multiplicity of the given element. O(log n + count _ _).

Construction

empty :: Bag a Source #

O(1)

singleton :: a -> Bag a Source #

O(1)

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 #