[Haskell-cafe] Typeclass constraints not inferred when defining a function

Kiss Csongor kiss.csongor.kiss at gmail.com
Thu Feb 9 18:26:35 UTC 2017


Hi,

It’s because the monomorphism restriction turned off by default in GHCi sessions.
If you put this at the beginning of your source file, it should work:

{-# LANGUAGE NoMonomorphismRestriction #-}

You can read up about it here: https://wiki.haskell.org/Monomorphism_restriction

— Csongor


> On 9 Feb 2017, at 18:20, Stephen Demos <stphndemos at gmail.com> wrote:
> 
> Hi all,
> 
> A professor showed me a function today that looks like this -
> 
> `append = flip (foldr (:))`
> 
> GHC spits back an error when this is compiled -
> 
> ```
>    • Ambiguous type variable ‘t0’ arising from a use of ‘foldr’
>      prevents the constraint ‘(Foldable t0)’ from being solved.
>      Relevant bindings include
>        append :: t0 a -> [a] -> [a] (bound at test.hs:4:1)
>      Probable fix: use a type annotation to specify what ‘t0’ should be.
> ```
> 
> It's obvious from this error message the problem is that the type GHC
> infers doesn't include the typeclass constraint. In this case, it's
> Foldable, but you can easily think of other situations where the same
> error comes up with different typeclasses (a silly example that comes
> to mind is `fmap (const [])`). It's pretty easy to fix this error by
> just providing a type for the function that is more specific than the
> one GHC infers.
> 
> However, he showed me that defining the same function in ghci using a
> let binding doesn't yield the same error. In fact, when using `:t`, it
> shows that ghci successfully infers the typeclass constraint on the
> function -
> 
> ```
>> :t flip (foldr (:))
> flip (foldr (:)) :: Foldable t => t a -> [a] -> [a]
> ```
> 
> I was wondering if anyone could explain this apparent discrepancy to me.
> 
> Thanks!
> Stephen Demos
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



More information about the Haskell-Cafe mailing list