[GHC] #11671: Allow labels starting with uppercase with OverloadedLabels

#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program {{{#!hs {-# LANGUAGE OverloadedLabels, DataKinds, FlexibleInstances, MultiParamTypeClasses #-} import GHC.OverloadedLabels instance IsLabel "Three" Int where fromLabel _ = 3 test :: Int test = #Three main :: IO () main = print test }}} fails to compile in ghc 8.0 with a parse error (while it works as expected if we replace "Three" -> "three"). This may be a conscious design decision, but if not I figured I would ask if it would be possible to allow such labels starting with uppercase letters. I run into this when working on adding support for OverloadedLabels to the gobject-introspection bindings (autogenerated bindings for gtk, etc.), where it would be natural in a few places to write overloaded labels starting with a capital letter. Not hugely important, but sometimes aesthetically more pleasing (imho), and I am not aware of a good reason to forbid them. Perhaps there is one? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) * keywords: => ORF * component: Compiler => Compiler (Parser) Comment: This is simply because overloaded labels are lexed similarly to variables after the initial `#`. I don't think there is a fundamental reason we couldn't permit uppercase letters here, it would just require a bit of lexer hacking. That said, the original motivation for overloaded labels came from record fields, where the initial letter must be lowercase. So I'm two minds as to whether this is worthwhile or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Just to elaborate on my motivation for asking this: in bindings to C libraries (say gtk), due to the requirement of uniqueness of identifiers, one ends up with rather long identifiers for constants, which are typically represented by different constructors for a certain sum type. See for example: https://hackage.haskell.org/package/gtk-0.14.2/docs/Graphics-UI-Gtk- General-Enums.html#t:TreeViewColumnSizing It would be much more convenient to be able to say {{{#!hs treeViewColumnSetSizing tvc #Fixed }}} rather than the current, much more verbose {{{#!hs treeViewColumnSetSizing tvc TreeViewColumnFixed }}} The former is just as typesafe, but much more pleasant to read and use, I think, and here it is fairly natural to expect the overloaded label to start with uppercase. It can just as easily be made to work with lowercase, but I think that from the point of view of the user of the library the version starting with uppercase is more natural. (As a side remark: the above is still unnecessarily verbose, with further use of OverloadedLabels we can shorten it to {{{#!hs set tvc [#sizing := #Fixed] }}} which is close to Python levels of convenience, while being perfectly type safe. This already works well in the haskell-gi autogenerated bindings for gtk, only that I need to replace `#Fixed` -> `#fixed` due to the parser limitation.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Thanks for expanding on your use case! I think you've convinced me that overloaded labels can just as well be used for overloading constructors as overloading field names, and hence it makes sense to allow the initial uppercase letter. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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): Ah, there is actually already #11350 open about the parse failure above. But even if the above works I am not sure how to use the construction above to deal with cases like `#Just True`, say (i.e. overloaded constructors that take arguments). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 mpickering): If you want these values to actually look like constructors then have you tried using pattern synonyms? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Replying to [comment:6 mpickering]:
If you want these values to actually look like constructors then have you tried using pattern synonyms?
Yes, indeed, that is what I do now. (For context, this is for https://github.com/haskell-gi/haskell-gi , a set of autogenerated libraries for a number of libraries in the gtk ecosystem.) The following works beautifully: {{{#!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 Truish :: IsOverloadedPattern "Truish" a => a pattern Truish <- ((checkOverloadedPattern @"Truish") -> True) where Truish = buildOverloadedPattern @"Truish" data Statement = Provable | Refutable instance IsOverloadedPattern "Truish" Statement where checkOverloadedPattern Provable = True checkOverloadedPattern Refutable = False buildOverloadedPattern = Provable test :: Statement -> Int test Truish = 42 test _ = -1 main :: IO () main = print (test Truish) }}} The problem is that this requires one pattern for each constructor one wants to overload in this way. Which are quite a few hundred/thousand for a large library like gtk (or glib, webkit, etc.). Not an issue in itself, but we cannot ask the user of the library to write them by hand, they should be automatically in the namespace when importing `GI.Gtk` or any other autogenerated binding. And we cannot bundle this with the library directly, since patterns with the same name may be easily generated by different autogenerated libraries, giving rise to name clashes. The way we solve it now is by asking the user of the library to run some command such that all possible such patterns, for all libraries used in the project, are generated in advance, and compiled into a single module. The resulting module should then be compiled as part of the users's project. Which works, but it is clunky. In similar situations (overloaded property names and overloaded signals) we can do away completely with this somewhat annoying "overloading module" by using OverloadedLabels, but I don't currently see a way of doing the same thing allowing to pattern match against the overloaded symbols. The construction in #comment:4 comes close, perhaps it can be made to work somehow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): I should add one point: some of the possible constructors that we want to overload can be fairly generic words (`Nothing`, for instance, is one). Having the `#` character in front helps a lot in here, since it makes the distinction between `Nothing` (constructor of `Maybe a` type) and `#Nothing` (some pattern to be resolved depending on the usage location). So creating patterns explicitly easily leads to name clashes with ordinary constructors. To avoid this currently we add a final underscore (`Nothing` -> `Nothing_`), but this final underscore is easy to forget, and not that nice as a solution. Having a OverloadedLabels style solution would be much nicer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

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

#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 simonpj): There are two things going on here * Allowing uppper-case names for overloaded labels. This sounds plausible to me, although I have not thought through the consequences. * Some form of overloading for pattern matching, building on pattern synonyms. Certainly sounds interesting, but should really have its own ticket and wiki page. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

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
There are two things going on here
* Allowing uppper-case names for overloaded labels. This sounds
#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): Replying to [comment:9 adamgundry]: particular, I've lowercased the label names): Clever :) Replying to [comment:10 simonpj]: plausible to me, although I have not thought through the consequences.
* Some form of overloading for pattern matching, building on pattern
synonyms. Certainly sounds interesting, but should really have its own ticket and wiki page. Indeed! I thought it may be an straightforward feature request, but now I am not sure. Honestly, the realization that they cannot be (straightforwardly) pattern matched against removes quite a bit of my original motivation (detailed in comment:2) for asking this. So the fact that they are not really patterns may make it a good thing that they cannot start by uppercase, so one is not tempted to match against them. In any case I can certainly file a new ticket with the feature request for "OverloadedPatterns", if you think that's useful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by jplatte): * cc: jplatte (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) 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: | -------------------------------------+------------------------------------- Changes (by glaebhoerl): * cc: glaebhoerl (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) 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: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) 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 dwincort): Just to bump this, I also have a use case for labels starting with uppercase letters. Specifically, in the same way that overloaded labels have been used for record field selectors (lenses), my group is trying to use ones that start with uppercase letters for constructor selectors (prisms). Although the ability to use them in patterns would be great, this is truly a separate issue, and we have uses for just the prisms (for example, as handlers in the foldl package [https://hackage.haskell.org/package/foldl]). Right now, we have a hack where overloaded labels starting with `_` are treated as prisms, and we write, e.g., `#_Foo` to get the prism for the constructor `Foo`. Not only is this ugly, but it means that any record fields starting with `_` are turned into prisms instead of lenses. Having labels that can start with uppercase letters would fix this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) 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 echatav): I also have a use case for labels starting with uppercase letters. It would be extremely helpful for supporting PostgreSQL enum types which are compatible with Haskell enum types in Squeal (https://hackage.haskell.org/package/squeal-postgresql). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) 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 osa1): There's a patch for this feature but it needs to go through the proposal process: https://github.com/ghc/ghc/pull/192 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11671: Allow labels starting with uppercase with OverloadedLabels -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 (Parser) | Keywords: ORF, Resolution: | GHCProposal 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): * keywords: ORF => ORF, GHCProposal -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11671#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC