It's just a bogus warning from ghc's renamer (updated from CVS today),
but anyway, here it is:
-- Foo.hs ------------------------------
module Foo where
class Readable a where readIt :: String -> IO a
readN :: (Integral a, Readable b) => a -> String -> IO [b]
readN n = sequence . replicate (fromIntegral n) . readIt
-- Bar.hs ------------------------------
module Bar where
import Foo
read42 :: Readable a => String -> IO [a]
read42 = readN (42::Int)
----------------------------------------
panne@liesl: ~ > ghc -Wall -prof -auto-all -O -c Foo.hs
ghc: module version changed to 1; reason: no old .hi file
panne@liesl: ~ > ghc -Wall -prof -auto-all -O -c Bar.hs
Foo.hi:18:
Warning: The universally quantified type variable `a'
does not appear in the type `[PrelIOBase.IO b]
-> PrelIOBase.IO [b]'
In the interface signature for `s'
ghc: module version changed to 1; reason: no old .hi file
Cheers,
Sven
--
Sven Panne Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED] D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne