[GHC] #10875: Unexpected defaulting of partial type signatures and inconsistent behaviour when -fdefer-typed-holes is set.

GHC ghc-devs at haskell.org
Tue Sep 29 09:59:12 UTC 2015


#10875: Unexpected defaulting of partial type signatures and inconsistent behaviour
when -fdefer-typed-holes is set.
-------------------------------------+-------------------------------------
        Reporter:  holzensp          |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.10.2
      Resolution:                    |             Keywords:
                                     |  PartialTypeSignatures TypedHoles
Operating System:  MacOS X           |         Architecture:  x86_64
 Type of failure:  Incorrect         |  (amd64)
  warning at compile-time            |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
-------------------------------------+-------------------------------------

Comment (by holzensp):

 I found another interesting bit of behaviour, which I would argue is an
 error. Consider this program:

 {{{#!hs
 {-# LANGUAGE NoMonomorphismRestriction #-}
 {-# LANGUAGE PartialTypeSignatures #-}
 {-# LANGUAGE NamedWildCards #-}
 {-# LANGUAGE ImplicitParams #-}
 module Foo where

 foo :: _ => _outer
 foo = (+) ?a ?b ?c ?d
 }}}

 This produces the following output in GHCi:

 {{{
 [1 of 1] Compiling Foo              ( Foo.hs, interpreted )

 Foo.hs:7:8: Warning:
     Found hole ‘_’ with inferred constraints: (Num (t -> t -> w_outer),
                                                ?a::t -> t -> w_outer,
                                                ?b::t -> t -> w_outer,
                                                ?c::t,
                                                ?d::t)
     In the type signature for ‘foo’: _ => _outer

 Foo.hs:7:13: Warning:
     Found hole ‘_outer’ with type: w_outer
     Where: ‘w_outer’ is a rigid type variable bound by
                      the inferred type of
                      foo :: (Num (t -> t1 -> w_outer), ?a::t -> t1 ->
 w_outer,
                              ?b::t -> t1 -> w_outer, ?c::t, ?d::t1) =>
                             w_outer
                      at Foo.hs:8:1
     In the type signature for ‘foo’: _ => _outer
 Ok, modules loaded: Foo.
 }}}

 I would say the second warning is accurate, but in the first warning, the
 `t1` type variables are printed as `t`, which is too restrictive.
 Considering the validity of the second warning, I would say this is
 probably a ppr-bug.

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


More information about the ghc-tickets mailing list