[GHC] #8109: Type family patterns should support as-patterns.

#8109: Type family patterns should support as-patterns. ------------------------------------+------------------------------------- Reporter: carlhowells | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- I recently wrote code similar to the following: {{{ {-# LANGUAGE DataKinds, ScopedTypeVariables, TypeOperators, TypeFamilies #-} {-# LANGUAGE PolyKinds, FlexibleInstances, FlexibleContexts #-} import GHC.TypeLits data P n = P fromNat :: forall (p :: Nat -> *) (n :: Nat). SingI n => p n -> Integer fromNat _ = fromSing (sing :: Sing n) class C (a :: [Nat]) where type T a :: * val :: p a -> T a instance SingI n => C '[n] where type T '[n] = Integer val _ = fromNat (P :: P n) instance (SingI n, C (n2 ': ns)) => C (n ': n2 ': ns) where type T (n ': n2 ': ns) = (Integer, T (n2 ': ns)) val _ = (fromNat (P :: P n), val (P :: P (n2 ': ns))) }}} There were semantic constraints in my case that made an empty list nonsensical, so it wasn't an appropriate base case. But the resulting effort in ensuring type family patterns didn't overlap got unwieldy. I would have much preferred to write that second instance more like this: {{{ instance (SingI n, C ns) => C (n ': ns@(_ ': _)) where type T (n ': ns) = (Integer, T ns) val _ = (fromNat (P :: P n), val (P :: P ns)) }}} The reasoning here is identical to as-patterns in value-level pattern matching. If you only want to match an expression when it has a particular sub-structure, it's way more convenient to do it with an as-pattern. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------ Reporter: carlhowells | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by aavogt): * cc: vogt.adam@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------- Reporter: | Owner: carlhowells | Status: new Type: feature | Milestone: request | Version: 7.6.3 Priority: normal | Keywords: Component: Compiler | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): See also example at #9608, which is a duplicate of this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------- Reporter: | Owner: carlhowells | Status: new Type: feature | Milestone: request | Version: 7.6.3 Priority: normal | Keywords: newcomer Component: Compiler | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: | None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by jstolarek): * keywords: => newcomer -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------- Reporter: carlhowells | Owner: qnikst Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by qnikst): * owner: => qnikst -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------- Reporter: carlhowells | Owner: qnikst Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): qnikst: any progress? Please ask if you need help with anything, or unassign yourself if you don't plan to work on this ticket anymore. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------- Reporter: carlhowells | Owner: qnikst Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by qnikst): @thomie, still working I'm planning to invest more time into this ticket after this weekend. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------- Reporter: carlhowells | Owner: qnikst Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: newcomer, | TypeFamilies 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 ThrashAbaddon): * cc: ThrashAbaddon (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8109: Type family patterns should support as-patterns. -------------------------------------+------------------------------------- Reporter: carlhowells | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: newcomer, | TypeFamilies 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 qnikst): * owner: qnikst => (none) Comment: Seems, I have neither a good understanding on how to implement this ticket, nor enough time to pass through all changes in the parser and further, so if anyone would like to solve this one - feel free to. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8109#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC