How works this `do` example?

Hello, Dear List! Consider, I have: request1 :: A -> Connection -> IO () request2 :: A -> Connection -> IO A How does it work - resp <- getConnection >>= do request1 myA request2 anotherA ?! It is compiled but seems that does not execute `request1`... `request1 myA` gets `Connection` value, good. But it does not return `IO Connection`! It returns `IO ()`. But how does `request2 anotherA` get `Connection` value too? Because this is not compiled sure: resp <- getConnection >>= request1 myA >>= request2 anotherA I tried this: module Main where f1 :: Int -> IO () f1 i = do print "f1!" print i return () f2 :: Int -> IO Int f2 i = do print "f2!" print i return i f0 :: IO Int f0 = pure 10 main :: IO () main = f0 >>= do f1 f2 >> print "end" and I get output: "f2!" 10 "end" which means that `f1` is not executing in `do..`-block, but how does `f2` get 10 as input?! == Cheers, Paul

On Thu, Jul 13, 2017 at 11:29:56AM +0300, Baa wrote:
main :: IO () main = f0 >>= do f1 f2 >> print "end"
and I get output:
"f2!" 10 "end"
Hello Paul, your `main` desugars to main = f0 >>= (f1 >> f2) >> print "end" Now, the quizzical part is λ> :t (f1 >> f2) (f1 >> f2) :: Int -> IO Int Why does this even type checks? Because: λ> :i (->) [..] instance Monad ((->) r) -- Defined in ‘GHC.Base’ [..] ((->) r) is an instance of Monad! The instance is: instance Monad ((->) r) where f >>= k = \r -> k (f r) r you already know that `m >> k` is defined as `m >>= \_ -> k`, so f >> k = \r -> (\_ -> k) (f r) r = \r -> k r Is it clear enough?

I suspected that it was in Read monad, but I don't see where is it this
"Read" monad here :) Francesco, thank you very much!!
Absolutely clear :)
В Thu, 13 Jul 2017 11:06:13 +0200
Francesco Ariis
On Thu, Jul 13, 2017 at 11:29:56AM +0300, Baa wrote:
main :: IO () main = f0 >>= do f1 f2 >> print "end"
and I get output:
"f2!" 10 "end"
Hello Paul, your `main` desugars to
main = f0 >>= (f1 >> f2) >> print "end"
Now, the quizzical part is
λ> :t (f1 >> f2) (f1 >> f2) :: Int -> IO Int
Why does this even type checks? Because:
λ> :i (->) [..] instance Monad ((->) r) -- Defined in ‘GHC.Base’ [..]
((->) r) is an instance of Monad! The instance is:
instance Monad ((->) r) where f >>= k = \r -> k (f r) r
you already know that `m >> k` is defined as `m >>= \_ -> k`, so
f >> k = \r -> (\_ -> k) (f r) r = \r -> k r
Is it clear enough? _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (2)
-
Baa
-
Francesco Ariis