monad transformer library (was: Re: list monad transformer)

hello, (appologies for the long post) Andrew J Bromage wrote:
G'day.
On Mon, May 19, 2003 at 05:15:30PM -0700, Iavor Diatchki wrote:
i think the main probelm with adding transformers to the library is that the amount of code grows quadratically in the number of transformers (as one has to specify how each one interacts with every other one).
I personally think that there is too much of that in the existing library. Consider, for example, the declarations at the end of Control.Monad.State:
instance (MonadState s m) => MonadState s (ReaderT r m) where get = lift get put = lift . put
instance (Monoid w, MonadState s m) => MonadState s (WriterT w m) where get = lift get put = lift . put
IMO, this is a misfeature. As a maintainer, working out what instances are correct is a hassle and, as you note, leads to quadratic code complexity in the worst case. As a user, I know what monad transformers I have stacked on top of each other and I know where to find the "lift" function.
actually i disagree with this quite strongly :-) ideally i want no lifts in my program. things like: lift $ lift $ lift $ raise "error" are, well, annoying. also if i have a state and an environment (Reader they call it in the library) i can decide to switch them around as they do not inetract with each other. now all the lifts need to be changed. and besides if one has 1 of each transformer the whole "lift" thing is pointless as there is no ambiguity as to what you mean (i.e. put clearly refers to the state transformer wherevr it is). when there is more than one copy of a transformer things are different. then some sort of addressing is necessary, which is what motivated adding the "indexes" to my library. they work quite well, but i still think there must be a better way to achieve the same effect... as for maintenance, for a number of methods (i.e. ones where computions do not appear as arguments) there are standard ways of lifting. for example, what i've been using lately (don't remember if it is on my website) is: get' = lift get and then all instances for get use get' unfortunatelly i can't quite capture this commonality with a single instance. perhaps (as bellow) overlapping instances (in some form) could help.
The one exception is liftIO, which is very useful because if IO is anywhere in your stack of monad transformers, it must be at the bottom. I think there's also an argument for liftST.
actually the library can be generalized there. in my library i have a class: class (Monad m, Monad n) => HasBase m n | m -> n where inBase :: n a -> m a for each monad transformer there is an instance: instance HasBase m n => HasBase (t m) n inBase = lift . inBase for every base monad (i.e. one not made out of transformers) there is an instance: instance HasBase m m where inBase = id we can cut down the number of instances if overlapping intsnaces are used, but it is not quite clear (at least to me) how they interact with functional dependencies. using this calss you don't need liftIO and liftST, and liftId, and liftFudgets, etc... bye iavor

G'day all. On Tue, May 20, 2003 at 10:10:24AM -0700, Iavor Diatchki wrote:
actually i disagree with this quite strongly :-) ideally i want no lifts in my program. things like: lift $ lift $ lift $ raise "error" are, well, annoying.
Of course you want no lifts in your program. What you should have written instead is something like this: myLiftToError = lift . lift . lift myRaise = myLiftToError . raise I agree that client code which uses your particular stack of monad transformers shouldn't have to know what order the transformers are stacked in, but even more so, they shouldn't have to even know what the transformers _are_. If it's that complex, it should be abstract.
now all the lifts need to be changed.
If the lift operations were abstract, you would only need to change at most N of them, where N is the number of stacked transformers, and even then it would only be in one place.
and besides if one has 1 of each transformer the whole "lift" thing is pointless as there is no ambiguity as to what you mean (i.e. put clearly refers to the state transformer wherevr it is).
Not if there's an RWS transformer somewhere else on the stack. I understood that the main reason for the typeclasses was that there may be more than one reasonable implementation of a given interface.
when there is more than one copy of a transformer things are different. then some sort of addressing is necessary, which is what motivated adding the "indexes" to my library. they work quite well, but i still think there must be a better way to achieve the same effect...
I'm curious how these indexes work. There are many situations where I need a little extra state/nondeterminism/whatever for a small part of my code, and for that, stacking on an extra transformer can do the trick nicely. Does this upset the scheme that you use for indexing?
unfortunatelly i can't quite capture this commonality with a single instance. perhaps (as bellow) overlapping instances (in some form) could help.
Overlapping instances may help reduce the quadratic complexity, and if it could be done right (i.e. if the Haskell implementation can be trusted to pick the correct instance), I might be happy with that as a compromise. That way I can just do this: instance (MonadNondet m, MonadTrans t) => MonadNondet (t m) where msolutions = lift . msolutions mcommit = lift . mcommit and trust that the highest MonadNondet instance is picked.
actually the library can be generalized there. in my library i have a class:
class (Monad m, Monad n) => HasBase m n | m -> n where inBase :: n a -> m a
That's an excellent idea. As a random thought, there may be an argument for incorporating stToIO and/or ioToST in here too. Cheers, Andrew Bromage

A few comments on your recent commit of a proposed new monad structure (fptools/libraries/base/Control.Monad.X.*): I never liked the old "diagonal" structure, but a lot of people use these modules, and they'll notice the change of interface. In the old scheme, Control.Monad.Fix was portable, and now it isn't. (This will ripple through to my favourite module, Control.Arrow.) I'd prefer that the MonadFix instances for the new monad transformers be defined in the transformer modules, so they could import a portable Fix as before. You defined the classes in Trans, the types in Types and the instances in the *T modules, which makes them orphan instances, I believe (cf GHC User's Guide 4.9.8). Why not just get rid of Types and move the type definitions into the relevant *T modules? Use of type synonyms, like type Reader r = R.ReaderT r Identity is more economical, but will lead to more complex error messages. Resumptions may be generalized to newtype ResumeT f m a = Re { unRe :: m (Res f m a) } data Res f m a = Value a | Delay (f (ResumeT f m a)) where f is a functor.

hello, comments cool! i didn't think anyone would look at the library :-) Ross Paterson wrote: > A few comments on your recent commit of a proposed new monad structure > (fptools/libraries/base/Control.Monad.X.*): > > I never liked the old "diagonal" structure, but a lot of people use > these modules, and they'll notice the change of interface. well, in the old library there didn't seem to be a particular structure (perhaps this is what you mean by diagonal). for example: * the instance that StateT is a writer (if underlying monad is a writer) is in State.hs * the instance that ReaderT is a writer (if underlying monad is a writer) is in Writer.hs i tried to make the new library mostly compatable with the old one, but i think it is good to fix up things before the library has completeley solidified. > In the old scheme, Control.Monad.Fix was portable, and now it isn't. > (This will ripple through to my favourite module, Control.Arrow.) > I'd prefer that the MonadFix instances for the new monad transformers > be defined in the transformer modules, so they could import a portable > Fix as before. i have mixed feelings about MonadFix. on the one hand i quite agree with you that the instances kind of belong with the transformers. on the other i've had discussions with some collegues of mine, that think that since using monadic recursion is not that common, you should only get those instances when you use it, i.e. import Fix. this motivated separating them. but the potability issue you bring up is quite relevant (although one gets the portability at the cost of having very few instances). overall i agree with ross that they should probably be moved back to the transformers. any other opinions? > You defined the classes in Trans, the types in Types and the instances > in the *T modules, which makes them orphan instances, I believe (cf GHC > User's Guide 4.9.8). Why not just get rid of Types and move the type > definitions into the relevant *T modules? Types (and Utils) were supposed to be "private" modules. Types is used to access the underlying representations of the transformers, while the *T files still export the types abstractly. moving the mfix instance to the transformers will remove the need for Types, so perhaps that should be done. > Use of type synonyms, like > > type Reader r = R.ReaderT r Identity > > is more economical, but will lead to more complex error messages. this is a good point and i will change that, unless anyone objects? > Resumptions may be generalized to > > newtype ResumeT f m a = Re { unRe :: m (Res f m a) } > data Res f m a = Value a | Delay (f (ResumeT f m a)) > > where f is a functor. interesting, i hadn't seen that. this will also make the Resume monad a little more interesting (it used to be kind of like the natural numbers). i'll add that. is there a paper where they discuss that? i also haven't really proved the monad laws, hopefully they still work. thanks for the comments bye iavor

hello, Iavor Diatchki wrote:
Use of type synonyms, like
type Reader r = R.ReaderT r Identity
is more economical, but will lead to more complex error messages.
this is a good point and i will change that, unless anyone objects?
i am having 2nd thoughts about that. using newtypes will require an alwful lot of "fake" instances making the libarary about 2 times bigger. i tried to make a few errors and the error messages did not seem much worse with the "type" -- what happens is that "missing instances" are reported for the Identity monad, rather than the "Reader" monad. this seems reasonable as methods usually just search for the first layer that implements a given "feature", until they hit the "base case". using newtype changes the base case from Identity to Reader, which in some case i think is perhaps more confusing. any thoughts? bye iavor

On Wed, Jun 04, 2003 at 11:38:16AM -0700, Iavor Diatchki wrote:
well, in the old library there didn't seem to be a particular structure (perhaps this is what you mean by diagonal). for example: * the instance that StateT is a writer (if underlying monad is a writer) is in State.hs * the instance that ReaderT is a writer (if underlying monad is a writer) is in Writer.hs
The structure was that the monads were arranged in a sequence: Reader, Writer, State, RWS, Cont, Error, List Module n would import modules 1..n-1, introduce Mn and corresponding classes, make Mn an instance of all earlier classes and make previous monads instances of the new classes. If you picture a matrix of types vs classes, it was walking down the diagonal. As for where to place instances, SimonM has the following in the (much-overlooked) library document: A module corresponding to a class (e.g. Bits) contains the class definition, perhaps some auxiliary functions, and all sensible instances for Prelude types, but nothing more. Other modules containing types for which an instance for the class in question makes sense contain the code for the instance itself. which makes sense to me, though maybe I'd put several classes in one module.
Resumptions may be generalized to
newtype ResumeT f m a = Re { unRe :: m (Res f m a) } data Res f m a = Value a | Delay (f (ResumeT f m a))
where f is a functor.
interesting, i hadn't seen that. this will also make the Resume monad a little more interesting (it used to be kind of like the natural numbers). i'll add that. is there a paper where they discuss that? i also haven't really proved the monad laws, hopefully they still work.
One of Moggi's later ones, I think.

Dnia śro 4. czerwca 2003 20:38, Iavor Diatchki napisał:
well, in the old library there didn't seem to be a particular structure (perhaps this is what you mean by diagonal). for example: * the instance that StateT is a writer (if underlying monad is a writer) is in State.hs * the instance that ReaderT is a writer (if underlying monad is a writer) is in Writer.hs
It can't be done consistently without recursive modules and without orphan instances. So there is an arbitrary ordering among modules (roughly from less to more sophisticated), each module uses preceding modules, and defines instances applying to itself and used modules in both directions. If some pair of abilities don't mix in either direction, it doesn't need to be ordered. It's transparent for the user, matters only for development. -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/
participants (4)
-
Andrew J Bromage
-
Iavor Diatchki
-
Marcin 'Qrczak' Kowalczyk
-
Ross Paterson