[GHC] #9773: Binding ImplicitParams in lambda results in parse error

#9773: Binding ImplicitParams in lambda results in parse error -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Parser) | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: GHC Blocked By: | rejects valid program Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- {{{ImplicitParams}}} currently do not play well with lambdas :( == Steps to reproduce Create a file {{{Foo.hs}}} with the following content: {{{ {-# LANGUAGE ImplicitParams #-} import Control.Monad foo :: (?bar :: Int) => IO () foo = print ?bar main = do forM_ [1..3] $ \ ?bar -> foo }}} === Expected result {{{ $ runhaskell Foo.hs 1 2 3 }}} === Actual result {{{ $ runhaskell Foo.hs Foo.hs:9:21: Parse error in pattern: ?bar }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9773 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9773: Binding ImplicitParams in lambda results in parse error -------------------------------------+------------------------------------- Reporter: | Owner: SimonHengel | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: (Parser) | Architecture: Unknown/Multiple Resolution: invalid | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: GHC | rejects valid program | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: Well that really is syntactically illegal, isn't it? You can't explicitly lambda-abstract over an implicit parameter. Reopen if you disagree. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9773#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9773: Binding ImplicitParams in lambda results in parse error -------------------------------------+------------------------------------- Reporter: | Owner: SimonHengel | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: (Parser) | Architecture: Unknown/Multiple Resolution: invalid | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: GHC | rejects valid program | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by SimonHengel): As I understand it I have to explicitly bind an implicit parameter somewhere to bring it "into scope". At least intuitively I would assume that if {{{ forM_ [1..3] $ \ bar -> let ?bar = bar in foo }}} works, then {{{ forM_ [1..3] $ \ ?bar -> let ?bar = bar in foo }}} should work too. But I realize that the current behavior is clearly laid out in the User's Guide. So it's certainly not a bug, but (if anything) a feature request. Are there any fundamental limitations that would prevent us to make this work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9773#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9773: Binding ImplicitParams in lambda results in parse error -------------------------------------+------------------------------------- Reporter: | Owner: SimonHengel | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: (Parser) | Architecture: Unknown/Multiple Resolution: invalid | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: GHC | rejects valid program | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): If you mean that the latter could be syntactic sugar for the former, then I yes I suppose you could do that, but I think it'd be pretty confusing. Worth reading the original paper too: http://galois.com/wp- content/uploads/2014/08/pub_JL_ImplicitParameters.pdf -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9773#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC