[GHC] #14380: Compile error for PatternSynonyms together with OverloadedLists

#14380: Compile error for PatternSynonyms together with OverloadedLists -------------------------------------+------------------------------------- Reporter: lehins | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE PatternSynonyms #-} data Foo = Foo [Int] pattern Bar :: Foo pattern Bar = Foo [] }}} This code results in a cryptic compilation error: {{{ $ ghc main.hs [1 of 1] Compiling Main ( main.hs, main.o ) main.hs:7:19: error: • Couldn't match expected type ‘[a0] -> [Int]’ with actual type ‘[GHC.Exts.Item Int]’ • This rebindable syntax expects a function with two arguments, but its type ‘Int -> [GHC.Exts.Item Int]’ has only one In the first argument of ‘Foo’, namely ‘[]’ In the expression: Foo [] | 7 | pattern Bar = Foo [] | ^^ }}} As soon as `OverloadedLists` is removed, this error goes away. In itself the problem isn't too critical, but very unexpected. I got above error with GHC 8.0 and 8.2, so decided to check it with current version as well: {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.3.20171020 }}} Looking a bit more into `PatternSynonyms` extension I was able to work around this by declaring an explicit bidirectional pattern, which, surprisingly, solved the problem: {{{#!hs pattern Bar :: Foo pattern Bar <- Foo [] where Bar = Foo [] }}} If fixing this issue is too much trouble than it is worth, than at least a mention about it in documentation will be helpful. Out of curiosity I also tried it with `String`, which did not trigger this error and compiled just fine: {{{#!hs {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} data Foo = Foo [Char] pattern Bar :: Foo pattern Bar = Foo "" }}} PS. Even if this issue is closed, searching the internet for the error message will now at least return some info. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14380 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14380: Compile error for PatternSynonyms together with OverloadedLists -------------------------------------+------------------------------------- Reporter: lehins | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK, I know what is happening here. * The message is utterly bogus. * It arise because, with ''implicitly-bidirectional'' pattern synonyms, we have to translate a pattern into an expression. See `TcPatSyn` {{{ tcPatToExpr :: Name -> [Located Name] -> LPat GhcRn -> Either MsgDoc (LHsExpr GhcRn) }}} Note that this happens to a renamed, but not typechecked, pattern. * With rebindable syntax, a renamed list pattern `[p1, p2]`, implemented with `ListPat`, looks like {{{ ListPat [p1, p2] (Just toList) }}} where the `toList` is the name of the in-scope `toList` function. Matching on the pattern will call `toList` to convert the actual arg to a list, and match that list against `[p1, p2]` * But when converting a `ListPat` ''patttern'' to a to an `ExplicitList` ''expression'' we need `fromList` not `toList`!! Stupidly, `tcPatToExpr` just plops the `toList` in the `ExplicitList`. Wrong wrong. What do to? The typechecker (which is where `tcPatToExpr` is currently called) isn't really the right place to look up `fromList`, although it might be possible. E.g. the renamer would then not see this use of `fromList`, and hence perhaps complain about an unused import. I think the Right Thing is to move `tcPatToExpr` to the renamer, and which can look up that `fromList` just as it does the `toList`. To do that we'd need to alter `HsPatSynDir` thus {{{ data HsPatSynDir id = Unidirectional | ImplicitBidirectional (PostRn (LHsExpr id)) | ExplicitBidirectional (MatchGroup id (LHsExpr id)) }}} This adds a `LHsExpr` field to `ImplicitBidirectional`, the result of doing that conversion. I suppose that `tcPatToExpr` would then become monadic so that it can look up `fromList`. And then it can report errors rather than returning them in an `Either`. Would anyone like to try this? Meanwhile, I think I'll just reject programs that use implicitly- bidirectional syntax with overloaded lists, pointing to this ticket so that users can yell if it happens. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14380#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14380: Compile error for PatternSynonyms together with OverloadedLists
-------------------------------------+-------------------------------------
Reporter: lehins | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC