[GHC] #11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications

GHC ghc-devs at haskell.org
Sat Apr 16 21:33:16 UTC 2016


#11947: GHC mistakenly warns about type defaulting in the presence of
-XTypeApplications
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
  TypeApplications                   |
       Architecture:                 |   Type of failure:  Incorrect
  Unknown/Multiple                   |  warning at compile-time
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This code:

 {{{#!hs
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeApplications #-}
 module Main (main) where

 theFloatDigits :: forall a. RealFloat a => Int
 theFloatDigits = floatDigits (undefined @_ @a)

 main :: IO ()
 main = print (theFloatDigits @Double, theFloatDigits @Float)
 }}}

 erroneously produces this warning:

 {{{
 $ /opt/ghc/8.0.1/bin/runghc -Wall TheFloatDigits.hs

 TheFloatDigits.hs:6:19: warning: [-Wtype-defaults]
     • Defaulting the following constraint to type ‘Double’ RealFloat a0
     • In the ambiguity check for ‘theFloatDigits’
       To defer the ambiguity check to use sites, enable
 AllowAmbiguousTypes
       In the type signature:
         theFloatDigits :: forall a. RealFloat a => Int
 (53,24)
 }}}

 GHC's claim that `a0` was defaulted to `Double` is clearly bogus, since
 `theFloatDigits` outputs different answers for `Double` and `Float`.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11947>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list