[GHC] #11671: Allow labels starting with uppercase with OverloadedLabels
GHC
ghc-devs at haskell.org
Fri Mar 4 22:12:32 UTC 2016
#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 inaki):
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
pattern match on these overloaded constructors. Simply desugaring to
`fromLabel ...` seems to preclude this from working.
Just for fun, I tried to come up with a desugaring that allows for pattern
matching too, but I encountered a parsing problem when trying to
explicitly apply types in a pattern, the following is the closest I could
get:
{{{#!hs
{-# LANGUAGE DataKinds, FlexibleInstances,
MultiParamTypeClasses,
PatternSynonyms, ViewPatterns, ScopedTypeVariables, KindSignatures,
TypeApplications #-}
import GHC.TypeLits
class IsOverloadedPattern (tag :: Symbol) (a :: *) where
checkOverloadedPattern :: a -> Bool
buildOverloadedPattern :: a
pattern OverloadedPattern :: forall tag a. IsOverloadedPattern (tag ::
Symbol) a => a
pattern OverloadedPattern <- ((checkOverloadedPattern @tag @a) -> True)
where
OverloadedPattern = buildOverloadedPattern @tag @a
data Statement = Provable | Refutable
instance IsOverloadedPattern "Truish" Statement where
checkOverloadedPattern Provable = True
checkOverloadedPattern Refutable = False
buildOverloadedPattern = Provable
{-
-- We would like to write something like:
test :: Statement -> Int
test #Truish = 42
test _ = -1
-- desugaring to
test :: Statement -> Int
test (OverloadedPattern @"Truish") = 42
test _ = -1
-}
test2 :: Statement -> Int
test2 Provable = 42
test2 _ = -1
main :: IO ()
main = print (test2 (OverloadedPattern @"Truish"))
}}}
One may also worry how to pattern match on multi-parameter constructors,
which is not supported by the construction above. Perhaps there is some
clever way of making overloaded constructors work everywhere a normal
constructor would work? I guess that if #8583 was implemented we could use
that?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11671#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list