[GHC] #15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Using GHC 8.4.3, I'd expect the following to work: {{{#!hs {-# 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: {{{#!hs 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. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Could be. But would it not be simpler for you to provide a `fail` with type `String -> m a`? It's not hard to do! I'm not seeing a strong motivation for doing this in the compiler. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): The use case is for `Prelude` replacement modules that seek to switch the type of `[Char]` to something like `Text`. A standard way is to define your own `Monad`/`MonadFail` class which has `fail :: Text -> m a` in it. If that class is forced to have `fail :: [Char] -> m a` instead (as it is now) then all your users have to implement a function working on `[Char]`, even though for everything else in your custom library, they never see `[Char]` and your custom `Prelude` has no other `[Char]` related functions. In the particular example I'm working on, the `Char` type has been eliminated entirely, aside from the `fail` function. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): But all you have to do is define `fail = myFail . fromString` and you are done. I suppose you are going to say that you don't want two variants of `fail` in scope. That is a bit more convincing. But now you may get new mysterious messages about missing `IsString` instances arising from invisible code. Make a GHC proposal! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): Indeed, you can't use the name fail, which is unfortunate. The mysterious messages about things already happens - I get an error about `[Char]` vs `Text` - so the `IsString` thing is just the same consequence. I'd view this as a bug fix (overloaded strings should imply even generated strings are overloaded, if they are passed to user-controlled functions), but happy to go through GHC proposal process. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I'd view this as a bug fix (overloaded strings should imply even generated strings are overloaded, if they are passed to user-controlled functions), but happy to go through GHC proposal process.
Ah, now that is a much solider point! Thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): BTW, I'm happy to get the work done, if there's acceptance that it really is a bug, and what it should do. Implementation notes follow (only read them if we're agreed it is a bug, if not I'll transfer them to a proposal). There's still an open question of whether the `fromString` is injected only when you have `OverloadedStrings` and `RebindableSyntax` (and thus a user-controlled `fail`), or always for `OverloadedStrings` - my view is likely only when both are enabled. This would then be consistent with not desugaring pattern matches to `fromString`, since `patError` isn't user- controlled. My fix would be that `getFailFunction` and `failFunction` in `RnExpr.hs` should be changed so that if `OverloadedStrings` is enabled then the `fail_op` would be `fail . fromString` rather than just `fail` as it is now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The notes look ok to me. I do think a (small) proposal is the right way to proceed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): Proposal raised at https://github.com/ghc-proposals/ghc-proposals/pull/168 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => GHCProposal -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: shayne- | fletcher-da Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by shayne-fletcher-da): * owner: (none) => shayne-fletcher-da -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: shayne- | fletcher-da Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D5251 Wiki Page: | -------------------------------------+------------------------------------- Changes (by NeilMitchell): * differential: => D5251 Comment: Proposal was accepted. Patch submitted at https://phabricator.haskell.org/D5251 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: shayne- | fletcher-da Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5251 Wiki Page: | -------------------------------------+------------------------------------- Changes (by potato44): * differential: D5251 => Phab:D5251 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: shayne- | fletcher-da Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5251 Wiki Page: | -------------------------------------+------------------------------------- Comment (by shayne-fletcher-da): Updated revision to Diff 18486. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: shayne- | fletcher-da Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5251 Wiki Page: | -------------------------------------+------------------------------------- Changes (by NeilMitchell): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and
OverloadedStrings
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner: shayne-
| fletcher-da
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords: GHCProposal
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D5251
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#15645: TypeChecking of Monad patterns incorrect with RebindableSyntax and OverloadedStrings -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: shayne- | fletcher-da Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5251 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: 8.6.1 => 8.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15645#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC