monad library
Iavor Diatchki
diatchki@cse.ogi.edu
Thu, 31 Jul 2003 19:03:19 +0000
hello,
C.Reinke wrote:
> [sorry for not following this list closely,
> hope this interjection is appropriate..]
not at all, there is an alwfull lot of stuff going to haskell,
haskell-cafe, libraries, etc so i often miss things :-)
i think the issues bellow are addressed to some extent, but since i am
not 100% sure i understtod the post, please ask again if my answer is
not quite adequate.
the philosophy i took with the modified monad transformer library is
that it does not provide any instances for "standard classes" for
"standard types". by this i mean that there are _no_ instances like:
instance Monad (Either a) where ...
instance Monad ((->) a) where ...
etc.
every transformer is defined using newytpe, and is actually exported as
an abstract entity, so it is a completely new type that can only be
manipulated thru' functions/methods defined in the library. the library
defines a bunch of classes, and there are some instances for "standard
types", for example:
instance HasBaseMonad IO IO
that should not be a problem, as there are no other sensible instances
for this class.
one (somewhat debatable) point is the way the monads (not the monad
transformers) in the library are implemented: they are defined by
applying the corresponding transformer to the identity monad, and this
is done by simply using a type synonim. there was a short discussion if
we should use newtype instead, but no final decision was reached. i kind
of like the current way of doing things, but there was a concern about
the type errors one gets. i did a few experiments and the type errors
do not seem much worse, but if in the future that becomes a problem (or
most people want newtypes) we could easily change that.
is there demand to define instances for "standrd types", e.g. things like:
instance Monad (Either a) where ...
instance MonadError a (Either a) where ...
i am not sure that this is a good idea as the monads in the library do
the same job.
bye
iavor
> given this recent excitement about Control.Monad and transformers,
> this might be a good opportunity to point to a previous thread here:
>
> http://haskell.org/pipermail/libraries/2002-November/000714.html
>
> Have these problems been addressed yet, i.e.:
>
> - separating standard instances of common classes for common types
> from other stuff, unlike in the Monad hierarchy (which surprisingly
> adds instances of Functor/Monad for Either and ((->)a) just because
> those happen to be one way to implement Errors and Environments),
>
> As Haskell doesn't have parameterized modules, my preference
> would be to single out such instances (and only those which are
> unambiguously standard) in separate modules, which should make
> their contents obvious, and which could be imported by any
> other module needing these instances (without getting other
> stuff as well) *and wishing to export them*.
>
> - not stealing, e.g., the Monad instance for Either in
> Control.Monad.Error, for a not-quite standard definition.
>
> My preference would be use of newtype to define, e.g., an
> abstract type in terms of Either, and to have the instances
> defined for that abstract type. Haskell's module system gives
> no control over instances, but does give control over types.
>
> That is, there would be one module providing, e.g., reader monads
> *without* ursurping instances of "global" classes for "global" types
> for that purpose, and *another* module providing "standard" instances
> for "global" classes/types. The latter would be good for quick
> hacks, the former for modular development - different purposes,
> different modules.
>
> Otherwise, there are conflicts when one combines two packages trying
> to define their own versions of these instances as part of whatever
> else they are trying to do (such as the Monad modules right now).
>
> There seemed to be some support for these suggestions last time,
> and as there seems to be a maintainer around now, this might be
> a good time to fix these things?-)
>
> Cheers,
> Claus
>
> _______________________________________________
> Libraries mailing list
> Libraries@haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
--
==================================================
| Iavor S. Diatchki, Ph.D. student |
| Department of Computer Science and Engineering |
| School of OGI at OHSU |
| http://www.cse.ogi.edu/~diatchki |
==================================================