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

#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

#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 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm surprised that `n_sort` is `WiredIn` for `aaa`. That is most peculiar. Did you read `Note [AbsBinds]` in `HsBinds`? {{{ Note [AbsBinds] ~~~~~~~~~~~~~~~ The AbsBinds constructor is used in the output of the type checker, to record *typechecked* and *generalised* bindings. Consider a module M, with this top-level binding M.reverse [] = [] M.reverse (x:xs) = M.reverse xs ++ [x] In Hindley-Milner, a recursive binding is typechecked with the *recursive* uses being *monomorphic*. So after typechecking *and* desugaring we will get something like this M.reverse :: forall a. [a] -> [a] = /\a. letrec reverse :: [a] -> [a] = \xs -> case xs of [] -> [] (x:xs) -> reverse xs ++ [x] in reverse Notice that 'M.reverse' is polymorphic as expected, but there is a local definition for plain 'reverse' which is *monomorphic*. The type variable 'a' scopes over the entire letrec. That's after desugaring. What about after type checking but before desugaring? That's where AbsBinds comes in. It looks like this: AbsBinds { abs_tvs = [a] , abs_exports = [ABE { abe_poly = M.reverse :: forall a. [a] -> [a], , abe_mono = reverse :: [a] -> [a]}] , abs_binds = { reverse :: [a] -> [a] = \xs -> case xs of [] -> [] (x:xs) -> reverse xs ++ [x] } } Here, * abs_tvs says what type variables are abstracted over the binding group, just 'a' in this case. * abs_binds is the *monomorphic* bindings of the group * abs_exports describes how to get the polymorphic Id 'M.reverse' from the monomorphic one 'reverse' Notice that the *original* function (the polymorphic one you thought you were defining) appears in the abe_poly field of the abs_exports. The bindings in abs_binds are for fresh, local, Ids with a *monomorphic* Id. If there is a group of mutually recursive functions without type signatures, we get one AbsBinds with the monomorphic versions of the bindings in abs_binds, and one element of abe_exports for each variable bound in the mutually recursive group. This is true even for pattern bindings. Example: (f,g) = (\x -> x, f) After type checking we get AbsBinds { abs_tvs = [a] , abs_exports = [ ABE { abe_poly = M.f :: forall a. a -> a , abe_mono = f :: a -> a } , ABE { abe_poly = M.g :: forall a. a -> a , abe_mono = g :: a -> a }] , abs_binds = { (f,g) = (\x -> x, f) } }}} If it's not clear enough I should rewrite it until it is. So yes, there's a fundamental reason. The rule is this: a reference on the RHS goes to the monomorphic version (`abe_mono`) iff * The variable, say 'x', has no type signature * The RHS is part of a mutually recursive group which binds 'x'. To find mutually recursive groups, perform a strongly-connnected-component analysis on the bindings, where there is a an edge from binding `y = ey` to `x = ex` iff * `ey` mentions `x` * `x` does not have a type signature Does that help? How could the Note be better? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11176#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11176: Typechecked AST for recursive top-level call refers to non-exported HsVar. -------------------------------------+------------------------------------- Reporter: literon | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by literon): * status: new => closed * resolution: => wontfix Comment: Makes a lot of sense, thank you! Some comments: * WiredIn results from a ghc-dump-tree printing bug, thanks for noting! * The note is very helpful - unfortunately I often only browse the haddock, so some source-only comments escape me. I often have the feeling that many source comments would be useful haddock comments too. * If you didn't explicitly mention it, I would have missed the requirement for not having a type signature, based on the note only. Maybe "Consider a module M, with this top-level binding [without an explicit type signature]", if that is correct? Resolving ticket, thank you again for the explanation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11176#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11176: Typechecked AST for recursive top-level call refers to non-exported HsVar.
-------------------------------------+-------------------------------------
Reporter: literon | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
Resolution: wontfix | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC