[GHC] #14293: View patterns with locally defined functions in restructuring don't compile

#14293: View patterns with locally defined functions in restructuring don't compile -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE ViewPatterns #-} foo x = x Just (id -> res) = pure 'a' -- WORKS Just (foo -> res') = pure 'a' -- FAILS bar (foo -> res) = res -- WORKS {- [1 of 1] Compiling Main ( T14293.hs, interpreted ) T14293.hs:6:7-9: error: Variable not in scope: foo :: Char -> t | 6 | Just (foo -> res') = pure 'a' | ^^^ Failed, 0 modules loaded. -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14293 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14293: View patterns with locally defined functions in restructuring don't compile -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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 RyanGlScott): I looked into this yesterday, but this seems much harder to fix than I would have originally thought. The issue is that we rename top-level bindings in two phases: 1. First, we rename the LHSes of each top-level binding, and gather up the names of each binding form. 2. We then extend the global `RdrEnv` with these binding forms and proceed to rename the RHSes of each top-level binding. The problem concerns what constitutes a "LHS". For `FunBind`s, like `foo` and `bar`, the LHS is just the name of the function itself. As a result, the RHS of `bar` includes its `(foo -> res)` pattern, so by the time the RHS is renamed, `foo` is already in scope. For `PatBind`s, however, the LHS includes the pattern itself. This is out of necessity, since for example, `Just (foo -> res')` is binding `res'` at the top level, so we must dig into the pattern itself in order to rename `res'`. But that means that when we are renaming `Just (foo -> res')`, we haven't yet brought `foo` into scope in the `RdrEnv`, causing the error observed in this ticket. This is quite a sticky situation, and I'm not sure it's easy to resolve. Perhaps there's some sort of SCC analysis that could save us here? I'll have to defer to the wisdom of those who know more about the renamer than I do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14293#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14293: View patterns with locally defined functions in restructuring don't compile -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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): Here's an even more tricky case: {{{ (foo -> (a,b), foo) = ([True,False], \(a:b:_) -> (a,b)) }}} The lazy pattern binding matches a pair, binding `foo`, which is used as the viewing function in another part of the same pattern. I think the Right Thing here is to rename the ''binders'' of the pattern first, and then later rename the ''occurrences'' of bound variables. The latter occur in view patterns. At the moment a `HsBindLR` has two pass parameters, and goes through these stages: * `HsBindLR Parsed Parsed`: after the parser * `HsBindLR` Renamed Parsed`: binders renamed, but RHSs not renamed yet * `HsBindLR` Renamed Renamed`: fully renamed But patterns have only one pass parameter! So perhaps we can give them two, like `HsBindLR`. Then `rnPat` would be split into two, * `rnPatLHS` that deals with the binders, and * `rnPatRHS` that deals with the expressions in view patterns. The latter would be much simpler than the current `rnPat`: just find the view patterns and renamed the view function. The former is pretty much what we have now in `rnPat`. In the case of lambda/case patterns we don't want to split in this way. We positively want a left-to-right bias. For example {{{ f (foo -> (a,b), foo) = ... }}} is ill-scoped. So maybe `rnPatLHS` has type (roughly) {{{ rnPatLHS :: Pat GhcPs GhcPs -> (LHsExpr GhcPs -> RnM (LHsExpr p)) -> (LPat GhcRn p -> RnM (a, FreeVars)) -> RnM (a, FreeVars) }}} Here the second argument is used to rename the view functions; either it's a no-op (used in bindings) or it's `rnLHsExpr` (use in case/lambda). I have not worked through the details but it seems plausible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14293#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14293: View patterns with locally defined functions in restructuring don't compile -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ViewPatterns Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15893 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => ViewPatterns * related: => #15893 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14293#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14293: View patterns with locally defined functions in restructuring don't compile -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ViewPatterns Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15893 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I've realised that it may be simpler than I thought. Currently `RnBinds.rnLocalValBindsLHS` looks like this {{{ rnLocalValBindsLHS fix_env binds = do { binds' <- rnValBindsLHS (localRecNameMaker fix_env) binds ; let bound_names = collectHsValBinders binds' ... }}} I think instead we can do this {{{ = do { let bound_rdr_names = collectHsValBinders binds' ; bound_names <- mapM newLocalBndrRn bound_rdr_name ; binds' <- bindLocalNames bound_names $ addLocalFixities fix_env bound_names $ rnValBindsLHS (localRecNameMaker fix_env) binds ... }}} Take an tricky example binding {{{ (f, f -> x) = e }}} The idea is 1. Find all the `RdrName` binders from bindings, here `f` and `x`. 2. Make fresh `Names` for each of them, say `f_34` and `x_88`. 3. Extend the environment with bindings `f :-> f_34` and `x :-> x_88`. 4. Then rename the LHSs; but when we find a binder (say the `RdrName` `f`), `localRecNameMaker` should ''look it up'' in the environment, rather than making a fresh `Name` (that's been done already). Result is the pattern `(f_34, f_34 -> x_88)`. 5. After that, everything is as before. To do this we need to persuade `localRecNameMaker` to look up rather than make a fresh `Name`. I think we can do this easily, by altering the `LetMk` case of `newPatName`. We need to make exactly the same change in `rnSrcDecls`, for the same reason. I think that's it! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14293#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC