set-monad-0.3.0.0: Set monad

Safe HaskellSafe
LanguageHaskell98

Data.Set.Monad

Contents

Description

The set-monad library exports the Set abstract data type and set-manipulating functions. These functions behave exactly as their namesakes from the Data.Set module of the containers library. In addition, the set-monad library extends Data.Set by providing Functor, Applicative, Alternative, Monad, and MonadPlus instances for sets.

In other words, you can use the set-monad library as a drop-in replacement for the Data.Set module of the containers library and, in addition, you will also get the aforementioned instances which are not available in the containers package.

It is not possible to directly implement instances for the aforementioned standard Haskell type classes for the Set data type from the containers library. This is because the key operations map and union, are constrained with Ord as follows.

map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b
union :: (Ord a) => Set a -> Set a -> Set a

The set-monad library provides the type class instances by wrapping the constrained Set type into a data type that has unconstrained constructors corresponding to monadic combinators. The data type constructors that represent monadic combinators are evaluated with a constrained run function. This elevates the need to use the constraints in the instance definitions (this is what prevents a direct definition). The wrapping and unwrapping happens internally in the library and does not affect its interface.

For details, see the rather compact definitions of the run function and type class instances. The left identity and associativity monad laws play a crucial role in the definition of the run function. The rest of the code should be self explanatory.

The technique is not new. This library was inspired by [1]. To my knowledge, the original, systematic presentation of the idea to represent monadic combinators as data is given in [2]. There is also a Haskell library that provides a generic infrastructure for the aforementioned wrapping and unwrapping [3].

The set-monad library is particularly useful for writing set-oriented code using the do and/or monad comprehension notations. For example, the following definitions now type check.

s1 :: Set (Int,Int)
s1 = do a <- fromList [1 .. 4]
        b <- fromList [1 .. 4]
        return (a,b)
-- with -XMonadComprehensions
s2 :: Set (Int,Int)
s2 = [ (a,b) | (a,b) <- s1, even a, even b ]
s3 :: Set Int
s3 = fmap (+1) (fromList [1 .. 4])

As noted in [1], the implementation technique can be used for monadic libraries and EDSLs with restricted types (compiled EDSLs often restrict the types that they can handle). Haskell's standard monad type class can be used for restricted monad instances. There is no need to resort to GHC extensions that rebind the standard monadic combinators with the library or EDSL specific ones.

[1] CSDL Blog: The home of applied functional programming at KU. Monad Reification in Haskell and the Sunroof Javascript compiler. http://www.ittc.ku.edu/csdlblog/?p=88

[2] Chuan-kai Lin. 2006. Programming monads operationally with Unimo. In Proceedings of the eleventh ACM SIGPLAN International Conference on Functional Programming (ICFP '06). ACM.

[3] Heinrich Apfelmus. The operational package. http://hackage.haskell.org/package/operational

Synopsis

Set type

data Set a Source #

Instances
Monad Set Source # 
Instance details

Defined in Data.Set.Monad

Methods

(>>=) :: Set a -> (a -> Set b) -> Set b #

(>>) :: Set a -> Set b -> Set b #

return :: a -> Set a #

fail :: String -> Set a #

Functor Set Source # 
Instance details

Defined in Data.Set.Monad

Methods

fmap :: (a -> b) -> Set a -> Set b #

(<$) :: a -> Set b -> Set a #

Applicative Set Source # 
Instance details

Defined in Data.Set.Monad

Methods

pure :: a -> Set a #

(<*>) :: Set (a -> b) -> Set a -> Set b #

liftA2 :: (a -> b -> c) -> Set a -> Set b -> Set c #

(*>) :: Set a -> Set b -> Set b #

(<*) :: Set a -> Set b -> Set a #

Foldable Set Source # 
Instance details

Defined in Data.Set.Monad

Methods

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

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

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

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

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

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

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

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

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

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

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

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

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

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

Alternative Set Source # 
Instance details

Defined in Data.Set.Monad

Methods

empty :: Set a #

(<|>) :: Set a -> Set a -> Set a #

some :: Set a -> Set [a] #

many :: Set a -> Set [a] #

MonadPlus Set Source # 
Instance details

Defined in Data.Set.Monad

Methods

mzero :: Set a #

mplus :: Set a -> Set a -> Set a #

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

Defined in Data.Set.Monad

Methods

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

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

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

Defined in Data.Set.Monad

Methods

compare :: Set a -> Set a -> Ordering #

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

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

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

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

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

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

Defined in Data.Set.Monad

(Show a, Ord a) => Show (Set a) Source # 
Instance details

Defined in Data.Set.Monad

Methods

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

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Semigroup (Set a) Source # 
Instance details

Defined in Data.Set.Monad

Methods

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

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

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

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

Defined in Data.Set.Monad

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

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

(NFData a, Ord a) => NFData (Set a) Source # 
Instance details

Defined in Data.Set.Monad

Methods

rnf :: Set a -> () #

Operators

(\\) :: Ord a => Set a -> Set a -> Set a infixl 9 Source #

Query

null :: Ord a => Set a -> Bool Source #

size :: Ord a => Set a -> Int Source #

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

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

isSubsetOf :: Ord a => Set a -> Set a -> Bool Source #

isProperSubsetOf :: Ord a => Set a -> Set a -> Bool Source #

Construction

empty :: Ord a => Set a Source #

singleton :: Ord a => a -> Set a Source #

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

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

Combine

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

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

difference :: Ord a => Set a -> Set a -> Set a Source #

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

Filter

filter :: Ord a => (a -> Bool) -> Set a -> Set a Source #

partition :: Ord a => (a -> Bool) -> Set a -> (Set a, Set a) Source #

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

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

Map

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

mapMonotonic :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b Source #

Folds

foldr :: Ord a => (a -> b -> b) -> b -> Set a -> b Source #

foldl :: Ord a => (b -> a -> b) -> b -> Set a -> b Source #

Strict folds

foldr' :: Ord a => (a -> b -> b) -> b -> Set a -> b Source #

foldl' :: Ord a => (b -> a -> b) -> b -> Set a -> b Source #

Legacy folds

fold :: Ord a => (a -> b -> b) -> b -> Set a -> b Source #

Min/Max

findMin :: Ord a => Set a -> a Source #

findMax :: Ord a => Set a -> a Source #

deleteMin :: Ord a => Set a -> Set a Source #

deleteMax :: Ord a => Set a -> Set a Source #

deleteFindMin :: Ord a => Set a -> (a, Set a) Source #

deleteFindMax :: Ord a => Set a -> (a, Set a) Source #

maxView :: Ord a => Set a -> Maybe (a, Set a) Source #

minView :: Ord a => Set a -> Maybe (a, Set a) Source #

Conversion

List

elems :: Ord a => Set a -> [a] Source #

toList :: Ord a => Set a -> [a] Source #

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

Ordered list

toAscList :: Ord a => Set a -> [a] Source #

fromAscList :: Ord a => [a] -> Set a Source #

Debugging

showTree :: (Show a, Ord a) => Set a -> String Source #

showTreeWith :: (Show a, Ord a) => Bool -> Bool -> Set a -> String Source #

valid :: Ord a => Set a -> Bool Source #