[GHC] #7828: RebindableSyntax and Arrow

#7828: RebindableSyntax and Arrow --------------------------------------+------------------------------------- Reporter: AlessandroVermeulen | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.2 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: GHC rejects valid program | Blockedby: Blocking: | Related: --------------------------------------+------------------------------------- When trying to add constraints to the types of the arrow primitives I get a type error. I think that doing such a thing should be possible and I've attached the code I used to test this. The errors I get when using the arrow notation for the function test are as follows: {{{ test :: Typeable a => R a a test = proc n -> returnA -< n }}} {{{ bug-arrow.hs:15:8: Could not deduce (Typeable c) arising from a use of `arr' from the context (Typeable a) bound by the type signature for test :: Typeable a => R a a at bug-arrow.hs:14:9-27 Possible fix: add (Typeable c) to the context of a type expected by the context: (b -> c) -> R b c or the type signature for test :: Typeable a => R a a In the expression: arr When checking that `arr' (needed by a syntactic construct) has the required type: forall b1 c1. (b1 -> c1) -> R b1 c1 arising from a proc expression at bug-arrow.hs:15:8-29 In the expression: proc n -> returnA -< n bug-arrow.hs:15:8: Could not deduce (Typeable c) arising from a use of `>>>' from the context (Typeable a) bound by the type signature for test :: Typeable a => R a a at bug-arrow.hs:14:9-27 Possible fix: add (Typeable c) to the context of a type expected by the context: R a1 b -> R b c -> R a1 c or the type signature for test :: Typeable a => R a a In the expression: (>>>) When checking that `(>>>)' (needed by a syntactic construct) has the required type: forall a2 b1 c1. R a2 b1 -> R b1 c1 -> R a2 c1 arising from a proc expression at bug-arrow.hs:15:8-29 In the expression: proc n -> returnA -< n bug-arrow.hs:15:8: Could not deduce (Typeable d) arising from a use of `first' from the context (Typeable a) bound by the type signature for test :: Typeable a => R a a at bug-arrow.hs:14:9-27 Possible fix: add (Typeable d) to the context of a type expected by the context: R b c -> R (b, d) (c, d) or the type signature for test :: Typeable a => R a a In the expression: first When checking that `first' (needed by a syntactic construct) has the required type: forall b1 c1 d1. R b1 c1 -> R (b1, d1) (c1, d1) arising from a proc expression at bug-arrow.hs:15:8-29 In the expression: proc n -> returnA -< n }}} When I replace the definition with the translated core code (minus type applications and scoped type variables) the code compiles: {{{ test :: Typeable a => R a a test = (>>>) (arr (\ (n_apd) -> n_apd)) ((>>>) (arr (\ (ds_dst) -> ds_dst)) (returnA) ) }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7828 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7828: RebindableSyntax and Arrow ------------------------------------+--------------------------------------- Reporter: AlessandroVermeulen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: GHC rejects valid program Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ------------------------------------+--------------------------------------- Changes (by simonpj): * difficulty: => Unknown Comment: I know exactly what is happening here, but need some arrow-aware person to do some work to fix it. Remember that GHC typechecks the user-written '''source code''' not the desugared code. What shouuld happen is that at each source-code construct that requires (say) a use of `(>>>)`, we should instantiate a fresh call of `(>>>)`, and attach that instantiated call to the syntax tree. That's what happens for monads. For example, here is the data type of `Stmt` (in `HsExpr`): {{{ data StmtLR idL idR body -- body should always be (LHs**** idR) = LastStmt -- Always the last Stmt in ListComp, MonadComp, PArrComp, -- and (after the renamer) DoExpr, MDoExpr -- Not used for GhciStmtCtxt, PatGuard, which scope over other stuff body (SyntaxExpr idR) -- The return operator, used only for MonadComp -- For ListComp, PArrComp, we use the baked-in 'return' -- For DoExpr, MDoExpr, we don't appply a 'return' at all -- See Note [Monad Comprehensions] | BindStmt (LPat idL) body (SyntaxExpr idR) -- The (>>=) operator; see Note [The type of bind] (SyntaxExpr idR) -- The fail operator -- The fail operator is noSyntaxExpr -- if the pattern match can't fail ...etc... }}} The `SyntaxExpr` on the `ReturnStmt` is for the instantiated call of `return`; the ones on `BindStmt` are for `(>>=)` and `fail`. But currently for arrow `Cmd`s we use a different (older) plan. We have a '''single''' instantiated call of `(>>>)` for the whole `Cmd`. It is held in the `CmdTop`: {{{ data HsCmdTop id = HsCmdTop (LHsCmd id) PostTcType -- Nested tuple of inputs on the command's stack PostTcType -- return type of the command (CmdSyntaxTable id) -- See Note [CmdSyntaxTable] }}} The `CmdSyntaxTable` has the calls for `(>>>)`, `first` etc. But this approach requires `(>>>)` etc to be fully polymorphic in the non- arrow argument, so that this one call can be used at every place in the command that it's needed. And yours are not. Solution: use the same approach as we use for monads: * Get rid of the `CmdSyntaxTable` on HsCmdTop` * Add `SyntaxExpr` fields to all the appropriate constructs in `HsCmd` that need them. I don't think this is really hard, but it's a bit fiddly. I'd be happy to advise if someone wants to undertake it. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7828#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7828: RebindableSyntax and Arrow ------------------------------------+--------------------------------------- Reporter: AlessandroVermeulen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: GHC rejects valid program Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ------------------------------------+--------------------------------------- Comment(by AlessandroVermeulen): I would like to try and implement this seeing as I need it myself. However, I am completely unfamiliar with the internals of GHC and the development process. I do have checkout but what is a good place to start looking where I should make the modifications? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7828#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7828: RebindableSyntax and Arrow ----------------------------------------+----------------------------------- Reporter: AlessandroVermeulen | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler (Type checker) | Version: 7.6.2 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: GHC rejects valid program Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ----------------------------------------+----------------------------------- Changes (by igloo): * component: Compiler => Compiler (Type checker) * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7828#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC