[GHC] #16385: Lousy error message for `instance forall c. c`

GHC ghc-devs at haskell.org
Mon Mar 4 14:42:19 UTC 2019


#16385: Lousy error message for `instance forall c. c`
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.3
           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:
-------------------------------------+-------------------------------------
 This erroneous program is rejected with a rather strange error message:

 {{{#!hs
 {-# LANGUAGE ScopedTypeVariables #-}
 module Bug where

 instance forall c. c
 }}}
 {{{
 $ /opt/ghc/8.6.3/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:4:20: error: Not in scope: type variable ā€˜cā€™
   |
 4 | instance forall c. c
   |                    ^
 }}}

 This error message is hogwash, since `c` is absolutely in scope. The
 reason GHC believes that `c` is out of scope is because before GHC renamed
 the type signature in the instance, it performs a pass over all top-level
 binders in `RnNames.getLocalNonValBinders` to obtain their `Name`s. In
 particular,
 [https://gitlab.haskell.org/ghc/ghc/blob/473632d7671619ee08a2a0025aa22bd4f79eca2d/compiler/rename/RnNames.hs#L734-743
 this] is the culprit:

 {{{#!hs
     new_assoc overload_ok (L _ (ClsInstD _ (ClsInstDecl { cid_poly_ty =
 inst_ty
                                                       , cid_datafam_insts
 = adts })))
       | Just (L loc cls_rdr) <- getLHsInstDeclClass_maybe inst_ty
       = do { cls_nm <- setSrcSpan loc $ lookupGlobalOccRn cls_rdr
            ; (avails, fldss)
                     <- mapAndUnzipM (new_loc_di overload_ok (Just cls_nm))
 adts
            ; return (avails, concat fldss) }
       | otherwise
       = return ([], [])    -- Do not crash on ill-formed instances
                            -- Eg   instance !Show Int   Trac #3811c
 }}}

 Notice the use of `lookupGlobalOccRn` there. Since this code just tunnels
 into the instance type signature (using `getLHsInstDeclClass_maybe`)
 without binding any type variables, this calls `lookupGlobalOcc` on an
 unbound type variable `c`. Eek.

 I believe the fix would be to use `lookupGlobalOccRn_maybe` instead and
 simply default to `return ([], [])` in the event that
 `lookupGlobalOccRn_maybe` returns Nothing.

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


More information about the ghc-tickets mailing list