[nhc-bugs] Exporting class methods
Malcolm Wallace
Malcolm.Wallace at cs.york.ac.uk
Fri Apr 15 12:25:36 EDT 2005
Ian Lynagh <igloo at earth.li> writes:
> 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
More information about the Nhc-bugs
mailing list