[GHC] #13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings

GHC ghc-devs at haskell.org
Sat Jun 3 23:06:55 UTC 2017


#13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Poor/confusing
  Unknown/Multiple                   |  error message
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I originally observed this issue in the `parsers` library. Here's a
 minimal example:

 {{{#!hs
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# OPTIONS_GHC -Wmonomorphism-restriction #-}
 module Bug where

 class Monad m => C m where
   c :: (m Char, m Char)

 foo :: forall m. C m => m Char
 foo = bar >> baz
   where
     (bar, baz) = c
 }}}

 If you compile this with a GHC that supports `-Wmonomorphism-restriction`
 (GHC 8.0.1 or later), it'll rightfully give this warning:

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

 Bug.hs:11:5: warning: [-Wmonomorphism-restriction]
     • The Monomorphism Restriction applies to the bindings for ‘bar’,
                                                                ‘baz’
         Consider giving a type signature for these binders
     • In an equation for ‘foo’:
           foo
             = bar >> baz
             where
                 (bar, baz) = c
    |
 11 |     (bar, baz) = c
    |     ^^^^^^^^^^^^^^
 }}}

 Naturally, I tried to squelch this warning by adding type signatures for
 `bar` and `baz`:

 {{{#!hs
 foo :: forall m. C m => m Char
 foo = bar >> baz
   where
     bar, baz :: m Char
     (bar, baz) = c
 }}}

 But GHC //still// warns!

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

 Bug.hs:12:5: warning: [-Wmonomorphism-restriction]
     • The Monomorphism Restriction applies to the bindings for ‘bar’,
                                                                ‘baz’
         Consider giving a type signature for these binders
     • In an equation for ‘foo’:
           foo
             = bar >> baz
             where
                 bar, baz :: m Char
                 (bar, baz) = c
    |
 12 |     (bar, baz) = c
    |     ^^^^^^^^^^^^^^
 }}}

 And to make things even more absurd, GHC points out a chunk of code which
 //has// type signatures :)

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


More information about the ghc-tickets mailing list