[GHC] #8233: Type environment when reporting holes

GHC ghc-devs at haskell.org
Thu Sep 5 17:07:37 CEST 2013


#8233: Type environment when reporting holes
-------------------------------------+-------------------------------------
       Reporter:  monoidal           |             Owner:
           Type:  bug                |            Status:  new
       Priority:  normal             |         Milestone:
      Component:  Compiler (Type     |           Version:  7.7
  checker)                           |  Operating System:  Unknown/Multiple
       Keywords:                     |   Type of failure:  Incorrect
   Architecture:  Unknown/Multiple   |  warning at compile-time
     Difficulty:  Unknown            |         Test Case:
     Blocked By:                     |          Blocking:
Related Tickets:  #8191              |
-------------------------------------+-------------------------------------
 This is a sequel to #8191. Consider

 {{{
 {-# LANGUAGE TypeHoles #-}

 u1 = 0
 u2 = 0
 u3 = 0
 u4 = 0
 u5 = 0
 u6 = 0

 f :: a -> (a -> b) -> b
 f x y = _b

 v1 = 0
 v2 = 0
 v3 = 0
 v4 = 0
 v5 = 0
 v6 = 0
 }}}

 Compile with `-fno-max-relevant-binds` and see

 {{{
     Relevant bindings include
       v6 :: a0 (bound at THoles.hs:18:1)
       v5 :: a1 (bound at THoles.hs:17:1)
       v4 :: a2 (bound at THoles.hs:16:1)
       v3 :: a3 (bound at THoles.hs:15:1)
       v2 :: a4 (bound at THoles.hs:14:1)
       v1 :: a5 (bound at THoles.hs:13:1)
       f :: a -> (a -> b) -> b (bound at THoles.hs:11:1)
       x :: a (bound at THoles.hs:11:3)
       y :: a -> b (bound at THoles.hs:11:5)
 }}}

 The list is inverted: `v6` is first, while it was last. If we do not use
 `-fno-max-relevant-binds` then local parameters `x` and `y` are not
 visible at all, but they are the most important data.

 Another aspect is that we see `v1, v2` but not `u1, u2`. I'm not sure what
 is a good solution here. Display everything? Only N bindings above `f` and
 N bindings below `f`? People usually write code top to bottom, so
 preceding bindings should be more useful in general than following ones.

 I think this case deserves some attention because it will often occur in
 practice (putting a hole in any large file).

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




More information about the ghc-tickets mailing list