
Various small changes work, but this doesn't:
module Main where
main :: IO() main = putStrLn $ show $ foo 1
foo :: Int -> Int foo (-1) = 6 foo i = i
Compiling it gives nhc98 -c -o Q.o Q.lhs ==================================== Error when renaming:: Unbound Identifier - at 8:8 [Leaf2 ((Prelude._x,Identifier),160) followed by more stuff that I can give you if you need it and can't reproduce the problem. Thanks Ian, on a roll tonight...

module Main where
main :: IO() main = putStrLn $ show $ foo 1
foo :: Int -> Int foo (-1) = 6 foo i = i
Compiling it gives
==================================== Error when renaming:: Unbound Identifier - at 8:8
This buglet is revealed because the (-) is used only in a pattern, not in any expression in the module. Here's a patch. Regards, Malcolm Index: src/compiler98/Need.hs =================================================================== RCS file: /usr/src/master/nhc/src/compiler98/Need.hs,v retrieving revision 1.12 diff -u -r1.12 Need.hs --- src/compiler98/Need.hs 2001/08/17 14:04:15 1.12 +++ src/compiler98/Need.hs 2001/09/17 13:36:07 @@ -452,8 +452,8 @@ bindPat :: Exp TokenId -> NeedLib -> NeedLib bindPat (ExpApplication pos exps) = mapR bindPat exps -bindPat (ExpInfixList pos (ExpVarOp _ _:pats)) = mapR bindPat pats - -- ^ must be prefix - +bindPat (ExpInfixList pos (ExpVarOp _ op:pats)) = -- must be prefix - + needTid pos Var op >>> mapR bindPat pats bindPat (ExpInfixList pos exps) = mapR bindPat exps bindPat (ExpVar pos tid) = bindTid Var tid bindPat (ExpCon pos tid) = needTid pos Con tid
participants (2)
-
Ian Lynagh
-
Malcolm Wallace