
Hi Malcolm, On Tue, Apr 12, 2005 at 11:42:00AM +0100, Malcolm Wallace wrote:
Ian Lynagh
writes: By the way, these bugs are coming from looking at compiling darcs with nhc98, but there are also a number of modules/functions missing. Are you interested in a list of these?
Yes.
Control.Exception (bracket_, catch, block, unblock catchJust, Exception(IOException) catchDyn, throwDynTo, bracket, ioErrors, finally ) Control.Concurrent ( ThreadId, myThreadId ) Control.Concurrent.MVar (MVar, modifyMVar_, swapMVar, newMVar) Control.Monad.Reader (Reader, runReader, ask, local) System.Posix.IO (fdToHandle) System.Posix.Types ( Fd(Fd) ) System.IO ( hPutBuf, hGetBuf, hIsTerminalDevice ) -- claims to be portable! System.Posix (getFileStatus, setFileMode, unionFileModes, ownerExecuteMode, groupExecuteMode, fileMode EpochTime, modificationTime, sleep, FileOffset, fileSize, setFileTimes, epochTime) Control.Monad.Error (instance MonadPlus IO) Also, unboxed arrays of Int32, Bool, Int and STUArrays of Int and Bool (plus runST, mutable array functions, unsafeFreeze, etc). We make use of newtype deriving Integral+Real+Num+Enum, but it's obviously reasonable for us to avoid doing that as it's non-standard. Is there a way to get nhc to accept an instance for String? Another nhc bug: ----------------------------------------------------- $ cat Q.hs module Q where foo :: (Eq (f a), Functor f) => (a -> b) -> f a -> f b -> Bool foo = undefined $ nhc98 -c Q.hs ====== In file: ./Q.hs: 4:30-4:31 Found => but expected a {-end-of-definition-or-EOF-} $ ----------------------------------------------------- The type of foo is taken from 4.1.4 of http://www.haskell.org/onlinereport/decls.html which lists it under "For example, here are some valid types". Anyway, now I've got: nhc98comp: Couldn't simplify the context (Prelude.Monad (y_19 d_20)). Possible sources for the problem are: 248:35-248:40, 243:24-243:49, 245:42-245:51, 246:35-246:40 and 247:35-247:79 which I assume is related to the above bug. It'd probably be quite a bit of work to work around, so I think I'll stop there for now. Also a cpphs problem (I'm afraid I haven't got to the recent version yet, so this may be fixed already): (It would be nice if it could take input from stdin, BTW) It doesn't quote some __FOO__s that cpp does: $ echo -e "__FILE__\n__LINE__\n__TIME__\n__DATE__\n" > q $ cpp --no-line q "q" 2 "12:32:48" "Apr 15 2005" $ cpphs --noline q q 3 12:32:58 15 Apr 2005 Thanks Ian