[Haskell-beginners] Types and the difference between GHCi interactive and a file

Daniel Fischer daniel.is.fischer at web.de
Sun Sep 26 17:29:02 EDT 2010


On Sunday 26 September 2010 22:46:35, Russ Abbott wrote:
> The following runs without a problem.
>
> Prelude> let null' xs = xs == []
> null' :: (Eq a) => [a] -> Bool
>
> Prelude> let main' = do print (null' [])
> main' :: IO ()
>
> Prelude> main'
> True
> it :: ()
>
> But if I put essentially the same code in a file and try to load the
> file I get an error.
>
> File: Null
>
> null' xs = xs == []
>
> main = do print (null' [])
>
>
> Prelude> :load "Null.hs"
> [1 of 1] Compiling Main             ( Null.hs, interpreted )
>
> Null.hs:3:17:
>     Ambiguous type variable `a' in the constraint:
>       `Eq a' arising from a use of `null'' at Null.hs:3:17-24
>     Probable fix: add a type signature that fixes these type variable(s)
> Failed, modules loaded: none.
>
> Why is that?

ghci has extended defaulting rules, a lot of things have their type 
defaulted to avoid too many "Ambiguous type variable ..." messages at the 
prompt although per the report they shouldn't be defaulted.

When a source file is compiled (whether to object code or to bytecode), the 
defaulting rules of the report are applied. The expression "null' []" has 
the ambiguous type Eq a => [a] -> Bool (there's no way to determine at 
which type the expression should be evaluated).
The defaulting rules in the language report,
http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-790004.3.4
say such an ambiguity can be resolved by defaulting under certain 
cirumstances, a necessary condition is that there is one numeric type class 
constraint. That isn't the case here, so defaulting isn't allowed, 
compilation fails.

At the prompt, ghci merrily resolves the ambiguity by defaulting a to ().

>
>
> I had thought that the ambiguity was referring to the type of [] in the
> print statement, i.e., that GHC can't figure out the type of [].  If I
> modify the print statement to be   print ( null' ([] :: [Int]) ) 
> everything is ok.

Right.

>
> But if that's the case, why is this not a problem at the interactive
> level?

Extended defaulting rules, because otherwise there would be too many 
ambiguity errors.
At the prompt, most expressions you enter have very little context which 
would allow to determine a type, in source files there's usually much more 
context available, so ambiguities are less frequent in code.

>
> Here is a related question.  In the following what does it mean to say
> that x is of type [a] where "a" is a type variable?
>
> Prelude> let x = []
> x :: [a]

It means x is a polymorphic expression, x can belong to every list type.

Prelude> ([x,[True]],[x,"ah"],[x,[fromEnum 'u']])
([[],[True]],["","ah"],[[],[117]])

It can even appear at different types in the same expression.

>
> For example,
>
> Prelude> x == (tail [1 :: Int])
> True
> it :: Bool
>
> Prelude> x == (tail [1 :: Float])
> True
> it :: Bool
>
> Prelude> (tail [1 :: Int]) == (tail [1 :: Float])
>
> <interactive>:1:28:
>     Couldn't match expected type `Int' against inferred type `Float'
>     In the expression: 1 :: Float
>     In the first argument of `tail', namely `[1 :: Float]'
>     In the second argument of `(==)', namely `(tail [1 :: Float])'
>
> Can a value like the value of x really be of an incompletely specified
> type?

Yes, that's possible. [], Nothing and others have this property.
Although, it would be more correct to say that x can be instantiated at 
different types.

>
> I couldn't do that in the file.

You can, but there are a few things that can prevent it.
One is the monomorphism restriction (aka the dreaded MR).

>
> When I tried the following in the file,
>
> print (null' ([] :: (Eq a) => a))
>
> I got this error message on loading the file.
>
> Null.hs:3:24:
>     Couldn't match expected type `a1' against inferred type `[a]'
>       `a1' is a rigid type variable bound by
>            an expression type signature at Null.hs:3:34
>     In the first argument of `null'', namely `([] :: (Eq a) => a)'
>     In the first argument of `print', namely
>         `(null' ([] :: (Eq a) => a))'
>     In the expression: print (null' ([] :: (Eq a) => a))
>

Yes, that's not very illuminating at first.
The point of this message is that you said [] could have any type, as long 
as it belongs to Eq, in particular, it could be Bool. However, the most 
general type of [] is [a], so it could be any type, as long as it's a list 
type - Bool isn't, so you have the type mismatch, the promised type
(Eq a) => a versus the inferred type [b].

If you fix that and write

print (null' ([] :: (Eq a) => [a]))

You'll get a different error, the one you got before you added the 
expression type signature:

   Ambiguous type variable `b' in the constraint:
      `Eq b'
        arising from an expression type signature at TTest.hs:3:22-40
    Probable fix: add a type signature that fixes these type variable(s)

>
> Thanks.
>
> -- Russ



More information about the Beginners mailing list