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)


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to