[GHC] #13159: Allow visible type application with pattern synonyms in patterns

#13159: Allow visible type application with pattern synonyms in patterns -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #13158 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Somewhat related to #13158, it would be nice if pattern synonyms allowed visible type application with the `TypeApplications` extension enabled. This would obviously be tricky due to the existing meaning of `@` in patterns, though I think it would technically be unambiguous here. Still, I’d understand if you didn’t want to complicate the parser that much further. The motivator, though, is that it would be nice to be able to write pattern synonyms with ambiguous types an explicitly instantiate them, for the same reason type applications are useful for terms. As mentioned in #13158, this would permit writing a pattern synonym to emulate case analysis on types: {{{#!hs {-# LANGUAGE GADTs, PatternSynonyms, ScopedTypeVariables, TypeApplications, TypeOperators, ViewPatterns #-} import Data.Typeable viewEqT :: forall b a. (Typeable a, Typeable b) => a -> Maybe ((a :~: b), b) viewEqT x = case eqT @a @b of Just Refl -> Just (Refl, x) Nothing -> Nothing pattern EqT :: forall b a. (Typeable a, Typeable b) => (a ~ b) => b -> a pattern EqT x <- (viewEqT @b -> Just (Refl, x)) }}} If visible type applications were permitted in patterns, then such case analysis could be written like this: {{{#!hs evilId :: Typeable a => a -> a evilId (EqT @Int n) = n + 1 evilId (EqT @String str) = reverse str evilId x = x }}} …which I think looks relatively pleasant! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13159 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13159: Allow visible type application with pattern synonyms in patterns -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13158, #11350 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * related: #13158 => #13158, #11350 Comment: Very related to #11350, the ticket requesting type applications in patterns, in general. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13159#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13159: Allow visible type application with pattern synonyms in patterns -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13158, #11350 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I think this, #13158 and #11350 should all be considered the same as each other. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13159#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13159: Allow visible type application with pattern synonyms in patterns -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13158, #11350 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I think #13158 is not fundamentally related here, except as motivation. Perhaps this could be combined with #11350. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13159#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13159: Allow visible type application with pattern synonyms in patterns -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13158, #11350 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => duplicate Comment: Yes, my mistake. I will close this as a duplicate. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13159#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC