[GHC] #11352: Allow applying type to label

#11352: Allow applying type to label -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE DataKinds #-} import GHC.TypeLits import GHC.OverloadedLabels instance IsLabel "answer" Int where fromLabel _ = 42 answer :: IsLabel "answer" a => a answer = #answer }}} The follow works: {{{#!hs
answer @Int 42 }}}
but fails with a label: {{{#!hs
#answer @Int <interactive>:...:1: error: • Cannot not apply expression of type ‘t0’ to a visible type argument ‘Int’ • In the expression: #answer @Int In an equation for ‘it’: it = #answer @Int }}}
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11352 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11352: Allow applying type to label -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: adamgundry Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * owner: => adamgundry * keywords: => ORF * version: 7.10.3 => 7.11 * component: Compiler => Compiler (Type checker) * failure: None/Unknown => GHC rejects valid program Comment: I don't see any reason why this shouldn't work, I suspect the overloaded labels implementation just needs a bit of re-organization now that visible type application is implemented. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11352#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11352: Allow applying type to label -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * owner: adamgundry => Comment: Hmm, this isn't as straightforward as I thought. We could change the type of `fromLabel` to be `forall x a . IsLabel x a => a`, and then implement `#answer` by replacing it with `fromLabel @"answer"`. That gives you the behaviour you want, but it means that error messages mention applications of `fromLabel`, e.g. {{{ Could not deduce (IsLabel "y" t) arising from the overloaded label ‘#y’ }}} becomes {{{ Could not deduce (IsLabel "y" t) arising from a use of ‘fromLabel’ }}} which is somewhat undesirable. Moreover, overloaded string/numeric literals are similarly incompatible with visible type application. So I'm inclined to leave things as they are: after all, you can always write `#answer :: Int`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11352#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11352: Allow applying type to label -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11409 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * related: => #11409 Comment: See also #11409, the corresponding ticket for numeric literals, in which Simon observes that it's possible to use an auxiliary definition instead of changing the type of `fromLabel`. Although it might still make sense to do the latter, now that we have type application, rather than have a `Proxy#` argument that is unnecessary. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11352#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11352: Allow applying type to label -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: ORF, Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11409 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: ORF => ORF, TypeApplications -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11352#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11352: Allow applying type to label -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: isovector Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: ORF, Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11409 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by isovector): * owner: (none) => isovector -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11352#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC