[Haskell-cafe] Re: Type errors, would extensions help?

Ryan Ingram ryani.spam at gmail.com
Thu Jan 15 14:03:21 EST 2009


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 <briqueabraque at yahoo.com> wrote:
>>> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list