{-# LANGUAGE Arrows, NoMonomorphismRestriction #-}module T whereimport Prelude hiding ( id, (.) )import Control.Arrowcc1 :: Arrow a => a e b -> a e b -> a e bcc1 = undefined-- 'g' fails to compile.-- g = proc (x, y, z) ->-- ((returnA -< x) &&& (returnA -< y) &&& (returnA -< z))-- 'f' compiles:-- - without an infix declaration-- - with the infixl declaration-- and fails with the infixr declarationinfixr 6 `cc1`-- infixl 6 `cc1`f = proc (x, y, z) -> ((returnA -< x) `cc1` (returnA -< y) `cc1` (returnA -< z))
GHC says:
ghc: panic! (the 'impossible' happened) (GHC version 7.0.3 for i386-apple-darwin): dsSyntaxTable Not found: base:GHC.Desugar.>>>{v 01W}
The problem is that the renamer attaches a table of rebindable names to each top-level command (body of proc or argument of a form, including infix operators) before it does the fix-up for right associativity. That re-arrangement moves the left argument out of scope of the table.
One fix would be to add these tables in a separate pass after renaming.
But I was wondering whether having a separate table on each argument of a form is particularly useful, since it's not very easy to have different names in scope there than at the proc.
Thanks Ross. Adding a whole new pass just to deal with this very special case isn't very attractive.
In fact, I've moved sharply away from these "syntax tables" in the rest of the compiler. As you'll see, the only use of SyntaxTable is on a HsCmdTop, and I'd love to be rid of it. Instead, in (say) monad comprehensions, the necessary operators are attached directly to the HsStmt constructors, see the SyntaxExpr arguments in StmtLR (in HsExpr) for example. This would mean the problem reported here simply would not arise.
This would not as straightforward for arrows, because in effect we hijack a bunch of HsExpr constructors for use in arrow abstractions (see line 600ff of HsExpr), which says
The legal constructors for commands are: = HsArrApp ... -- as above | HsArrForm ... -- as above | HsApp (HsCmd id) (HsExpr id) | HsLam (Match id) -- kappa -- the renamer turns this one into HsArrForm | OpApp (HsExpr id) -- left operand (HsCmd id) -- operator Fixity -- Renamer adds fixity; bottom until then (HsCmd id) -- right operand | HsPar (HsCmd id) -- parenthesised command | HsCase (HsExpr id) [Match id] -- bodies are HsCmd's SrcLoc | HsIf (Maybe (SyntaxExpr id)) -- cond function (HsExpr id) -- predicate (HsCmd id) -- then part (HsCmd id) -- else part SrcLoc | HsLet (HsLocalBinds id) -- let(rec) (HsCmd id) | HsDo (HsStmtContext Name) -- The parameterisation is unimportant -- because in this context we never use -- the PatGuard or ParStmt variant [Stmt id] -- HsExpr's are really HsCmd's PostTcType -- Type of the whole expression SrcLoc
I'm not keen on adding extra fields to all of these constructors. Actually I think it might be best simply to make a new data type for arrows, with these constructors, each decorated with appropriate methods as in StmtLR. The desugaring code is separate anyway. There would be some duplication of typechecking code, not not a lot. But I think the clarity would be worth it; code dealing with arrows would, well, deal with arrows, and other code would not need to worry about the case that it was actually (say) typechecking an arrow abstraction. Decoupling the two would simplify both -- admittedly at the cost of a bit more code. But I feel that the code-sharing we get just isn't paying its way.
If you felt able to look at this it would be fantastic. I'd be happy to have a Skype chat about details, if that would help. Frankly I'm out of my depth with the arrow syntax.
Yes, I noticed a lot of sighing around the rebindable stuff. It sounds like a good idea to have a separate HsCmd type, with a corresponding variant of Stmt. #5045 (closed) would have been caught by the type-checker if that had been in place. But duplicating MatchGroup and friends would be a nuisance. That might be saved if they were generalized to something like
type MatchGroup = MatchGroupG HsExpdata MatchGroupG e id = MatchGroup [LMatchG e id] PostTcTypetype LMatch = LMatchG HsExp
and so on.
Splitting the types won't fix the current bug, but it's probably best to do that first and then rework the rebinding for arrows properly. My algorithm for the first part would be to copy everything and then simplify the arrow version.
Unfortunately I'll be online only intermittently until September.
That sounds good. So the plan that, when you can, you will
First split the data types
Then fix the rebinding problem
For MatchGroup I suggest abstracting over something of kind *, rather than over the type constructor. Less brain-strain. But let's discuss when you get to it.
When you have a rough cut (say the data types worked out) it would be good to talk.