[Haskell-cafe] [Haskell] ANNOUNCE: set-monad

George Giorgidze giorgidze at gmail.com
Mon Jun 18 22:40:28 CEST 2012


Hi Dan,

Thanks for your feedback and your question regarding the functor laws.

Please try your example in GHCi and/or evaluate it by hand. The
library does not violate the functor laws.

I committed quick check properties for functor laws, as well as, laws
for other type classes to the repo. You can give it a try. It is also
possible, with a little bit of effort, to prove those properties by
hand.

Speaking of laws, BTW, your contrived Ord instance violates one of the
Ord laws. The documentation for Ord says that: "The Ord class is used
for totally ordered datatypes". Your definition violates the
antisymmetry law [1]:

If a <= b and b <= a then a == b

by reporting two elements that are not equal as equal.

Cheers, George

[1] http://en.wikipedia.org/wiki/Totally_ordered

On 16 June 2012 09:47, Dan Burton <danburton.email at gmail.com> wrote:
> Convenience aside, doesn't the functor instance conceptually violate some
> sort of law?
>
> fmap (const 1) someSet
>
> The entire shape of the set changes.
>
> fmap (g . h) = fmap g . fmap h
>
> This law wouldn't hold given the following contrived ord instance
>
> data Foo = Foo { a, b :: Int }
> instance Ord Foo where
>   compare = compare `on` a
>
> Given functions
>
> h foo = foo { a = 1 }
> g foo = foo { a = b foo }
>
> Does this library address this? If so, how? If not, then you'd best note it
> in the docs.
>
> On Jun 15, 2012 6:42 PM, "George Giorgidze" <giorgidze at gmail.com> wrote:
>
> I would like to announce the first release of the set-monad library.
>
> On Hackage: http://hackage.haskell.org/package/set-monad
>
> 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
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell



More information about the Haskell-Cafe mailing list