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

Georgi Lyubenov godzbanebane at gmail.com
Mon Mar 28 14:14:44 UTC 2022


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



More information about the Haskell-Cafe mailing list