Exporting class methods

Hi, Andother problem with both nhc98 1.16 and 1.18. $ cat Q.hs module Q where import Data.Bits (shiftL) $ nhc98 -c Q.hs ====== Errors when renaming: Identifier shiftL used at 4:19-4:24 is not defined. If I change the second line to import Data.Bits (Bits(shiftL)) then it compiles fine. ghc and hugs are both happy with it either way. My reading of the report suggests the first form should be allowed (and hence this is a bug in nhc98): http://www.haskell.org/onlinereport/modules.html says: --------8<----------------8<----------------8<-------- 5.2 Export Lists Entities in an export list may be named as follows: 1. A value, field name, or class method, whether declared in the module body or imported, may be named by giving the name of the value as a qvarid, which must be in scope. 5.3.1 What is imported Exactly which entities are to be imported can be specified in one of the following three ways: 1. The imported entities can be specified explicitly by listing them in parentheses. Items in the list have the same form as those in export lists, except qualifiers are not permitted and the `module modid' entity is not permitted. --------8<----------------8<----------------8<-------- 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? Here is a (probably incomplete) one: Control.Concurrent.MVar System.IO (hPutBuf, hGetBuf) Control.Exception (catch, block, unblock, bracket_) Thanks Ian

Ian Lynagh
$ cat Q.hs module Q where import Data.Bits (shiftL)
$ nhc98 -c Q.hs ====== Errors when renaming: Identifier shiftL used at 4:19-4:24 is not defined.
If I change the second line to import Data.Bits (Bits(shiftL)) then it compiles fine. ghc and hugs are both happy with it either way. My reading of the report suggests the first form should be allowed (and hence this is a bug in nhc98):
It is a bug, and one I have been aware of for some time. The workaround is easy (just change the import line), so fixing it has not been a high priority.
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.Concurrent.MVar Control.Exception (catch, block, unblock, bracket_)
nhc98 at the moment does not implement concurrent threads, nor general exceptions. I have made a start on the former (using a similar cooperative scheduling model to that used in Embedded Gofer), but it will be some time before it is complete. If someone else were looking for a nice self-contained little implementation project, then either exceptions or threads would be very welcome, and I would happily pass on the baton.
System.IO (hPutBuf, hGetBuf)
Implementing binary I/O should be pretty straightforward in nhc98 - it doesn't perform any CR/LF translation anyway, so there is effectively no difference between text and binary modes. Adding these library functions in particular should come down to writing a few lines of C and a Haskell FFI wrapper. Regards, Malcolm

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

Ian Lynagh
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).
Yes, pretty-much all of these rely on significant extensions to Haskell'98.
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.
Well, all the other extensions are "non-standard" in the same sense... I think newtype deriving might actually be one of the easier extensions to implement!
Is there a way to get nhc to accept an instance for String?
Class instances for type synonyms require yet another extension: overlapping instances.
Another nhc bug:
foo :: (Eq (f a), Functor f) => (a -> b) -> f a -> f b -> Bool
This is documented as one point of non-compliance with H'98 - it is the "lifting of the simple context restriction", and cannot be done right in nhc98 until it implements kind inference properly.
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 is slightly related. It indicates a genuine type error, which you probably introduced in an attempt to workaround the above bug in nhc98. For instance, this should fail: f :: (Monad m, Eq a) => a -> m a -> Bool f x y = (return x == y) with the error: Couldn't simplify the context (Prelude.Eq (u_5 t_5))
cpphs (It would be nice if it could take input from stdin, BTW)
OK, fixed.
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
Also now fixed, thanks. BTW, the value of __LINE__ appears to be wrong in cpphs for this example, but I have other examples where it is calculated correctly, so I'm not sure what is happening there yet. Regards, Malcolm

On Fri, Apr 15, 2005 at 05:25:36PM +0100, Malcolm Wallace wrote:
Ian Lynagh
writes: Another nhc bug:
foo :: (Eq (f a), Functor f) => (a -> b) -> f a -> f b -> Bool
This is documented as one point of non-compliance with H'98 - it is the "lifting of the simple context restriction", and cannot be done right in nhc98 until it implements kind inference properly.
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 is slightly related. It indicates a genuine type error, which you probably introduced in an attempt to workaround the above bug in nhc98. For instance, this should fail:
f :: (Monad m, Eq a) => a -> m a -> Bool f x y = (return x == y)
with the error:
Couldn't simplify the context (Prelude.Eq (u_5 t_5))
Ah, the problem turns out to be that the type can't be infered without the type signature, presumably due to the monomorphism restriction. Thanks Ian
participants (2)
-
Ian Lynagh
-
Malcolm Wallace