Type errors, would extensions help?

Hi, I have this problem trying to define a function inside a do expression. I tried this small code to help me check. This works well: --- import Data.Ratio ; main = do { printNumber <- let { print :: (Num n,Show n) => n -> IO () ; print n = do { putStrLn $ show n} } in return print ; print (1%5) ; print 5.0 } --- However, just removing 'Num n' gives: Ambiguous type variable `n' in the constraint: `Show n' arising from a use of `print' at teste.hs:7:16-20 Why is it ambiguous? Since I don't use numeric functions, 'Num n,Show n' doesn't seem more specific. Besides that, the real problem I have is a similar function declared inside a 'let' as col :: (WidgetClass w) => w->IO Int col wid = do {... that, after beeing used with w beeing Table (and instance WidgetClass Table do exist) refuses beeing used with DrawingArea (also with instance WidgetClass DrawingArea), but I wasn't able to simulate that in a small program, and don't know if it's related to the case I'm showing. Thanks for your kindness, Maurício

Mauricio wrote:
Hi,
I have this problem trying to define a function inside a do expression. I tried this small code to help me check. This works well:
--- import Data.Ratio ; main = do { printNumber <- let { print :: (Num n,Show n) => n -> IO () ; print n = do { putStrLn $ show n} } in return print ; print (1%5) ; print 5.0 } ---
I guess you intended to call printNumber in the quoted snippet? There's a way to use GHC's extensions to do what you want, let me illustrate with simpler example: {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ImpredicativeTypes #-} t1 () = do f <- (return id :: IO (forall a. a->a)) return (f "foo", f True) However, I would call this style unnatural and unnecessary. What's wrong with plain 'let' or 'where' that work without any extensions? t2 () = do let f = id return (f "foo", f True)

I have this problem trying to define a function inside a do expression. I tried this small code to help me check. This works well:
I guess you intended to call printNumber in the quoted snippet? (...) {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ImpredicativeTypes #-}
After you pointed my dumb mistake, I was able to build the first example -- without any of the extensions! Haskell can be misterious some times. Strange enough, I can't get the original (and, to my eyes, equal) problem to work. This is the smallest I could get it to be: --- WARNING: wrong use of gtk, just to get an example --- import Graphics.UI.Gtk ; main = do { initGUI ; j1 <- drawingAreaNew ; j2 <- tableNew 1 1 True ; notebook <- do { note <- notebookNew ; insertInNotebook <- let { colocar :: (WidgetClass w) => w -> String -> IO Int ; colocar wid texto = do { lb <- labelNew Nothing ; labelSetMarkup lb texto ; notebookAppendPageMenu note wid lb lb } } in return $ colocar ; insertInNotebook j1 "J1" ; insertInNotebook j2 "J2" ; return note } ; putStrLn "Finish" } --- GHC says: teste.hs:15:21: Couldn't match expected type `DrawingArea' against inferred type `Table' In the first argument of `insertInNotebook', namely `j2' In a stmt of a 'do' expression: insertInNotebook j2 "J2" (...) but I would like first argument of insert... to be any instance of WidgetClass, be it Drawing... or Table. Thanks, Maurício

I suggest you start using "let" in your do blocks; both of these
problems are solvable with let.
Binding with <- instead of "let" makes the type system work harder,
and will generally require type annotations & extensions for
polymorphic results. And it's almost never what you want, anyways;
you don't often have an object of type "IO (forall a. a -> a)"
instead of "forall a. IO (a -> a)" and this situation usually means
you should be using "let" instead.
Here's the Gtk example; the let on "mkNotebook" is not strictly
necessary but is just showing the concept in more places; I tend to
avoid x <- do ... in my code; I feel it means I should be abstracting
more.
main = do
initGUI
j1 <- drawingAreaNew
j2 <- tableNew 1 1 True
let mkNotebook = do
note <- notebookNew
let insertInNoteBook wid texto = do
lb <- labelNew Nothing
labelSetMarkup lb texto
notebookAppendPageMenu note wid lb lb
insertInNotebook j1 "J1"
insertInNotebook j2 "J2"
return note
notebook <- mkNotebook
putStrLn "Finish"
Also, is there a reason you hate the layout rule and are using
explicit semicolons everywhere?
-- ryan
On Thu, Jan 15, 2009 at 10:46 AM, Mauricio
I have this problem trying to define a function inside a do expression. I tried this small code to help me check. This works well:
I guess you intended to call printNumber in the quoted snippet? (...) {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ImpredicativeTypes #-}
After you pointed my dumb mistake, I was able to build the first example -- without any of the extensions! Haskell can be misterious some times.
Strange enough, I can't get the original (and, to my eyes, equal) problem to work. This is the smallest I could get it to be:
--- WARNING: wrong use of gtk, just to get an example --- import Graphics.UI.Gtk ; main = do { initGUI ; j1 <- drawingAreaNew ; j2 <- tableNew 1 1 True ; notebook <- do { note <- notebookNew ; insertInNotebook <- let { colocar :: (WidgetClass w) => w -> String -> IO Int ; colocar wid texto = do { lb <- labelNew Nothing ; labelSetMarkup lb texto ; notebookAppendPageMenu note wid lb lb } } in return $ colocar ; insertInNotebook j1 "J1" ; insertInNotebook j2 "J2" ; return note } ; putStrLn "Finish" } ---
GHC says:
teste.hs:15:21: Couldn't match expected type `DrawingArea' against inferred type `Table' In the first argument of `insertInNotebook', namely `j2' In a stmt of a 'do' expression: insertInNotebook j2 "J2" (...)
but I would like first argument of insert... to be any instance of WidgetClass, be it Drawing... or Table.
Thanks, Maurício
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks, everything works now. What should I read to better understand the difference for the type system between using <- and 'let'? That is not intuitive for me. About layout, I used to filter my code to better fit everyone taste before posting to this list. The filter stoped working due to some problems in 'Language.Haskell', but I'll rewrite it with haskell-src-exts before posting again. Thanks, Maurício
I suggest you start using "let" in your do blocks; both of these problems are solvable with let.
Binding with <- instead of "let" makes the type system work harder, and will generally require type annotations & extensions for polymorphic results. (...)
Also, is there a reason you hate the layout rule and are using explicit semicolons everywhere?
I have this problem trying to define a function inside a do expression. (...)

The <- binding is lambda binding (look at how it desugars). Lambda
bindings are monomorphic without any type extensions. The monadic
'let' binding is like regular 'let', so it's a point where the type
checker does generalization, and so you get (possibly) polymorphic
bindings from let.
-- Lennart
On Thu, Jan 15, 2009 at 11:20 PM, Mauricio
Thanks, everything works now.
What should I read to better understand the difference for the type system between using <- and 'let'? That is not intuitive for me.
About layout, I used to filter my code to better fit everyone taste before posting to this list. The filter stoped working due to some problems in 'Language.Haskell', but I'll rewrite it with haskell-src-exts before posting again.
Thanks, Maurício
I suggest you start using "let" in your do blocks; both of these problems are solvable with let.
Binding with <- instead of "let" makes the type system work harder, and will generally require type annotations & extensions for polymorphic results. (...)
Also, is there a reason you hate the layout rule and are using explicit semicolons everywhere?
I have this problem trying to define a function inside a do expression. (...)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Here's the desugaring:
do { pattern <- expression ; rest }
desugars to
expression >>= \temp -> case temp of pattern -> do { rest } _ -> fail "Pattern match failure"
(where "temp" is a fresh variable not used elsewhere, and the failure message usually includes source position) Whereas
do { let pattern = expression ; rest }
desugars to
let pattern = expression in do { rest }
-- ryan
On Thu, Jan 15, 2009 at 3:26 PM, Lennart Augustsson
The <- binding is lambda binding (look at how it desugars). Lambda bindings are monomorphic without any type extensions. The monadic 'let' binding is like regular 'let', so it's a point where the type checker does generalization, and so you get (possibly) polymorphic bindings from let.
-- Lennart
On Thu, Jan 15, 2009 at 11:20 PM, Mauricio
wrote: Thanks, everything works now.
What should I read to better understand the difference for the type system between using <- and 'let'? That is not intuitive for me.
About layout, I used to filter my code to better fit everyone taste before posting to this list. The filter stoped working due to some problems in 'Language.Haskell', but I'll rewrite it with haskell-src-exts before posting again.
Thanks, Maurício
I suggest you start using "let" in your do blocks; both of these problems are solvable with let.
Binding with <- instead of "let" makes the type system work harder, and will generally require type annotations & extensions for polymorphic results. (...)
Also, is there a reason you hate the layout rule and are using explicit semicolons everywhere?
I have this problem trying to define a function inside a do expression. (...)
_______________________________________________ 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

Mauricio wrote:
After you pointed my dumb mistake, I was able to build the first example -- without any of the extensions! Haskell can be misterious some times.
Strange enough, I can't get the original (and, to my eyes, equal) problem to work.
Indeed Haskell can be misterious sometimes. Now that you fixed the typo the first example compiles, but I think you will be surprised with its output: 1 % 5 5 % 1 As you can see, the type of printNumber is still monomorphic for the reasons explained by Ryan Ingram and Lennart Augustsson. It's only the peculiarity of the numeric classes in Haskell that makes two your examples different - the constant `5.0' has type `(Fractional t) => t', and (Ratio a) is an instance of Fractional.
participants (4)
-
Gleb Alexeyev
-
Lennart Augustsson
-
Mauricio
-
Ryan Ingram