TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings
Using GHC 8.4.3, I'd expect the following to work:
{-# LANGUAGE RebindableSyntax, OverloadedStrings #-}
module Fail where
import Prelude hiding (fail)
foo x = do
Just y <- x
return y
newtype Text = Text String
fail :: Text -> a
fail (Text x) = error x
fromString :: String -> Text
fromString = Text
But it fails with:
Fail.hs:8:5-15: error:
* Couldn't match expected type `[Char]' with actual type `Text'
* In a stmt of a 'do' block: Just y <- x
In the expression:
do Just y <- x
return y
In an equation for `foo':
foo x
= do Just y <- x
return y
|
8 | Just y <- x
| ^^^^^^^^^^^
Given the enabled extensions, I'd expect foo
to desugar as:
foo x = x >>= \v -> case v of
Just y -> return y
_ -> fail (fromString "pattern match error")
But looking at TcMatches.tcMonadFailOp it checks the fail operation (which is literally fail
) takes an argument of type tyString (e.g. [Char]
). One way around that would be to make the "fail-op" being passed around be fail . fromString
if the appropriate extensions are enabled.
Trac metadata
Trac field | Value |
---|---|
Version | 8.4.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | ndmitchell@gmail.com |
Operating system | |
Architecture |