
Thinking more about this, I came up with a small worry: having such overloaded constructors makes it very tempting to ask if it is possible to
#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 (Parser) | Resolution: | Keywords: ORF 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 adamgundry): pattern match on these overloaded constructors. Interesting point! Various people have been telling me I should think about overloaded constructors, and perhaps I should have done so before now... I played around with your example a bit and came up with the following construction, which isn't the most beautiful but works in GHC 8.0 (so in particular, I've lowercased the label names): {{{#!hs {-# LANGUAGE DataKinds, FlexibleInstances, MultiParamTypeClasses, ViewPatterns, ScopedTypeVariables, KindSignatures, TypeApplications, OverloadedLabels, TypeFamilies, FunctionalDependencies #-} import GHC.TypeLits import GHC.OverloadedLabels data Statement = Provable | Refutable deriving Show class IsPattern (tag :: Symbol) a r | tag a -> r where checkPattern :: a -> Maybe r instance IsPattern tag a r => IsLabel tag (a -> Maybe r) where fromLabel _ = checkPattern @tag instance IsPattern "truish" Statement () where checkPattern Provable = Just () checkPattern Refutable = Nothing instance IsLabel "truish" Statement where fromLabel _ = Provable test :: Statement -> Int test (#truish -> Just ()) = 42 test _ = -1 x = test #truish }}} This extends to constructors with arguments, after a fashion: {{{#!hs instance IsPattern "truthiness" Statement (Int, Bool) where checkPattern Provable = Just (42, True) checkPattern Refutable = Nothing instance a ~ (Int, Bool) => IsLabel "truthiness" (a -> Statement) where fromLabel _ (42, True) = Provable fromLabel _ _ = Refutable test2 :: Statement -> Int test2 (#truthiness -> Just (k, _)) = k test2 _ = -1 y = test2 (#truthiness (42, True)) }}} A potential problem here is that the required `IsLabel` instances might conflict with "record field selector" instances. I suppose one way of dealing with that might be to desugar `#Foo` using a different class to `#foo`, but otherwise similarly. Though perhaps we should come up with a special desugaring for `#Foo` that works in patterns, as you suggest. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler