[GHC] #11460: OverloadedStrings cause error in annotation

GHC ghc-devs at haskell.org
Tue Jan 19 11:52:03 UTC 2016


#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


More information about the ghc-tickets mailing list