<div dir="ltr"><div><div>This looks very similar to <a href="https://ghc.haskell.org/trac/ghc/ticket/11319">https://ghc.haskell.org/trac/ghc/ticket/11319</a>, but might be worth including as a separate example there. Note that it does compile if you swap the order of the case alternatives.<br><br></div>Regards,<br></div><div>Reid Barton<br><br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Fri, Mar 4, 2016 at 8:43 AM, Kosyrev Serge <span dir="ltr"><<a href="mailto:_deepfire@feelingofgreen.ru" target="_blank">_deepfire@feelingofgreen.ru</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Good day!<br>
<br>
I realise that ImpredicativeTypes is a problematic extension, but I have<br>
found something that looks like an outright bug -- no polymorphism involved:<br>
<br>
,----<br>
| {-# LANGUAGE ImpredicativeTypes #-}<br>
|<br>
| module Foo where<br>
|<br>
| foo :: IO (Maybe Int)<br>
| foo = do<br>
| pure $ case undefined :: Maybe String of<br>
| Nothing<br>
| -> Nothing<br>
| Just _<br>
| -> (undefined :: Maybe Int)<br>
`----<br>
<br>
produces the following errors:<br>
<br>
,----<br>
| foo.hs:7:3: error:<br>
| • Couldn't match type ‘forall a. Maybe a’ with ‘Maybe Int’<br>
| Expected type: IO (Maybe Int)<br>
| Actual type: IO (forall a. Maybe a)<br>
| • In a stmt of a 'do' block:<br>
| pure<br>
| $ case undefined :: Maybe String of {<br>
| Nothing -> Nothing<br>
| Just _ -> (undefined :: Maybe Int) }<br>
| In the expression:<br>
| do { pure<br>
| $ case undefined :: Maybe String of {<br>
| Nothing -> Nothing<br>
| Just _ -> (undefined :: Maybe Int) } }<br>
| In an equation for ‘foo’:<br>
| foo<br>
| = do { pure<br>
| $ case undefined :: Maybe String of {<br>
| Nothing -> Nothing<br>
| Just _ -> (undefined :: Maybe Int) } }<br>
|<br>
| foo.hs:11:19: error:<br>
| • Couldn't match type ‘a’ with ‘Int’<br>
| ‘a’ is a rigid type variable bound by<br>
| a type expected by the context:<br>
| forall a. Maybe a<br>
| at foo.hs:11:19<br>
| Expected type: forall a. Maybe a<br>
| Actual type: Maybe Int<br>
| • In the expression: (undefined :: Maybe Int)<br>
| In a case alternative: Just _ -> (undefined :: Maybe Int)<br>
| In the second argument of ‘($)’, namely<br>
| ‘case undefined :: Maybe String of {<br>
| Nothing -> Nothing<br>
| Just _ -> (undefined :: Maybe Int) }’<br>
`----<br>
<span class="HOEnZb"><font color="#888888"><br>
--<br>
с уважениeм / respectfully,<br>
Косырев Сергей<br>
_______________________________________________<br>
ghc-devs mailing list<br>
<a href="mailto:ghc-devs@haskell.org">ghc-devs@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs</a><br>
</font></span></blockquote></div><br></div>