Error when ($) is used, but no error without

Bulat Ziganshin bulat.ziganshin at gmail.com
Thu Apr 27 06:04:48 EDT 2006


Hello Robin,

Thursday, April 27, 2006, 8:01:16 AM, you wrote:
> g x = f $ x  -- the only change

> gives this error:

>      Inferred type is less polymorphic than expected
>        Quantified type variable `a' escapes
>        Expected type: a a1 -> b
>        Inferred type: C a1 -> Int
>      In the first argument of `($)', namely `f'
>      In the definition of `g': g x = f $ x

> What's going on here?

may be, because '$' can't work with rank-2 types (at least error
message is the same as i got when tried to use "runST $ ..."). i asked
similar question some time ago, below are the answers (you can find
them on pipermail):



Bulat Ziganshin wrote:

the following code can't go through typechecking
> import Control.Monad.ST
> import Data.Array.ST
> main = print $ runST $
>            do arr <- newArray (1,10) 127
>               a <- readArray arr 1
>               writeArray arr 1 216
>               b <- readArray arr 1
>               return (a,b)


Indeed. The short answer: use 
        runST (long expression) 
rather than
        runST $ long expression 

when it comes to higher-ranked functions such as runST.
A longer answer:
        http://www.haskell.org/pipermail/haskell-cafe/2004-December/008062.html

> let me know what i need to read to fix it myself
MLF (see Daan Leijen, A. Loeh, `Qualified types for MLF', ICFP05)






Bulat Ziganshin wrote:

... for the same reason as this one doesn't get through:

import Control.Monad.ST
import Data.Array.ST
main = print $ runST $
           do return ()

... but this one does:

import Control.Monad.ST
import Data.Array.ST
main = print $ runST (
           do return ())

it's all about rank-2 types; see SPJ's et al. paper on type inference
for these types. However, I guess that the jury is still out, say this
specific rank-2 behavior may be revised (and I also hope so).

HTH
Ralf


> -----Original Message-----
> From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-
> bounces at haskell.org] On Behalf Of Bulat Ziganshin
> Sent: Tuesday, January 03, 2006 2:28 AM
> To: haskell-cafe at haskell.org
> Subject: [Haskell-cafe] ST monad
> 
> Hello
> 
> the following code can't go through typechecking. can anyone help me
> to fix it or, better, let me know what i need to read to fix it
myself? :)
> 
> import Control.Monad.ST
> import Data.Array.ST
> main = print $ runST $
>            do arr <- newArray (1,10) 127
>               a <- readArray arr 1
>               writeArray arr 1 216
>               b <- readArray arr 1
>               return (a,b)
> 
> 
> PS: error message is
> 
> b.hs:4:15:
>     Inferred type is less polymorphic than expected
>       Quantified type variable `s' escapes
>       Expected type: ST s a -> b
>       Inferred type: (forall s1. ST s1 a) -> a
>     In the first argument of `($)', namely `runST'
>     In the second argument of `($)', namely
>         `runST
>          $ (do
>               arr <- newArray (1, 10) 127
>               a <- readArray arr 1
>               writeArray arr 1 216
>               b <- readArray arr 1
>               return (a, b))'
> 
> 

-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Glasgow-haskell-users mailing list