[GHC] #11460: OverloadedStrings cause error in annotation

#11460: OverloadedStrings cause error in annotation -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Linux Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code {{{#!hs {-# LANGUAGE OverloadedStrings #-} {-# ANN module "HLint: ignore Eta reduce" #-} main = putStrLn "hello" }}} results in {{{ /tmp/Foo.hs:3:1: No instance for (Data.Data.Data a0) arising from an annotation The type variable ‘a0’ is ambiguous Note: there are several potential instances: instance (Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Either a b) -- Defined in ‘Data.Data’ instance Data.Data.Data t => Data.Data.Data (Data.Proxy.Proxy t) -- Defined in ‘Data.Data’ instance (GHC.Types.Coercible a b, Data.Data.Data a, Data.Data.Data b) => Data.Data.Data (Data.Type.Coercion.Coercion a b) -- Defined in ‘Data.Data’ ...plus 31 others In the annotation: {-# ANN module "HLint: ignore Eta reduce" #-} /tmp/Foo.hs:3:16: No instance for (Data.String.IsString a0) arising from the literal ‘"HLint: ignore Eta reduce"’ The type variable ‘a0’ is ambiguous Note: there is a potential instance available: instance Data.String.IsString [Char] -- Defined in ‘Data.String’ In the annotation: {-# ANN module "HLint: ignore Eta reduce" #-} }}} when using GHC 7.10.3, and similar for GHC 8 RC -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11460 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11460: OverloadedStrings cause error in annotation -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): This is actually expected. An annotation can be of any data type; I quote
Any expression that has both Typeable and Data instances may be attached to a top-level value binding using an ANN pragma.
So the error message is fine. The work-around is to add `::String` afterwards. Or is there a version of GHC that behaved differently? No one could see this ticket as a request to make this a bit more smooth, e.g. by defaulting to `String` within an `ANN` or something. Is it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11460#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11460: OverloadedStrings cause error in annotation -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alanz): In the parser, we have {{{ aexp2 :: { LHsExpr RdrName } : qvar { sL1 $1 (HsVar $! $1) } | qcon { sL1 $1 (HsVar $! $1) } | ipvar { sL1 $1 (HsIPVar $! unLoc $1) } | overloaded_label { sL1 $1 (HsOverLabel $! unLoc $1) } | literal { sL1 $1 (HsLit $! unLoc $1) } -- This will enable overloaded strings permanently. Normally the renamer turns HsString -- into HsOverLit when -foverloaded-strings is on. -- | STRING { sL (getLoc $1) (HsOverLit $! mkHsIsString (getSTRINGs $1) -- (getSTRING $1) placeHolderType) } }}} The annotation expression in this case is parsed as a `HsString`, and the comment seems to indicate that the renamer should be making the `HsString` into an `HsOverLit` when `OverloadedStrings` is active, which I suspect is not happening. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11460#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11460: OverloadedStrings cause error in annotation -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => invalid Comment: Yes, it ''is'' an overloaded literal, so it desugars to {{{ {-# ANN module (fromString ("HLint: ignore Eta reduce" :: String)) #-} }}} The return type of `fromString` is ambiguous, as GHC says. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11460#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC