[Haskell-cafe] inference with implicitparams seems broken

rowan goemans goemansrowan at gmail.com
Wed Mar 23 14:48:12 UTC 2022


Hello everyone,

I wonder why the following taken from an stackoverflow answer doesn't 
work: 
https://stackoverflow.com/questions/71184922/is-it-possible-to-infer-a-type-that-is-a-reflection-like-closure. 
Code of the answer posted here verbatim:

```
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE RankNTypes #-}

module Temp where

withX :: Int -> ((?x :: Int) => r) -> r
withX x r =
   let ?x = x
   in r

somethingThanNeedsX :: (?x :: Int) => Int
somethingThanNeedsX = ?x + 2

foo :: Int
foo = bar
   where
     bar = withX 42 baz

     baz = somethingThanNeedsX
```

This won't compile with the error message:

```
Orig.hs:19:11: error:
     • Unbound implicit parameter (?x::Int)
         arising from a use of ‘somethingThanNeedsX’
     • In the expression: somethingThanNeedsX
       In an equation for ‘baz’: baz = somethingThanNeedsX
       In an equation for ‘foo’:
           foo
             = bar
             where
                 bar = withX 42 baz
                 baz = somethingThanNeedsX
    |
19 |     baz = somethingThanNeedsX
```

If you give `baz` a type signature which includes the implicit param it 
compiles. But I think this is a bug. GHC should not require a type 
signature here. I tried searching for a GHC ticket but I couldn't find 
one. But that might also be down to me not using the right query.

Anyway my question is, is this expected behavior? This really makes 
implicit params less ergonomic.

Best regards,

Rowan Goemans



More information about the Haskell-Cafe mailing list