[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

Heinrich Apfelmus apfelmus at quantentunnel.de
Sat May 1 08:29:40 EDT 2010


Limestraël wrote:
> Heinrich, I saw you updated your operational package (you considered my
> remark about ProgramView, thank you)

Your feedback is much appreciated. :)

> I saw you added a liftProgram function, however it is not like the mapMonad
> function you were talking about.
> mapMonad was:
> mapMonad :: (Monad m1, Monad m2) =>
>                         (forall a . m1 a -> m2 a)
>                    -> ProgramT instr m1 a
>                    -> ProgramT instr m2 a
> 
> and you turned it into the less generic:
> liftProgram :: Monad m => Program instr a -> ProgramT instr m a
> 
> Did you change your mind?

Yes, I opted for the less generic function. My reasons were:

a)  mapMonad  has a precondition that is not caught by the type checker.
Namely, the first argument  f :: forall a. m1 a -> m2 a  must respect
the monad laws, i.e.

    f . return  = return
    f (m >>= k) = f m >>= f . k

If the  f  supplied by the user doesn't satisfy these equations, then it
will break invariants internal to the library, which is bad.

b) Excluding  mapMonad  does not go beyond the  mtl  in that the latter
does not provide functions

    mapStateT :: (Monad m1, Monad m2) =>
              => (forall a . m1 a -> m2 a)
              -> StateT s m1 a -> StateT s m2 a

either.

b') The TicTacToe example only uses  m = IO  and  m = Identity  and
liftProgram  is enough for that.

Basically, I'm unsure about the whole business of monad modularity. No
completely satisfactory solution has emerged yet, so I'm copying the
mtl  style for now.

c) Fortunately, users of the library don't lose functionality, only
convenience, because they can implement  mapMonad  themselves if they so
desire:

>>    mapMonad f = id' <=< lift . f . viewT
>>        where
>>        id' :: ProgramViewT instr m1 a -> ProgramT instr m2 a
>>        id' (Return a) = return a
>>        id' (i :>>= k) = singleton i >>= mapMonad f . k

(This is contrary to what I said earlier,  mapMonad  does *not* have to
be a library function.)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com



More information about the Haskell-Cafe mailing list