[GHC] #11461: Allow pattern synonyms to be bundled with type classes?

#11461: Allow pattern synonyms to be bundled with type classes? -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- One can very nearly get associated pattern synonyms by defining suitably polymorphic pattern synonyms. However, they are not quite associated as there's no way to bundle them with the class. This isn't as good as "proper" support but it would be an easy thing to implement for now if people think it worthwhile. For a concrete example, `Null` is an associated pattern synonym in this style but the following program doesn't compile because it is disallowed to bundle a pattern synonym with a type class. {{{ {-# LANGUAGE PatternSynonyms #-} module Foo(Nullable(Null)) where import Data.Maybe class Nullable f where null :: f a -> Bool instance Nullable (Maybe a) where null = isNothing pattern Null :: Nullable f => f a pattern Null = (null -> True) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11461 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11461: Allow pattern synonyms to be bundled with type classes? -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternSynonyms 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 Iceland_jack): How does this relate to #8583? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11461#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11461: Allow pattern synonyms to be bundled with type classes? -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternSynonyms 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 Iceland_jack): Did you mean {{{#!hs instance Nullable Maybe where null = isNothing pattern Null :: Nullable f => f a pattern Null <- (null -> True) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11461#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11461: Allow pattern synonyms to be bundled with type classes? -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by hvr: @@ -11,1 +11,1 @@ - {{{ + {{{#!hs New description: One can very nearly get associated pattern synonyms by defining suitably polymorphic pattern synonyms. However, they are not quite associated as there's no way to bundle them with the class. This isn't as good as "proper" support but it would be an easy thing to implement for now if people think it worthwhile. For a concrete example, `Null` is an associated pattern synonym in this style but the following program doesn't compile because it is disallowed to bundle a pattern synonym with a type class. {{{#!hs {-# LANGUAGE PatternSynonyms #-} module Foo(Nullable(Null)) where import Data.Maybe class Nullable f where null :: f a -> Bool instance Nullable (Maybe a) where null = isNothing pattern Null :: Nullable f => f a pattern Null = (null -> True) }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11461#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11461: Allow pattern synonyms to be bundled with type classes? -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternSynonyms 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 rwbarton): Probably obvious to the pattern synonym cognoscenti but you can change the export list to {{{ module Foo(Nullable, pattern Null) where }}} and use this style today. The disadvantages relative to "real" associated patterns are * no association between the class and the pattern as far as import/export is concerned * you have to give a single top-level definition of the pattern synonym, and do the per-instance work in an auxiliary function. I think you can always do this at negligible cost (other than syntactic noise). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11461#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11461: Allow pattern synonyms to be bundled with type classes? -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11461#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC