[Haskell-cafe] Can't use TypeApplications with polymorphic let bind

adam vogt vogt.adam at gmail.com
Tue Mar 29 19:38:17 UTC 2022


For the third case, the GHC manual says -XTypeApplications:

> can be used whenever the full polymorphic type of the function is known.
If the function is an identifier (the common case), its type is considered
known only when the identifier has been given a type signature. If the
identifier does not have a type signature, visible type application cannot
be used.

So it works if x has a type signature:

x :: C m => () -> m
x u = c u
g = (x @Int (), x @Bool ())

I think 'g' should work without the type signature on 'x'. Inferred type
variables may switch places between ghc versions. So "h" below might change
between (Int,Bool) and (Bool,Int). So they reject "h". But for 'g' there's
only one ordering.

h = (x (), x ()) @Int @Bool

The error "Cannot apply expression of type _ to a visible type argument _
in the expression: x ..." might be clearer if it also had "Possible fix:
add a type signature to the declaration/binding of x"

Regards,
Adam



On Tue, Mar 29, 2022 at 11:40 AM Oleg Grenrus <oleg.grenrus at iki.fi> wrote:

> First example doesn't work due MonomorphismRestriction.
> Second one works because it's all Haskell98 (to first approximation: it
> must work).
> Third one is interesting. At first I didn't expect it work, but given a
> bit of thought, I wasn't tht sure anymore: I don't know why `x` isn't
> already generalized when type-checking body of the let-in.
>
> - Oleg
>
> On 28.3.2022 17.14, Georgi Lyubenov wrote:
> > Dear Cafe,
> >
> > I recently came upon this little "type-inference puzzle". Can anyone
> > shine some light on why the third example doesn't compile?
> >
> > ```
> > {-# LANGUAGE TypeApplications #-}
> > -- doesn't work
> > -- I expect this, not sure why it happens
> > {-
> > class C m where
> >   c :: () -> m
> >
> > instance C Int where
> >   c () = 0
> >
> > instance C Bool where
> >   c () = False
> >
> > f :: (Int, Bool)
> > f =
> >   let x = c
> >    in
> >    (x (), x ())
> > -}
> >
> > -- works
> > -- I expect this, not sure why it happens
> > {-
> > class C m where
> >   c :: () -> m
> >
> > instance C Int where
> >   c () = 0
> >
> > instance C Bool where
> >   c () = False
> >
> > f :: (Int, Bool)
> > f =
> >   let x u = c u
> >    in
> >    (x (), x ())
> > -}
> >
> > -- doesn't work
> > -- I don't expect this, not sure why it happens
> > {-
> > class C m where
> >   c :: () -> m
> >
> > instance C Int where
> >   c () = 0
> >
> > instance C Bool where
> >   c () = False
> >
> > f :: (Int, Bool)
> > f =
> >   let x u = c u
> >    in
> >    (x @Int (), x @Bool ())
> > -- wtf.hs:54:5: error:
> > --     • Cannot apply expression of type ‘() -> m0’
> > --       to a visible type argument ‘Int’
> > --     • In the expression: x @Int ()
> > --       In the expression: (x @Int (), x @Bool ())
> > --       In the expression: let x u = c u in (x @Int (), x @Bool ())
> > --    |
> > -- 54 |    (x @Int (), x @Bool ())
> > --    |     ^^^^^^^^^
> > -}
> > ```
> >
> > Cheers,
> > Georgi
> >
> > _______________________________________________
> > 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.
> _______________________________________________
> 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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20220329/a1a57019/attachment.html>


More information about the Haskell-Cafe mailing list