signed-multiset-0.5: Multisets with negative membership.
Copyright(c) 2012 Stefan Holdermans
LicenseBSD-style
Maintainerstefan@vectorfabrics.com
Stabilityprovisional
Portabilitynon-portable (DeriveDataTypeable)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.SignedMultiset

Description

An efficient implementation of signed multisets.

A signed multiset is like a multiset (or bag), but additionally allows for negative membership. That is, in a signed multiset, an object can occur a negative number of times.

For a theory of signed multisets, see

  • Wayne D. Blizard. Negative membership. Notre Dame Journal of Formal Logic, 31(3):346--368, 1990.

Since many function names (but not the type name) clash with Prelude names, this module is usually imported qualified, e.g.,

 import Data.SignedMultiset (SignedMultiset)
 import qualified Data.SignedMultiset as SignedMultiset

Function comments contain the function's time complexity in so-called big-O notation, with n referring to the number of multiset members involved.

Signed-multiset types are constructed by the type constructor SignedMultiset. The number of times an object appears in a signed multiset is called its multiplicity. An object is said to be a member of a signed multiset if it has a nonzero multiplicity. The number of members of a signed multiset is referred to as its size, while the cardinality of a signed multiset is the sum of the multiplicities of its members. A signed multiset is empty if it is without members.

Textually, signed multisets are represented by listing their members and, in parentheses, their multiplicities between curly brackets. For instance, the signed multiset that contains -1 copies of 2, 2 copies of 3, and -4 copies of 5 is denoted by "{2(-1),3(2),5(-4)}".

Synopsis

Type

data SignedMultiset a Source #

A signed multiset over objects of type a.

Instances

Instances details
(Ord a, Data a) => Data (SignedMultiset a) Source # 
Instance details

Defined in Data.SignedMultiset

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SignedMultiset a -> c (SignedMultiset a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SignedMultiset a) #

toConstr :: SignedMultiset a -> Constr #

dataTypeOf :: SignedMultiset a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SignedMultiset a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SignedMultiset a)) #

gmapT :: (forall b. Data b => b -> b) -> SignedMultiset a -> SignedMultiset a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SignedMultiset a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SignedMultiset a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SignedMultiset a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SignedMultiset a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SignedMultiset a -> m (SignedMultiset a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SignedMultiset a -> m (SignedMultiset a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SignedMultiset a -> m (SignedMultiset a) #

Ord a => Monoid (SignedMultiset a) Source #

Monoid under union.

Instance details

Defined in Data.SignedMultiset

Ord a => Semigroup (SignedMultiset a) Source #

Semigroup under union.

Instance details

Defined in Data.SignedMultiset

(Ord a, Read a) => Read (SignedMultiset a) Source # 
Instance details

Defined in Data.SignedMultiset

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

Defined in Data.SignedMultiset

Ord a => Eq (SignedMultiset a) Source # 
Instance details

Defined in Data.SignedMultiset

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

Defined in Data.SignedMultiset

Construction

empty :: SignedMultiset a Source #

O(1). The empty signed multiset, i.e., the multiset in which every object has multiplicity zero.

singleton :: a -> SignedMultiset a Source #

O(1). Create a signed multiset that contains exactly one copy of the given object.

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

O(log n). Insert a new copy of the given object into a signed multiset, i.e., increment the multiplicity of the object by 1.

insertMany :: Ord a => a -> Int -> SignedMultiset a -> SignedMultiset a Source #

O(log n). Insert a specified number of new copies of the given object into a signed multiset, i.e., increment the multiplicity of the object by the specified number. If the specified number is negative, copies are deleted from the set.

delete :: Ord a => a -> SignedMultiset a -> SignedMultiset a Source #

O(log n). Delete a copy of the given object from a signed multiset, i.e., decrement the multiplicity of the object by 1.

deleteMany :: Ord a => a -> Int -> SignedMultiset a -> SignedMultiset a Source #

O(log n). Delete a specified number of copies of the given object from a signed multiset, i.e., decrement the multiplicity of the object by the specified number. If the specified number is negative, new copies of the object are inserted into the set.

deleteAll :: Ord a => a -> SignedMultiset a -> SignedMultiset a Source #

O(log n). Delete all copies of the given object from a signed multiset, i.e., set the multiplicity of the object to zero.

Queries

null :: SignedMultiset a -> Bool Source #

O(1). Return whether the signed multiset is empty, i.e., whether every object has multiplicity zero.

isSet :: SignedMultiset a -> Bool Source #

O(n). Return whether the signed multiset is a set, i.e., whether all object have either multiplicity zero or else multiplicity 1.

isPositive :: SignedMultiset a -> Bool Source #

O(n). Return whether all objects in the signed multiset have nonnegative multiplicities.

isNegative :: SignedMultiset a -> Bool Source #

O(n). Return whether all objects in the signed multiset have nonpositive multiplicities.

size :: SignedMultiset a -> Int Source #

O(1). Return the number of members of the signed multiset, i.e., the number of objects that have nonzero multiplicity.

cardinality :: SignedMultiset a -> Int Source #

O(n). Return the cardinality of the signed multiset, i.e., the sum of the multiplicities of all objects.

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

O(log n). Return whether the given object is a member of the signed multiset, i.e., whether the object has nonzero multiplicity.

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

O(log n). Return whether the given object is not a member of the signed multiset, i.e., whether the object has multiplicity zero.

multiplicity :: Ord a => a -> SignedMultiset a -> Int Source #

O(log n). Return the multiplicity of the given object in the signed multiset.

isSubmultisetOf :: Ord a => SignedMultiset a -> SignedMultiset a -> Bool Source #

O(n). Return whether the first signed multiset is a submultiset of the second, i.e., whether each object that has nonzero multiplicity m in the first multiset has nonzero multiplicity n with m <= n in the second.

Combining

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

O(n). Return the union of two signed multisets. The multiplicity of an object in the returned multiset is the maximum of its nonzero multiplicities in the argument multisets.

additiveUnion :: Ord a => SignedMultiset a -> SignedMultiset a -> SignedMultiset a Source #

O(n). Return the additive union of two signed multisets. The multiplicity of an object in the returned multiset is the sum of its multiplicities in the argument multisets.

intersection :: Ord a => SignedMultiset a -> SignedMultiset a -> SignedMultiset a Source #

O(n). Return the intersection of two signed multisets. If an object has nonzero multiplicity in both argument multisets, its multiplicity in the returned multiset is the minimum of its multiplicities in the argument multisets; otherwise, its multiplicity in the returned multiset is zero.

Memberwise operations

root :: SignedMultiset a -> SignedMultiset a Source #

O(n). Return the root of the signed multiset. The multiplicity of an object in the returned multiset is zero if its multiplicity in the argument multiset is zero and 1 otherwise.

shadow :: SignedMultiset a -> SignedMultiset a Source #

O(n). Return the shadow of the signed multiset. The multiplicity of an object in the returned multiset is the additive inverse of its multiplicity in the argument multiset.

modulus :: SignedMultiset a -> SignedMultiset a Source #

O(n). Return the modulus of the signed multiset. The multiplicity of an object in the returned multiset is the absolute value of its multiplicity in the argument multiset.

signum :: SignedMultiset a -> SignedMultiset a Source #

O(n). Return the signum of the signed multiset. The multiplicity of an object in the returned multiset is -1 if it has negative multiplicity in the argument multiset, zero if its multiplicity in the argument multiset is zero, and 1 if it has positive multiplicity in the argument multiset.

unitstep :: SignedMultiset a -> SignedMultiset a Source #

O(n). Return the left-continuous unit step of the signed multiset. The multiplicity of an object in the returned multiset is zero if it has negative multiplicity in the argument multiset, and 1 otherwise.

multiply :: Int -> SignedMultiset a -> SignedMultiset a Source #

O(n). Return the additive union of the given number of copies of the signed multiset.

Traversals

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

O(n * log n). Apply the given function to all objects of the signed multiset. If the the function maps distinct objects to the same new object, the multiplicity of the new object is the maximum of the nonzero multiplicities of the two original objects.

additiveMap :: Ord b => (a -> b) -> SignedMultiset a -> SignedMultiset b Source #

O(n * log n). Apply the given function to all objects of the signed multiset. If the the function maps distinct objects to the same new object, the multiplicity of the new object is the sum of the multiplicities of the two original objects.

filter :: (a -> Int -> Bool) -> SignedMultiset a -> SignedMultiset a Source #

O(n). Apply the given predicate to the members of the signed multiset and their multiplicities. The returned multiset contains the copies of the members that satisfy the predicate.

partition :: (a -> Int -> Bool) -> SignedMultiset a -> (SignedMultiset a, SignedMultiset a) Source #

O(n). Apply the given predicate to the members of the signed multiset and their multiplicity. The first returned multiset contains the copies of the members that satisfy the predicate, while the second returned multiset contains the copies of the members that do not satisfy the predicate.

split :: Int -> SignedMultiset a -> (SignedMultiset a, SignedMultiset a) Source #

O(n). Split the signed multiset into a multiset containing the copies of the members with a multiplicity less than or equal to the given number and a multiset containing the copies of the members with a multiplicity greater than the given number.

foldr :: (a -> Int -> b -> b) -> b -> SignedMultiset a -> b Source #

O(n). Perform a right-associative fold on the members of the signed multiset and their multiplicities using the given operator and start value.

foldr' :: (a -> Int -> b -> b) -> b -> SignedMultiset a -> b Source #

O(n). Perform a strict right-associative fold on the members of the signed multiset and their multiplicities using the given operator and start value.

foldl :: (a -> b -> Int -> a) -> a -> SignedMultiset b -> a Source #

O(n). Perform a left-associative fold on the members of the signed multiset and their multiplicities using the given operator and start value.

foldl' :: (a -> b -> Int -> a) -> a -> SignedMultiset b -> a Source #

O(n). Perform a strict left-associative fold on the members of the signed multiset and their multiplicities using the given operator and start value.

Conversion

toList :: SignedMultiset a -> [(a, Int)] Source #

O(n). Convert the signed multiset to a list that associates all members of the multiset with their multiplicity.

toLists :: SignedMultiset a -> ([a], [a]) Source #

O(n + k) (with k the combined length of the returned lists). Return two lists, such that: for each object with a positive multiplicity m in the signed multiset, the first list contains m copies and the second list contains no copies of the object; for each object with a negative multiplicity -n, the first list contains no and the second list contains n copies of the object; and for each object with zero multiplicity, neither list contains a copy of the object.

fromList :: Ord a => [(a, Int)] -> SignedMultiset a Source #

O(k * log n) (with k the length of the argument list). Construct a signed multiset from a list of object/multiplicity pairs.

fromLists :: Ord a => [a] -> [a] -> SignedMultiset a Source #

O(k * log n) (with k the combined length of the argument lists). Construct a signed multiset by, starting from the empty multiset, inserting copies of objects from the first argument list and deleting copies of objects from the second argument list.

Additive wrapper

newtype Additive a Source #

An element of the free abelian group on a.

Constructors

Additive 

Instances

Instances details
Ord a => Monoid (Additive a) Source #

Monoid under additiveUnion.

Instance details

Defined in Data.SignedMultiset

Methods

mempty :: Additive a #

mappend :: Additive a -> Additive a -> Additive a #

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

Ord a => Semigroup (Additive a) Source #

Semigroup under additiveUnion.

Instance details

Defined in Data.SignedMultiset

Methods

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

sconcat :: NonEmpty (Additive a) -> Additive a #

stimes :: Integral b => b -> Additive a -> Additive a #

(Ord a, Read a) => Read (Additive a) Source # 
Instance details

Defined in Data.SignedMultiset

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

Defined in Data.SignedMultiset

Methods

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

show :: Additive a -> String #

showList :: [Additive a] -> ShowS #

Ord a => Eq (Additive a) Source # 
Instance details

Defined in Data.SignedMultiset

Methods

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

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

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

Defined in Data.SignedMultiset

Methods

compare :: Additive a -> Additive a -> Ordering #

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

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

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

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

max :: Additive a -> Additive a -> Additive a #

min :: Additive a -> Additive a -> Additive a #