Skip to content
Snippets Groups Projects
Commit d1650dab authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1999-11-05 10:09:36 by simonmar]

Allow this syntax on the lhs:

	(e1 `op` e2) e3 = ...

(bug reported by Ralf Hinze).

Add a test for it.
parent 26bced60
No related merge requests found
......@@ -335,8 +335,8 @@ checkValDef lhs opt_sig grhss loc
-- A variable binding is parsed as an RdrNamePatBind.
isFunLhs (OpApp l (HsVar op) fix r) [] | not (isRdrDataCon op)
= Just (op, True, [l,r])
isFunLhs (OpApp l (HsVar op) fix r) es | not (isRdrDataCon op)
= Just (op, True, (l:r:es))
isFunLhs (HsVar f) es@(_:_) | not (isRdrDataCon f)
= Just (f,False,es)
isFunLhs (HsApp f e) es = isFunLhs f (e:es)
......
......@@ -684,7 +684,8 @@ checkPrecMatch :: Bool -> Name -> RenamedMatch -> RnMS ()
checkPrecMatch False fn match
= returnRn ()
checkPrecMatch True op (Match _ [p1,p2] _ _)
checkPrecMatch True op (Match _ (p1:p2:_) _ _)
-- True indicates an infix lhs
= getModeRn `thenRn` \ mode ->
-- See comments with rnExpr (OpApp ...)
case mode of
......
module ShouldCompile where
(<>) :: (a -> Maybe b) -> (b -> Maybe c) -> (a -> Maybe c)
(m1 <> m2) a1 = case m1 a1 of
Nothing -> Nothing
Just a2 -> m2 a2
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment