Some minor quirks with today's ghc-4.00:

   * fptools/ghc/rts/StgPrimFloat.c did not compile because of the redefiniton of
     union ieee754_double, which is already defined in /usr/include/ieee754.h on
     my Linux (libc5) box. Fix: rename ieee754_double to my_ieee754_double. This
     works, but autoconf should better check for this.

   * Word.lhs needs a little bit more heap for compilation:

        diff -r fptools.orig/ghc/lib/exts/Makefile fptools/ghc/lib/exts/Makefile
        43c43
        < Word_HC_OPTS         += -H12m
        ---
        > Word_HC_OPTS         += -H16m

   * Remove some imports in PosixIO (PrelHandle does not export these):

        diff -r fptools.orig/ghc/lib/posix/PosixIO.lhs 
fptools/ghc/lib/posix/PosixIO.lhs
        34c34
        < import PrelHandle (readHandle, writeHandle, newHandle, getBMode__, 
getHandleFd )
        ---
        > import PrelHandle (newHandle, getBMode__, getHandleFd )

   * fptools/distrib is missing. My quick hack: Use the one from 3.03.

   * The stubs generated for the FFI include rtsdefs.h instead of Rts.h.

   * The C compiler complains when using foreign exports:
       /tmp/ghc17785.hc:242: macro `STK_CHK' used with too many (7) args

   * GHC dies during the compilation of:

        module Foo where
        import GlaExts(Addr)
        foreign export _ccall dynamic myBaz :: (Int -> IO Char) -> IO Addr

     with the message:

        panic! (the `impossible' happened):
                applyTypeToArgs {-_ccall-}_ccall_ createAdjustor {dDT
                                                          0
                                                          dDU
                                                          (_litlit_ "dEc" 
PrelAddr.Addr{-32,W-})}

        Please report it as a compiler bug to [EMAIL PROTECTED]

   * Bootstrapping does not work at all: The compilation of 
fptools/ghc/compiler/utils/FastString.lhs
     aborts with:

        FastString.lhs:64: Module `PrelHandle' does not export `readHandle'

     Alas, grepping through the whole fptools directory reveals no definition of 
readHandle...

Apart from that, everything was OK...  :-}

-- 
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

Reply via email to