user3140285
user3140285

Reputation:

Taking monadic functions out of a monad

Haskell has the function join, which "runs" a monadic action which is inside a monad:

join :: Monad m => m (m a) -> m a
join m = m >>= \f -> f

We can write a similar function for monadic functions with one argument:

join1 :: Monad m => m (a -> m b) -> (a -> m b)
join1 m arg1 = m >>= \f -> f arg1

And for two arguments:

join2 :: Monad m => m (a -> b -> m c) -> (a -> b -> m c)
join2 m arg1 arg2 = m >>= \f -> f arg1 arg2

Is it possible to write a general function joinN, that can handle monadic functions with N arguments?

Upvotes: 2

Views: 153

Answers (3)

TheCriticalImperitive
TheCriticalImperitive

Reputation: 1457

The short answer is no. The slightly longer answer is you could probably define an infix operator.

Take a look at the implementation for liftM: http://hackage.haskell.org/package/base-4.7.0.2/docs/src/Control-Monad.html#liftM

It defines up to liftM5. This is because it's not possible to define liftMN, just like your joinN isn't possible.

But we can take a lesson from Appicative <$> and <*> and define our own infix operator:

> let infixr 1 <~> ; x <~> f = fmap ($ x) f
> :t (<~>)
(<~>) :: Functor f => a -> f (a -> b) -> f b
> let foo x y = Just (x + y)
> let foobar = Just foo
> join $ 1 <~> 2 <~> foobar
Just 3

This is quite reminiscent of a common applicative pattern:

f <$> a1 <*> a2 .. <*> an
join $ a1 <~> a2 .. <~> an <~> f

Upvotes: 3

Tikhon Jelvis
Tikhon Jelvis

Reputation: 68152

A single function for every possible N? Not really. Generalizing over functions with different numbers of arguments like this is difficult in Haskell, in part because "number of arguments" is not always well-defined. The following are all valid specializations of id's type:

id :: a -> a
id :: (a -> a) -> a -> a
id :: (a -> a -> a) -> a -> a -> a
...

We'd need some way to get N at the type level, and then do a different thing depending on what N is.

Existing "variadic" functions like printf do this with typeclasses. They establish what N is by induction on ->: they have a "base case" instance for a non-function type like String and a recursive instance for functions:

instance PrintfType String ...
instance (PrintfArg a, PrintfType r) => PrintfType (a -> r) ...

We can (after a lot of thinking :P) use the same approach here, with one caveat: our base case is a bit ugly. We want to start with the normal join, which produces a result of type m a; the problem is that to support any m a, we have to overlap with normal functions. This means that we need to enable a few scary extensions and that we might confuse the type inference system when we actually use our joinN. But, with the right type signatures in place, I believe it should work correctly.

First off, here's the helper class:

class Monad m => JoinN m ma where
  joinN :: m ma -> ma

ma will take the relevant function type like a -> m b, a -> b -> m c and so on. I couldn't figure out how to leave m out of the class definition, so right off the bat we need to enable MultiParamTypeClasses.

Next, our base case, which is just normal join:

instance Monad m => JoinN m (m a) where
  joinN = join

Finally, we have our recursive case. What we need to do is "peel off" an argument and then implement the function in terms of a smaller joinN. We do this with ap, which is <*> specialized to monads:

instance (Monad m, JoinN m ma) => JoinN m (b -> ma) where
  joinN m arg = joinN (m `ap` return arg)

We can read the => in the instance as implication: if we know how to joinN an ma, we also know how to do a b -> ma.

This instance is slightly weird, so it requires FlexibleInstances to work. More troublingly, because our base case (m (m a)) is made up entirely of variables, it actually overlaps with a bunch of other reasonable types. To actually make this work we have to enable OverlappingInstances and IncoherentInstances, which are relatively tricky and bug-prone.

After a bit of cursory testing, it seems to work:

λ> let foo' = do getLine >>= \ x -> return $ \ a b c d -> putStrLn $ a ++ x ++ b ++ x ++ c ++ x ++ d
λ> let join4 m a b c d = m >>= \ f -> f a b c d
λ> join4 foo' "a" "b" "c" "d"

a  b  c  d
λ> joinN foo' "a" "b" "c" "d"

a  b  c  d

Upvotes: 1

J. Abrahamson
J. Abrahamson

Reputation: 74354

You can do something like this with a fair amount of ugliness if you really desire.

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}

import Control.Monad (join, liftM)

class Joinable m z | z -> m where
  joins :: m z -> z

instance Monad m => Joinable m (m a) where
  joins = join

instance (Monad m, Joinable m z) => Joinable m (r -> z) where
  joins m r = joins (liftM ($ r) m)

But, as you can see this relies on some shaky typeclass magic (in particular, the unenviable UndecidableInstances). It is quite possibly better—if ugly looking—to write all of the instances join1...join10 and export them directly. This is the pattern established in the base library as well.

Notably, inference won't work too well under this regime. For instance

λ> joins (return (\a b -> return (a + b))) 1 2
Overlapping instances for Joinable ((->) t0) (t0 -> t0 -> IO t0)
  arising from a use of ‘joins’
Matching instances:
  instance Monad m => Joinable m (m a)
    -- Defined at /Users/tel/tmp/ASD.hs:11:10
  instance (Monad m, Joinable m z) => Joinable m (r -> z)
    -- Defined at /Users/tel/tmp/ASD.hs:14:10

but if we give an explicit type to our argument

λ> let {q :: IO (Int -> Int -> IO Int); q = return (\a b -> return (a + b))}

then it can still work as we hope

λ> joins q 1 2
3

This arises because with typeclasses alone it becomes quite difficult to indicate whether you want to operate on the monad m in the final return type of the function chain or the monad (->) r that is the function chain itself.

Upvotes: 5

Related Questions