Why doesn't this simple composition work? - haskell

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.

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.

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.

Related

Point free version for readMaybe

I want to write a function to read an Int without do notation. It works (see below), but I was wondering if it the bit around readMaybe can be written in point free form (or cleaned up a bit in some other way)?
main :: IO ()
main = getLine >>= (\x -> return $ (readMaybe x :: Maybe Int)) >>= print
Step 1: Replace the lambda with its pointfree equivalent:
main :: IO ()
main = getLine >>= return . (readMaybe :: String -> Maybe Int) >>= print
Step 2: Replace m >>= return . f with f <$> m:
main :: IO ()
main = (readMaybe :: String -> Maybe Int) <$> getLine >>= print
Step 3: Replace f <$> m >>= g with m >>= g . f:
main :: IO ()
main = getLine >>= print . (readMaybe :: String -> Maybe Int)
Step 4: Use a type application instead of writing out a long, awkward type:
{-# LANGUAGE TypeApplications #-}
main :: IO ()
main = getLine >>= print . readMaybe #Int
As an alternative to using <$> in steps 2 and 3, you can accomplish the same with just the monad laws, like this (picking up after step 1):
Replace m >>= f >>= g with m >>= \x -> f x >>= g (associativity):
main :: IO ()
main = getLine >>= \x -> (return . (readMaybe :: String -> Maybe Int)) x >>= print
Simplify the . away:
main :: IO ()
main = getLine >>= \x -> return ((readMaybe :: String -> Maybe Int) x) >>= print
Replace return x >>= f with f x (left identity):
main :: IO ()
main = getLine >>= \x -> print ((readMaybe :: String -> Maybe Int) x)
Now just replace that new lambda with its pointfree equivalent, and you end up in the exact same place as step 3.

Getting Access to 'a' in StateT

I'm trying to write a function with StateT only to learn more about it.
In f, I'd like to access to the Int in the last type argument of StateT [Int] IO Int:
f :: StateT [Int] IO Int
f = state $ \xs -> update (error "I want a") xs
update :: Int -> [Int] -> (Int, [Int])
update x [] = (x, [])
update x (y:ys) = (x+y, ys)
Here's how I'd like to call it:
let x = return 55 :: StateT [Int] IO Int
Referencing runStateT:
*Main> :t runStateT
runStateT :: StateT s m a -> s -> m (a, s)
I'd expect to run it:
runStateT (f x) [1,2,3]
to get the following from GHCI, i.e. the IO (Int, [Int]) gets printed:
(56, [2,3])
since the inner a, i.e. 55, + 1, i.e. from [1,2,3], returns (56, [2,3]).
How can I write the above function, getting access to the a?
Ok, here's what say you want:
>>> let x = return 55 :: StateT [Int] IO Int
>>> runStateT (f x) [1,2,3]
(56, [2,3])
So let's work backwards from that.
From the use of f, we can infer its type -
f :: StateT [Int] IO Int -> StateT [Int] IO Int
Note the difference from your given type for f in the question - namely f is a function between values of type StateT [Int] IO Int, not a value of that type.
To define f, we need (>>=) :: Monad m => m a -> (a -> m b) -> m b. This will allow us to take our input of type StateT [Int] IO Int and run some computation on the Int the input computes.
f x = x >>= \i -> state (splitAt 1) >>= \[j] -> return (i + j)
or, using do-notation:
f x = do
i <- x
[j] <- state (splitAt 1)
return (i + j)
Which gives us exactly the result we want.
While this works, it's highly non-idiomatic. Rather than passing monadic values in as inputs to functions and binding them inside the function, it's far more common to define functions that take regular values and return monadic ones, using the bind operator (>>=) outside.
So it'd be far more normal to define
shiftAdd :: Int -> StateT [Int] IO Int
shiftAdd i = do
[j] <- state (splitAt 1)
return (i + j)
So now we can run not only
>>> runStateT (shiftAdd 55) [1,2,3]
(56,[2,3])
but also
>>> runStateT (shiftAdd 55 >>= shiftAdd >>= shiftAdd)
(61,[])
It's still not as idiomatic as it could be as:
I made it unnecessarily partial by using splitAt (it'll throw an exception if the state list is empty)
it's unnecessarily specific (doesn't use IO at all, but we can't use it with other base monads)
Fixing that up gives us:
shiftAdd' :: (Monad m, Num a) => a -> StateT [a] m a
shiftAdd' i = state $ \js -> case js of
[] -> (i, [])
j : js -> (i + j, js)
Which works just fine:
>>> runStateT (return 55 >>= shiftAdd') [1,2,3]
(56,[2,3])
>>> runStateT (return 55 >>= shiftAdd' >>= shiftAdd' >>= shiftAdd') [1,2,3]
(61,[])
>>> runStateT (return 55 >>= shiftAdd' >>= shiftAdd' >>= shiftAdd') []
(55,[])

Using a pure function in a Haskell monad / left-lifting?

Consider the following function:
foo =
[1,2,3] >>=
return . (*2) . (+1)
For better readability and logic, I would like to move my pure functions (*2) and (+1) to the left of the return. I could achieve this like this:
infixr 9 <.
(<.) :: (a -> b) -> (b -> c) -> (a -> c)
(<.) f g = g . f
bar =
[1,2,3] >>=
(+1) <.
(*2) <.
return
However, I don't like the right-associativity of (<.).
Let's introduce a function leftLift:
leftLift :: Monad m => (a -> b) -> a -> m b
leftLift f = return . f
baz =
[1,2,3] >>=
leftLift (+1) >>=
leftLift (*2) >>=
return
I quite like this. Another possibility would be to define a variant of bind:
infixl 1 >>$
(>>$) :: Monad m => m a -> (a -> b) -> m b
(>>$) m f = m >>= return . f
qux =
[1,2,3] >>$
(+1) >>$
(*2) >>=
return
I am not sure whether that is a good idea, since it would not allow me to use do notation should I want that. leftLift I can use with do:
bazDo = do
x <- [1,2,3]
y <- leftLift (+1) x
z <- leftLift (*2) y
return z
I didn't find a function on Hoogle with the signature of leftLift. Does such a function exist, and, if, what is it called? If not, what should I call it? And what would be the most idiomatic way of doing what I am trying to do?
Edit: Here's a version inspired by #dunlop's answer below:
infixl 4 <&>
(<&>) :: Functor f => f a -> (a -> b) -> f b
(<&>) = flip fmap
blah =
[1,2,3] <&>
(+1) <&>
(*2) >>=
return
I should also add that I was after a bind-variant, because I wanted to write my code in point-free style. For do-notation, I guess I don't need to "pretend" that I'm doing anything monadic, so I can use lets.
Every Monad is a Functor (and an Applicative too). Your (>>$) is (flipped) fmap.
GHCi> :t fmap
fmap :: Functor f => (a -> b) -> f a -> f b
GHCi> :t (<$>) -- Infix synonym for 'fmap'
(<$>) -- Infix synonym for 'fmap'
:: Functor f => (a -> b) -> f a -> f b
GHCi> fmap ((*2) . (+1)) [1,2,3]
[4,6,8]
GHCi> (*2) . (+1) <$> ([1,2,3] >>= \x -> [1..x])
[4,4,6,4,6,8]
(By the way, a common name for flipped fmap is (<&>). That is, for instance, what lens calls it.)
If you are using do-notation, there is little reason to use any variant of fmap explicitly for this kind of transformation. Just switch your <- monadic bindings for let-bindings:
bazDo = do
x <- [1,2,3]
let y = (+1) x
z = (*2) y
return z
bazDo = do
x <- [1,2,3]
let y = (+1) x
return ((*2) z)
For better readability...
That's going to be subjective as people disagree on what constitutes readable.
That being said, I agree that sometimes it's easier to understand data transformations when they are written left to right. I think your >>$ is overkill, though. The & operator in Data.Function does the job:
import Data.Function
foo = [1,2,3] & fmap (+1) & fmap (*2)
I like that this says exactly what to start with and exactly what to do at each step from left to right. And unlike >>$, you aren't forced to remain in the monad:
bar = [1,2,3] & fmap (+1) & fmap (*2) & sum & negate
Or you can just assemble your transformation beforehand and map it over your monad:
import Control.Category
f = (+1) >>> (*2)
quuz = fmap f [1,2,3]

Lazy list wrapped in IO

Suppose the code
f :: IO [Int]
f = f >>= return . (0 :)
g :: IO [Int]
g = f >>= return . take 3
When I run g in ghci, it cause stackoverflow. But I was thinking maybe it could be evaluated lazily and produce [0, 0, 0] wrapped in IO. I suspect IO is to blame here, but I really have no idea. Obviously the following works:
f' :: [Int]
f' = 0 : f'
g' :: [Int]
g' = take 3 f'
Edit: In fact I am not interested in having such a simple function f, original code looked more along the lines:
h :: a -> IO [Either b c]
h a = do
(r, a') <- h' a
case r of
x#(Left _) -> h a' >>= return . (x :)
y#(Right _) -> return [y]
h' :: IO (Either b c, a)
-- something non trivial
main :: IO ()
main = mapM_ print . take 3 =<< h a
h does some IO computations and stores invalid (Left) responses in a list until a valid response (Right) is produced. The attempt is to construct the list lazily even though we are in the IO monad. So that someone reading the result of h can start consuming the list even before it is complete (because it may even be infinite). And if the one reading the results cares only for the first 3 entries no matter what, the rest of the list does not even have to be constructed. And I am getting the feeling that this will not be possible :/.
Yes, IO is to blame here. >>= for IO is strict in the "state of the world". If you write m >>= h, you'll get an action that first performs the action m, then applies h to the result, and finally performs the action h yields. It doesn't matter that your f action doesn't "do anything"; it has to be performed anyway. Thus you end up in an infinite loop starting the f action over and over.
Thankfully, there is a way around this, because IO is an instance of MonadFix. You can "magically" access the result of an IO action from within that action. Critically, that access must be sufficiently lazy, or you'll throw yourself into an infinite loop.
import Control.Monad.Fix
import Data.Functor ((<$>))
f :: IO [Int]
f = mfix (\xs -> return (0 : xs))
-- This `g` is just like yours, but prettier IMO
g :: IO [Int]
g = take 3 <$> f
There's even a bit of syntactic sugar in GHC for this letting you use do notation with the rec keyword or mdo notation.
{-# LANGUAGE RecursiveDo #-}
f' :: IO [Int]
f' = do
rec res <- (0:) <$> (return res :: IO [Int])
return res
f'' :: IO [Int]
f'' = mdo
res <- f'
return (0 : res)
For more interesting examples of ways to use MonadFix, see the Haskell Wiki.
It sounds like you want a monad that mixes the capabilities of lists and IO. Luckily, that's just what ListT is for. Here's your example in that form, with an h' that computes the Collatz sequence and asks the user how they feel about each element in the sequence (I couldn't really think of anything convincing that fit the shape of your outline).
import Control.Monad.IO.Class
import qualified ListT as L
h :: Int -> L.ListT IO (Either String ())
h a = do
(r, a') <- liftIO (h' a)
case r of
x#(Left _) -> L.cons x (h a')
y#(Right _) -> return y
h' :: Int -> IO (Either String (), Int)
h' 1 = return (Right (), 1)
h' n = do
putStrLn $ "Say something about " ++ show n
s <- getLine
return (Left s, if even n then n `div` 2 else 3*n + 1)
main = readLn >>= L.traverse_ print . L.take 3 . h
Here's how it looks in ghci:
> main
2
Say something about 2
small
Left "small"
Right ()
> main
3
Say something about 3
prime
Left "prime"
Say something about 10
not prime
Left "not prime"
Say something about 5
fiver
Left "fiver"
I suppose modern approaches would use pipes or conduits or iteratees or something, but I don't know enough about them to talk about the tradeoffs compared to ListT.
I'm not sure if this is an appropriate usage, but unsafeInterleaveIO would get you the behavior you're asking for, by deferring the IO actions of f until the value inside of f is asked for:
module Tmp where
import System.IO.Unsafe (unsafeInterleaveIO)
f :: IO [Int]
f = unsafeInterleaveIO f >>= return . (0 :)
g :: IO [Int]
g = f >>= return . take 3
*Tmp> g
[0,0,0]

No cooperation between readFile & IO monad when programming pointlessly

Why do countInFile1 & countInFile3 have compiler errors, when countInFile0 & countInFile2 do not. All four are the same thing.
count :: String -> String -> Int
count w = length . filter (==w) . words
present :: String -> String -> IO String
present w = return . show . count w
-- VALID: pointed readFile, regular present
countInFile0 :: String -> FilePath -> IO ()
countInFile0 w f = putStrLn =<< present w =<< readFile f
-- INVALID: pointless readFile, regular present
countInFile1 :: String -> FilePath -> IO ()
countInFile1 w = putStrLn =<< present w =<< readFile
-- VALID: pointed readFile, inline present
countInFile2 :: String -> FilePath -> IO ()
countInFile2 w f = putStrLn =<< (return . show . count w) =<< readFile f
-- INVALID: pointless readFile, inline present
countInFile3 :: String -> FilePath -> IO ()
countInFile3 w = putStrLn =<< (return . show . count w) =<< readFile
main = do
countInFile0 "bulldogs" "bulldogs.txt"
countInFile1 "bulldogs" "bulldogs.txt"
countInFile2 "bulldogs" "bulldogs.txt"
countInFile3 "bulldogs" "bulldogs.txt"
Also why does countInFile3 have this additional error that countInFile1 does not:
example_one.hs:21:27:
No instance for (Monad ((->) FilePath))
arising from a use of `=<<'
Possible fix:
add an instance declaration for (Monad ((->) FilePath))
In the expression:
putStrLn =<< (return . show . count w) =<< readFile
In an equation for `countInFile3':
countInFile3 w
= putStrLn =<< (return . show . count w) =<< readFile
With both countInFile1 and countInFile3, since you are composing three things of the form a -> IO b, you are thinking of the so-called Kleisli composition, the <=< from Control.Monad. Try
countInFile1 w = putStrLn <=< present w <=< readFile
countInFile3 w = putStrLn <=< return . show . count w <=< readFile
Or you can write countInFile3 w file = ... =<< readFile file, as you do elsewhere. readFile file (with the parameter) is an IO String, so it can be passed along by >>= or =<< to any String -> IO b. But that isn't as swank as what you intended. readFile just by itself is a FilePath -> IO String so it can be >=>'d with any String -> IO b to make a FilePath -> IO b and so on with a b -> IO c, etc. in your case ending with a FilePath -> IO ()
The second error comes from ghc trying to read =<< readFile, to do so it needs readFile to be m b for some monad m, so it settles on Monad ((->) FilePath) (this would actually make sense with Control.Monad.Instances, but would just delay getting the first error.)
If you add the file parameter to these it would be thus,
countInFile1 w file = (putStrLn <=< present w <=< readFile) file
and it is possible that you are parsing countInFile2 and countInFile0 this way, while construing =<< as <=< when actually they are like so:
countInFile0 w file = putStrLn =<< present w =<< (readFile file)
The difference is the same as that between
f n = (even . (+1) . (*3)) n
or equivalently
f = even . (+1) . (3*)
and on the other hand
f n = even $ (+1) $ 3 * n -- cp. your 0 and 2
If you delete the n from both sides here
f = even $ (+1) $ (3*) -- cp. your 1 and 3
you will get a type error akin to the ones you saw:
No instance for (Integral (a0 -> a0)) arising from a use of `even'
Where you use $ you need the parameter n -- as where you use >>= or =<< you need the parameter file. With ., as with <=<, you don't.
Function application has higher precedence than infix =<< operator.
So f =<< g a is equivalent to f =<< (g a) and not (f =<< g) a.

Resources