Bartek Banachewicz
Bartek Banachewicz

Reputation: 39370

Why doesn't this simple composition work?

I was recently in need of putting head in between two monadic operations. Here's the SSCCE:

module Main where

f :: IO [Int]
f = return [1..5]

g :: Int -> IO ()
g = print

main = do
    putStrLn "g <$> head <$> f"
    g <$> head <$> f

    putStrLn "g . head <$> f"
    g . head <$> f

    putStrLn "head <$> f >>= g"
    head <$> f >>= g

This program is well-formed and compiles without warnings. However, only one version out of 3 above works1. Why is that?

And specifically, what would be the best way to link f and g together with head in the middle? I ended up using the 3rd one (in the form of do notation), but I don't really like it, since it should be a trivial one-liner2.


1 Spoiler alert: the 3rd one is the only one that prints 1; the other two are silent, both under runhaskell and repl.

2 I do realize that those are all one-liners, but the order of operations feels really confusing in the only one that works.

Upvotes: 7

Views: 117

Answers (2)

willeM_ Van Onsem
willeM_ Van Onsem

Reputation: 476534

Probably the best way to write this is:

f >>= g . head

or in a more verbose form:

f >>= (g . head)

so we basically perform an fmap on the value for f (we thus take the head of the values wrapped in the IO monad), and then we pass then to g, like:

(head <$> f) >>= g

is semantically the same.

But now what happens if we use g <$> head <$> f? Let us first analyze the types:

f :: IO [Int]
g :: Int -> IO ()
(<$>) :: Functor m => (a -> b) -> m a -> m b

(I used m here to avoid confusion with the f function)

The canonical form of this is:

((<$>) ((<$>) g head) f)

The second (<$>) takes a g :: Int -> IO () and head :: [c] -> c as parameters, so that means that a ~ Int, b ~ IO (), and m ~ (->) [c]. So the result is:

 (<$>) g head :: (->) [c] (IO ())

or less verbose:

g <$> head :: [c] -> IO ()

The first (<$>) function thus takes as parameters g <$> head :: [c] -> IO (), and IO [Int], so that means that m ~ IO, a ~ [Int], c ~ Int, b ~ IO (), and hence we obtain the type:

(<$>) (g <$> head) f :: IO (IO ())

We thus do not perform any real action: we fmap the [Int] list to an IO action (that is wrapped in the IO). You could see it as return (print 1): you do not "evaluate" the print 1, but you return that wrapped in an IO.

You can of course "absorb" the outer IO here, and then use the inner IO, like:

evalIO :: IO (IO f) -> IO f
evalIO res = do
   f <- res
   f

or shorter:

evalIO :: IO (IO f) -> IO f
evalIO res = res >>= id

(this can be generalized to all sorts of Monads, but this is irrelevant here).

The evalIO is also known as join :: Monad m => m (m a) -> m a.

Upvotes: 4

Will Ness
Will Ness

Reputation: 71065

The first and second are exactly the same, because <$> is left-associative and head is a function, and <$> is . in the function monad. Then,

    g . head <$> f

    =  fmap (print . head) (return [1..5] :: IO [Int])
    =  do { x <- (return [1..5] :: IO [Int])
          ; return ( print (head x) ) }
    =  do { let x = [1..5] 
          ; return ( print (head x) ) } :: IO _whatever
    =       
            return ( print 1 )   :: IO (IO ())

We have one too many returns there. In fact,

    =  fmap (print . head) (return [1..5] :: IO [Int])
    =  return (print (head [1..5]))
    =  return (print 1)

is a shorter derivation.

The third one is

    (head <$> f) >>= g
  = (fmap head $ return [1..5]) >>= print
  = (return (head [1..5])) >>= print
  = (return 1) >>= print

which is obviously OK.

Upvotes: 4

Related Questions