[Haskell-cafe] strange GHCi type inference behavior involving map and partially applied functions

Erik Hesselink hesselink at gmail.com
Sun Apr 15 22:45:47 CEST 2012


GHCi is defaulting the 'a' in 'Show a' to unit because of the extended
defaulting feature [1] in GHCi. If you turn on
NoMonomorphismRestriction in GHCi, you get the same behavior as in
GHC. If you turn on ExtendedDefaulting in GHC, you get the same
behavior as in GHCi.

Erik

[1] http://www.haskell.org/ghc/docs/latest/html/users_guide/interactive-evaluation.html#extended-default-rules

On Sun, Apr 15, 2012 at 22:31, Ting Lei <tinlyx at hotmail.com> wrote:
> Hi All,
>
> I found a really strange case where GHC and GHCi behave differently in
> inferring types. It took me hours to figure this out.
>
> The following program
>
> {-# LANGUAGE NoMonomorphismRestriction #-}
> g x i = x ++ show i
> [a,b] = map g ["X","Y"]
>
> will not load without "NoMonomorphismRestriction". With that option, it
> will load and return the correct types (as expected):
> *Main> :t [a,b]
> [a,b] :: Show a => [a -> [Char]]
>
> *Main> a 1
> "X1"
>
> However, if I do the same thing GHCi, the type inferencing seems to have
> been messed up:
>
> *Main> let g x i = x ++ show i
> *Main> let [a,b] = map g ["X","Y"]
> *Main> :t [a,b]
> [a,b] :: [() -> [Char]]
> *Main> :t map g ["X","Y"]
> map g ["X","Y"] :: Show a => [a -> [Char]]
>
> Note how in the last two instances the terms on the left and right-hand
> sides of the definition return different types. Also, the correct return
> type should be a list of unary functions taking an (Show a) as
> the parameter. Now the result is unusable:
>
> *Main> a 1
> <interactive>:52:3:
>     No instance for (Num ())
>       arising from the literal `1'
>     Possible fix: add an instance declaration for (Num ())
>     In the first argument of `a', namely `1'
>     In the expression: a 1
>     In an equation for `it': it = a 1
>
> I am using GHCi 7.4.1 under windows. I also tried this under GHC 7.0x
> Is this a GHCi bug or could anyone please explain why this can of strange
> behavior happens?
> If this is a bug, could anyone with an account help file a bug for this?
>
> Thanks in advance,
>
> Ting
>
>
> _______________________________________________
> 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