[GHC] #11176: Typechecked AST for recursive top-level call refers to non-exported HsVar.

GHC ghc-devs at haskell.org
Tue Dec 8 08:48:58 UTC 2015


#11176: Typechecked AST for recursive top-level call refers to non-exported HsVar.
-------------------------------------+-------------------------------------
           Reporter:  literon        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Code:
 {{{#!hs
 module B where

 aaa x = aaa x

 bbb = aaa 1
 }}}

 === In the renamed AST

 The reference is to the exported aaa (span 3:1-3, sort WiredIn), which is
 as expected (by me at least).
 (dump with ghc-dump-tree with some local mods compiled by GHC 7.10.2)

 {{{
                                       (HsApp
                                               (L /tmp/B.hs:3:9-11
                                                  (HsVar
                    here ------------>    { n_loc = /tmp/B.hs:3:1-3
 <----------- here
                                                       , n_sort =  {
 WiredIn = Module main B }
                                                       , VarName = aaa
                                                       }))
                                               (L /tmp/B.hs:3:13
                                                  (HsVar
                                                       { n_loc =
 /tmp/B.hs:3:5
                                                       , n_sort = Internal
                                                       , VarName = x
                                                       })))))
 }}}

 === In the typechecked AST

 Here the call target changes to internal (as described by the monomorphic
 binding abe_mono).

 {{{
 (HsApp
                                              (L /tmp/B.hs:3:9-11
                                                 (HsVar
                                                      { varType =
                                                            { t -> t =
                                                                FunTy
                                                                  (TyVarTy
                                                                       {
 varType =
 { * = TyConApp * [] }
                                                                       ,
 n_loc = /tmp/B.hs:3:1-13
                                                                       ,
 n_sort = Internal
                                                                       ,
 TvName = t
                                                                       })
                                                                  (TyVarTy
                                                                       {
 varType =
 { * = TyConApp * [] }
                                                                       ,
 n_loc = /tmp/B.hs:3:1-13
                                                                       ,
 n_sort = Internal
                                                                       ,
 TvName = t
                                                                       })
                                                            }
                  here ------------->   , n_loc = /tmp/B.hs:3:1-13
                                                      , n_sort = Internal
                                                      , VarName = aaa
                                                      }))
                                              (L /tmp/B.hs:3:13
                                                 (HsVar
                                                      { varType =
                                                            { t =
                                                                TyVarTy
                                                                    {
 varType =
                                                                         {
 * = TyConApp * [] }
                                                                    , n_loc
 = /tmp/B.hs:3:1-13
                                                                    ,
 n_sort = Internal
                                                                    ,
 TvName = t
                                                                    }
                                                            }
                                                      , n_loc =
 /tmp/B.hs:3:5
                                                      , n_sort = Internal
                                                      , VarName = x
                                                      })))))
 }}}

 (Just remarking, that GHC 7.8 and 7.10 seem to have improved the span
 ranges a bit over 7.6, so trying to reproduce with 7.6 the span will be
 the shorter one on the function name, but the sort will still be the
 internal).

 Note that referring the function in a non-recursive way seem to refer to
 the exported (abe_poly) binding.

 From the perspective of a tooling writer, this difference is somewhat
 surprising, and is a case to be handled separately.

   * Is there a fundamental reason why the reference changes after
 Typechecking?

   * Since I'm not deeply familiar with the AST, I might miss something.
 Does it happen in other cases too that sometimes abe_poly is referred,
 sometimes the abe_mono? If so, what is the rule?

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


More information about the ghc-tickets mailing list