Heinrich, I saw you updated your operational package (you considered my remark about ProgramView, thank you)

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?

2010/4/19 Heinrich Apfelmus <apfelmus@quantentunnel.de>
Heinrich Apfelmus wrote:
> Limestraël wrote:
>> Okay, I start to understand better...
>>
>> Just, Heinrich, how would implement the mapMonad function in terms of the
>> operational package?
>> You just shown the signature.
>
> Ah, that has to be implemented by the library, the user cannot implement
> this. Internally, the code would be as Bertram suggests:
>
>     mapMonad :: (Monad m1, Monad m2)
>              => (forall a . m1 a -> m2 a)
>              -> ProgramT instr m1 a -> ProgramT instr m2 a
>     mapMonad f (Lift m1)  = Lift (f m1)
>     mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
>     mapMonad f (Instr i)  = Instr i

Silly me! This can be implement by the user:

   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

and it would be a shame for the operational approach if that were not
possible. :)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe