in which monad am I?

Hello, this is my first post to the list. I am learning Haskell and I think I understand monads (well, that doesn't mean that I actually understand them :-) ) Nevertheless, I would like to check something with you. My question is: how do you know in which monad you are computing at a given time? What I mean is that, when dealing with more than a monad at the same time (Maybe, List, IO come to my mind) if I understand correctly you have to lift values back and forth from a monad to the other. How do you "keep" track of the monad you are in a given time? I think that the type system will help to resolve to the relevant function (eg, thinking to liftM signature, liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r But doesn't ever happen that poor liftM be confused? and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ? I hope it's not a too silly question. If so, please point me to the relevant resouces (Are monad transformers relevant to my issue?) Thanks in advance, Francesco

I am not sure I completely understand your question (I think I do)
But doesn't ever happen that poor liftM be confused?
The compiler is able to figure out which Monad you are working in via type inference. This is true for all overloaded functions not just the monadic ones. For example in this ghci session: Prelude> :m Control.Monad Prelude Control.Monad> liftM id [1] [1] Prelude Control.Monad> liftM id (Just "qaz") Just "qaz" ghci is able to infer that the Monad's in question are the Maybe and List respectively. In (almost?) all cases type inference allows the compiler to pick which overloaded implementation is to be used.
and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ?
It is probably a matter of taste - but adding type signatures even in
the presence
of type inference is usually a good thing except for the most trivial cases It
serves as a documentation and a quick test by making sure that the
compiler and you
infer the same type since it is a compile error to specify a type
which is not compatible
with what the compiler infers.
The haskell wiki book though incomplete in places does a good job and
so does the
wikipedia entry for Type Inference
http://en.wikibooks.org/wiki/Haskell/Type_basics#Type_inference
http://en.wikipedia.org/wiki/Type_inference
http://stackoverflow.com/questions/463870/when-to-exploit-type-inference-in-...
On Sun, Jan 3, 2010 at 4:38 PM, Francesco Guerrieri
Hello, this is my first post to the list.
I am learning Haskell and I think I understand monads (well, that doesn't mean that I actually understand them :-) ) Nevertheless, I would like to check something with you. My question is: how do you know in which monad you are computing at a given time? What I mean is that, when dealing with more than a monad at the same time (Maybe, List, IO come to my mind) if I understand correctly you have to lift values back and forth from a monad to the other. How do you "keep" track of the monad you are in a given time? I think that the type system will help to resolve to the relevant function (eg, thinking to liftM signature, liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r
But doesn't ever happen that poor liftM be confused? and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ?
I hope it's not a too silly question. If so, please point me to the relevant resouces (Are monad transformers relevant to my issue?)
Thanks in advance, Francesco _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Sun, Jan 3, 2010 at 11:06 PM, Rahul Kapoor
I am not sure I completely understand your question (I think I do)
It appears that you did. Thanks!
ghci is able to infer that the Monad's in question are the Maybe and List respectively. In (almost?) all cases type inference allows the compiler to pick which overloaded implementation is to be used.
Why did you put the "almost"? Given the types on which the function is acting, either it finds a good match or not, in which case it is a compile-time error. What am I missing?
and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ?
It is probably a matter of taste - but adding type signatures even in the presence of type inference is usually a good thing except for the most trivial cases It serves as a documentation and a quick test by making sure that the compiler and you infer the same type since it is a compile error to specify a type which is not compatible with what the compiler infers.
Great, I didn't recall that a wrong annotation was a compile error. Francesco

On Sun, 2010-01-03 at 23:21 +0100, Francesco Guerrieri wrote:
On Sun, Jan 3, 2010 at 11:06 PM, Rahul Kapoor
wrote: I am not sure I completely understand your question (I think I do)
It appears that you did. Thanks!
ghci is able to infer that the Monad's in question are the Maybe and List respectively. In (almost?) all cases type inference allows the compiler to pick which overloaded implementation is to be used.
Why did you put the "almost"? Given the types on which the function is acting, either it finds a good match or not, in which case it is a compile-time error. What am I missing?
That further it may be lost (if I misunderstood the question then sorry). liftM a b will now the correct monad as long as: 1. It knows monad in second parameter or 2. It knows monad in result Knowing (or defaulting in case of GHCi) is sufficient.
and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ?
It is probably a matter of taste - but adding type signatures even in the presence of type inference is usually a good thing except for the most trivial cases It serves as a documentation and a quick test by making sure that the compiler and you infer the same type since it is a compile error to specify a type which is not compatible with what the compiler infers.
Well. As far as 'global' signatures (i.e. the ones directly in module) are concerned it is correct. However there is sometimes need to write something like:
sizeOf (undefined :: CInt) or map (show :: Int -> String) . map read
Great, I didn't recall that a wrong annotation was a compile error.
That's strong type system :) Regards

On Sun, 2010-01-03 at 22:38 +0100, Francesco Guerrieri wrote:
Hello, this is my first post to the list.
I am learning Haskell and I think I understand monads (well, that doesn't mean that I actually understand them :-) ) Nevertheless, I would like to check something with you. My question is: how do you know in which monad you are computing at a given time? What I mean is that, when dealing with more than a monad at the same time (Maybe, List, IO come to my mind) if I understand correctly you have to lift values back and forth from a monad to the other. How do you "keep" track of the monad you are in a given time? I think that the type system will help to resolve to the relevant function (eg, thinking to liftM signature, liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r
But doesn't ever happen that poor liftM be confused? and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ?
I hope it's not a too silly question. If so, please point me to the relevant resouces (Are monad transformers relevant to my issue?)
Thanks in advance, Francesco
'In which monad' question is the same as 'can type system be confused'. Except for syntax sugar (do) monads are nothing special in Haskell. Not more special then Read or Show classes. For example (for type system):
f :: [String] -> [String] f = map show . map read
main = interact (unlines . f . lines)
test.lhs:6:21: Ambiguous type variable `a' in the constraints: `Read a' arising from a use of `read' at test.lhs:6:21-24 `Show a' arising from a use of `show' at test.lhs:6:10-13 Probable fix: add a type signature that fixes these type variable(s) With monad it is harder (as monad is one-way) but it is possible to do it:
extract $ liftM (+1) (return 0)
results in: Ambiguous type variable `f' in the constraints: `Monad f' arising from a use of `liftM' at <interactive>:1:10-30 `Copointed f' arising from a use of `extract' at <interactive>:1:0-6 Probable fix: add a type signature that fixes these type variable(s) We only know that we operate on some monad which is copointed. But we have no idea what is it. However in 99% of cases we don't have to. (You man notice the signature of extract is - extract :: (Copointed f) => f a -> a so the problem is when we remove type [type does not occures on RHS of last ->]) Regards

On Sun, Jan 3, 2010 at 11:21 PM, Maciej Piechotka
On Sun, 2010-01-03 at 22:38 +0100, Francesco Guerrieri wrote:
My question is: how do you know in which monad you are computing at a given time?
'In which monad' question is the same as 'can type system be confused'.
I like this way of rephrasing it. Rahul's earlier answer led me to it, too.
Except for syntax sugar (do) monads are nothing special in Haskell. Not more special then Read or Show classes.
For example (for type system):
f :: [String] -> [String] f = map show . map read
main = interact (unlines . f . lines)
test.lhs:6:21: Ambiguous type variable `a' in the constraints: `Read a' arising from a use of `read' at test.lhs:6:21-24 `Show a' arising from a use of `show' at test.lhs:6:10-13 Probable fix: add a type signature that fixes these type variable(s)
Ok, I understand it this way: f takes a list of string, maps "read" to it and maps "show" (converting them to their string representation) to the resulting list. f never explicitly bothers with the type to which the strings were "read", since it shows them asap. BUT if the compiler is to pick an implementation of read, the type must be known.
With monad it is harder (as monad is one-way) but it is possible to do it:
extract $ liftM (+1) (return 0)
results in:
Ambiguous type variable `f' in the constraints: `Monad f' arising from a use of `liftM' at <interactive>:1:10-30 `Copointed f' arising from a use of `extract' at <interactive>:1:0-6 Probable fix: add a type signature that fixes these type variable(s)
We only know that we operate on some monad which is copointed. But we have no idea what is it. However in 99% of cases we don't have to.
(You man notice the signature of extract is - extract :: (Copointed f) => f a -> a so the problem is when we remove type [type does not occures on RHS of last ->])
Ok, you're losing me a bit with the "copointed f". Could you please clarify further the example? I assume that extract is the "inverse" of liftM. I have not yet found it and searching for "haskell extract monad" doesn't find a specific reference link. If extract "unlifts" a value out of a Monad I think that it cannot be defined for every monad (you cannot get out from the IO monad.... right?). In this sense you are first lifting and then unlifting like earlier you were first reading and then showing...? and so in principle you are "monad agnostic" but the type system is puzzled because it doesn't know to which monad you want to lift? Thanks, Francesco

On Sun, 2010-01-03 at 23:44 +0100, Francesco Guerrieri wrote:
On Sun, Jan 3, 2010 at 11:21 PM, Maciej Piechotka
wrote: Except for syntax sugar (do) monads are nothing special in Haskell. Not more special then Read or Show classes.
For example (for type system):
f :: [String] -> [String] f = map show . map read
main = interact (unlines . f . lines)
test.lhs:6:21: Ambiguous type variable `a' in the constraints: `Read a' arising from a use of `read' at test.lhs:6:21-24 `Show a' arising from a use of `show' at test.lhs:6:10-13 Probable fix: add a type signature that fixes these type variable(s)
Ok, I understand it this way: f takes a list of string, maps "read" to it and maps "show" (converting them to their string representation) to the resulting list. f never explicitly bothers with the type to which the strings were "read", since it shows them asap. BUT if the compiler is to pick an implementation of read, the type must be known.
Yes. It knows that he should call some read and some show functions but have no idea which function.
With monad it is harder (as monad is one-way) but it is possible to do it:
extract $ liftM (+1) (return 0)
results in:
Ambiguous type variable `f' in the constraints: `Monad f' arising from a use of `liftM' at <interactive>:1:10-30 `Copointed f' arising from a use of `extract' at <interactive>:1:0-6 Probable fix: add a type signature that fixes these type variable(s)
We only know that we operate on some monad which is copointed. But we have no idea what is it. However in 99% of cases we don't have to.
(You man notice the signature of extract is - extract :: (Copointed f) => f a -> a so the problem is when we remove type [type does not occures on RHS of last ->])
Ok, you're losing me a bit with the "copointed f".
It's one more strange class. The definition (from category-extras package if you need to know): class Copointed f where extract :: f a -> a Sorry if I mess a bit. You got the main point so read further only if you want to know a bit about copointed
Could you please clarify further the example? I assume that extract is the "inverse" of liftM.
It's rather inverse of return. However it is unlikely that you'll ever use it (at least - I haven't and many programs/libraries have not). It was just an example.
I have not yet found it and searching for "haskell extract monad" doesn't find a specific reference link.
http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/... Generally use hayoo[1] (hoogle stop working for me lately) inserting for example 'extract'. [1] http://holumbus.fh-wedel.de/hayoo/hayoo.html
If extract "unlifts" a value out of a Monad I think that it cannot be defined for every monad
Yest. Hence we know that it is monad which is copointed. I.e. we look for such m that (Copointed m, Monad m) - m that it member of both classes.
(you cannot get out from the IO monad.... right?).
Well. You can get out of IO monad. But you shouldn't (it creates lot's of problems). But generally you cannot. Imagine extractM :: Monad m => m a -> a What would be extractM []
In this sense you are first lifting and then unlifting like earlier you were first reading and then showing...? and so in principle you are "monad agnostic" but the type system is puzzled because it doesn't know to which monad you want to lift?
Yes. However as long you're in Functor/Monad/Applicative range you are quite safe as they are like Alcatraz - no escape (see however PS). However Identity is both monad and Copointed (it is somewhere defined)
newtype Identity a = Identity a instance Monad Identity where (Identity v) >>= f = f v return = Identity instance Copointed Identity where extract (Identity v) = v
So:
extract $ (liftM (+1) (return 0) :: Identity Int)
will work
Thanks, Francesco
Regards PS. Possibly simpler example:
liftNull :: (Monad m, Monad n) => m () -> n () liftNull _ = return ()
liftNull $ liftM (+1) (return 0)

On Sun, Jan 03, 2010 at 10:38:28PM +0100, Francesco Guerrieri wrote:
But doesn't ever happen that poor liftM be confused? and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ?
If by "explicitly state to which monad" you mean specializing liftM or fmap, then the answer is no. It is not uncommon to see fmap (fmap function) being used to map two layers of structures. If by stating you mean giving a type signature, then yes, it is a good practice to give type signatures to all top-level definitions. The compiler never gets "confused". The only thing that may happen is having more than one possible type that fulfills your needs. The classical example is Num overloading: $ ghci GHCi, version 6.10.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer ... linking ... done. Loading package base ... linking ... done. Prelude> :s -Wall Prelude> :m Data.Int Prelude Data.Int> let e :: Int; e = 31 Prelude Data.Int> 2^e <interactive>:1:0: Warning: Defaulting the following constraint(s) to type `Integer' `Num t' arising from a use of `^' at <interactive>:1:0-2 In the expression: 2 ^ e In the definition of `it': it = 2 ^ e <interactive>:1:0: Warning: Defaulting the following constraint(s) to type `Integer' `Num t' arising from a use of `^' at <interactive>:1:0-2 In the expression: 2 ^ e In the definition of `it': it = 2 ^ e 2147483648 Prelude Data.Int> 2^e :: Int32 -2147483648 Note that using just '2^e' in the GHCi prompt defaults to Integer. If I say I want Int32 as a type, then the result is completely different, in this case it overflows. Another case when you arrive at those oddities is when dealing with exceptions. The function you use to catch the exceptions need to explicitly say which type of exceptions it wants to catch. Failures to list the correct type will cause the exception to fall through and propagate. HTH, -- Felipe.

On Sun, Jan 3, 2010 at 11:30 PM, Felipe Lessa
On Sun, Jan 03, 2010 at 10:38:28PM +0100, Francesco Guerrieri wrote:
But doesn't ever happen that poor liftM be confused? and do poor haskell programmers never feel the need to explicitly state to which monad they "wish to lift" ?
If by "explicitly state to which monad" you mean specializing liftM or fmap, then the answer is no. It is not uncommon to see
fmap (fmap function)
being used to map two layers of structures. If by stating you mean giving a type signature, then yes, it is a good practice to give type signatures to all top-level definitions.
I was thinking to type signatures :-) By the way, you all refer to top-level definition. But in the map show . map read example, what I see at the top-level is [String] -> [String]. This probably means that my understanding of what is a top-level definition is faulty...
The compiler never gets "confused". The only thing that may happen is having more than one possible type that fulfills your needs. The classical example is Num overloading:
This is a very clear example, thanks! Francesco
participants (4)
-
Felipe Lessa
-
Francesco Guerrieri
-
Maciej Piechotka
-
Rahul Kapoor