
When I load the State module in Hugs, then I can define the function f below, but I do not immediately see exactly what function "return" returns. Explanation welcome. For example:
f [2..4] [6..9] [6,7,8,9,6,7,8,9,6,7,8,9] That is, it just repeats the second argument as many times as the length of the second argument.
Hans Aberg -------- import Control.Monad.State f :: Monad a => a b -> a c -> a c f x y = x >>= (return y) --------

It has nothing to do with State; it actually works in List monad. "return y" is just another way of writing "[y]". You don't need to import Control.Monad.State for this to work; you only need Control.Monad (which is imported by the former). On 16 Apr 2008, at 16:56, Hans Aberg wrote:
When I load the State module in Hugs, then I can define the function f below, but I do not immediately see exactly what function "return" returns. Explanation welcome.
For example:
f [2..4] [6..9] [6,7,8,9,6,7,8,9,6,7,8,9] That is, it just repeats the second argument as many times as the length of the second argument.
Hans Aberg
-------- import Control.Monad.State
f :: Monad a => a b -> a c -> a c f x y = x >>= (return y) --------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Before somebody noticed: I'm wrong. It's not List monad, but also a "(->) x" monad, also defined in Control.Monad. Therefore, "return y" is just "const y". Therefore, x >>= (return y) = x >>= (const y) = x >> y On 16 Apr 2008, at 17:04, Miguel Mitrofanov wrote:
It has nothing to do with State; it actually works in List monad. "return y" is just another way of writing "[y]".
You don't need to import Control.Monad.State for this to work; you only need Control.Monad (which is imported by the former).
On 16 Apr 2008, at 16:56, Hans Aberg wrote:
When I load the State module in Hugs, then I can define the function f below, but I do not immediately see exactly what function "return" returns. Explanation welcome.
For example:
f [2..4] [6..9] [6,7,8,9,6,7,8,9,6,7,8,9] That is, it just repeats the second argument as many times as the length of the second argument.
Hans Aberg
-------- import Control.Monad.State
f :: Monad a => a b -> a c -> a c f x y = x >>= (return y) --------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 16 Apr 2008, at 15:14, Miguel Mitrofanov wrote:
Before somebody noticed: I'm wrong.
It's not List monad, but also a "(->) x" monad, also defined in Control.Monad.
Therefore, "return y" is just "const y". Therefore,
x >>= (return y) = x >>= (const y) = x >> y
Right. It is an interesting monad, but it may cause unexpected effect, in view of its implicit name. Hans

Miguel Mitrofanov wrote:
It has nothing to do with State; it actually works in List monad. "return y" is just another way of writing "[y]".
Actually, it seems that in this case return is from the ((->) a) monad, i.e. return=const. f x y = x >>= return y = x >>= const y = (concat . map) (const y) x = concat (map (const y) x) Zun.

Am Mittwoch, 16. April 2008 14:56 schrieb Hans Aberg:
When I load the State module in Hugs, then I can define the function f below, but I do not immediately see exactly what function "return" returns. Explanation welcome.
For example:
f [2..4] [6..9]
[6,7,8,9,6,7,8,9,6,7,8,9] That is, it just repeats the second argument as many times as the length of the second argument.
Hans Aberg
-------- import Control.Monad.State
f :: Monad a => a b -> a c -> a c f x y = x >>= (return y) --------
The point is the instance Monad ((->) a) where return x = const x f >>= g = \x -> g (f x) x which is defined in Control.Monad.Instances (try in GHCI: Prelude> let f x y = x >>= (return y) Prelude> :t f f :: (Monad ((->) a), Monad m) => m a -> m b -> m b ). This is imported into Control.Monad.State and hence the instance is visible. By the type of (>>=), (return y) must have type (a -> m b), on the other hand, if y has type c, then (return y) has type (m' c) for some monad m'. Unifying m' c and a -> m b gives then m' === ((->) a) and c === m b. Now according to the instance, return y === const y, so f is the same as g x y = x >>= (const y).

On 16 Apr 2008, at 15:22, Daniel Fischer wrote:
The point is the
instance Monad ((->) a) where return x = const x f >>= g = \x -> g (f x) x
which is defined in Control.Monad.Instances...
Thank you. I suspected there was an instance somewhere, and I wanted to know where it is defined.
(try in GHCI: Prelude> let f x y = x >>= (return y) Prelude> :t f f :: (Monad ((->) a), Monad m) => m a -> m b -> m b ).
It works in Hugs too. If I don't import Control.Monad.State, then f :: (Monad a, Monad ((->) b)) => a b -> a c -> a c
This is imported into Control.Monad.State and hence the instance is visible.
By the type of (>>=), (return y) must have type (a -> m b), on the other hand, if y has type c, then (return y) has type (m' c) for some monad m'. Unifying m' c and a -> m b gives then m' === ((->) a) and c === m b. Now according to the instance, return y === const y, so f is the same as g x y = x >>= (const y).
Good to know the details. Thanks. Hans
participants (4)
-
Daniel Fischer
-
Hans Aberg
-
Miguel Mitrofanov
-
Roberto Zunino