[Haskell-cafe] Problems with nested Monads

Sjoerd Visscher sjoerd at w3future.com
Wed Jul 15 08:34:24 EDT 2009


Actually, you can make a joinInner for the State monad. However, it  
does not allow the inner function (h) to change the state, because how  
state is threaded through a monad N is different for each N.

i :: (Monad n) => (a -> State s b) -> (b -> n c) -> (c -> State s d) - 
 > (a -> State s (n d))
i f g h = joinInnerState . liftM (liftM h . g) . f

joinInnerState :: Monad n => State s (n (State s a)) -> State s (n a)
joinInnerState (State g) = State $ joinInnerAsReader . g
   where
     joinInnerAsReader (n, s) = (liftM (fst . ($ s) . runState) n, s)

joinInner is the only one of the 3 that works, because the outer M  
gives you an initial state to work with.

Sjoerd

On Jul 10, 2009, at 11:25 PM, Job Vranish wrote:

> Yeah, I think the problem with my case is that while M is a specific  
> monad (essentially StateT), N can be an arbitrary monad, which I  
> think destroys my changes of making a valid joinInner/joinOuter/ 
> distribute.
> Maybe someday Haskell will infer valid joinInner/joinOuter for  
> simple cases :D
> Thanks for you help. I'll definitely have to see if I can find that  
> paper.
>
> - Job Vranish
>
> On Fri, Jul 10, 2009 at 3:09 PM, Edward Kmett <ekmett at gmail.com>  
> wrote:
> The problem you have is that monad composition isn't defined in  
> general. You would need some form of distributive law either for  
> your monads in general, or for your particular monads wrapped around  
> this particular kind of value.
>
> What I would look for is a function of the form of one of:
>
> distribute :: N (M a) -> M (N a)
> joinInner :: M (N (M a)) -> M (N a)
> joinOuter :: N (M (N a)) -> M (N a)
>
> that holds for your partiular monads M and N.
>
> IIRC Mark P. Jones wrote a paper or a lib back around '93 that used  
> these forms of distributive laws to derive monads from the  
> composition of a monad and a pointed endofunctor.
>
> -Edward Kmett
>
> On Fri, Jul 10, 2009 at 11:34 AM, Job Vranish <jvranish at gmail.com>  
> wrote:
> I'm trying to make a function that uses another monadic function  
> inside a preexisting monad, and I'm having trouble.
> Basically my problem boils down to this. I have three monadic  
> functions with the following types:
> f :: A -> M B
> g :: B -> N C
> h :: C -> M D
> (M and N are in the monad class)
> I want a function i where
> i :: A -> M (N D)
>
> the best I can come up with is:
> i :: A -> M (N (M D))
> i a = liftM (liftM h) =<< (return . g) (f a)
>
> I'm starting to feel pretty sure that what I'm going for is  
> impossible. Is this the case?
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

--
Sjoerd Visscher
sjoerd at w3future.com



-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090715/398ee78b/attachment.html


More information about the Haskell-Cafe mailing list