nhc98-1.{00,01} produce crashing programs

Marcin 'Qrczak' Kowalczyk qrczak at knm.org.pl
Thu Jan 4 14:13:03 EST 2001


Thu, 4 Jan 2001 14:22:52 +0000, Malcolm Wallace <malcolm-nhc at cs.york.ac.uk> pisze:

> I don't understand - can you explain?  Surely the Num instances for
> Word/Int 8/16/32/64 mean that a literal integer 3 in the source code
> becomes (fromInteger 3) in reality, and this should be fine in
> case comparisons.

module Test where
newtype I = I Int
instance Eq I
instance Show I
instance Num I
test:: I -> Bool
test 0 = True
test _ = False

Fail: What? matchAltIf at 7:10

> As to dynamic import and export, I have never had any luck playing
> with dynamic loading of libraries in C.

They have nothing to do with dynamically loaded libraries.

foreign import dynamic is a plain generic "apply" operator in C:
take a pointert to a function and its arguments, return the value
returned by the function.

foreign export dynamic is harder. It must wrap a Haskell function
(closure) in a C function pointer. It is not possible to do this
portably in C: function pointers are normally only pointers to elements
of the finite set of (toplevel) functions. It should allocate a
block of unmovable memory on the heap (perhaps using malloc), attach
an equivalent of StablePtr of the function to it on a known offset
(to be able to free it later using freeHaskellFunPtr), write there a
constructed machine code which has this stable pointer hardcoded in
its body and applies it to parameters passed from C, and return the
pointer to the block as a function pointer.

> However, as far as I am aware, we agreed to remove the idea of
> *multiple* finalizers from the common FFI spec, because they have
> too many potential semantic problems.

I don't remember what the official spec says. Perhaps
addForeignPtrFinalizer should be dropped at all; I never used it.
It is present in ghc so I carried it on to QForeign.

Recently a bug in its implementation was fixed (which was discovered
because of a change in the typechecker). Did it work at all previously?
If not, I would just drop it.

> The next release of nhc98 will include GetOpt, Parsec, and a whole
> host of other libraries.

Parsec currently uses local universal quantification in one module to
simulate first-class modules. (I haven't uses that module in hsc2hs.)

> Yes, nhc98's Bit library follows version 1.3 of the Haskell Library
> Report,

I didn't know it was standarized.

> Fortunately, the next release of nhc98 can provide both interfaces
> if you wish.

Well, I used Bits on ghc because it is the only version it provides, so
to port library wrappers in QForeign to nhc I had to port Bits as well.
Some people say that Bits is ugly. I don't have an opinion how it should
really look like.

> > nhc does not provide CTypes and CTypesISO modules, nor HsFFI.h
> 
> CTypes and HsFFI.h exist as of yesterday.  CTypesISO will follow shortly.

I haven't found CTypes in CVS.

> Haskell characters are represented internal to nhc98 as 32-bit
> values, and always have been.

(maxBound::Char) is '\255', characters are cut to 8 bits in string
literals, HsChar is char, instance Storable Char use only 8 bits.

But they indeed seem to work otherwise. I will try to port Curses'
Unicode and perhaps my charset conversion machinery to nhc.

> > Is it possible to let hmake generate dependencies with that assumption?
> > Or could hmake be changed to support such scheme?
> 
> Yes, it is possible.  I've just committed a small patch to CVS
> which does what you want.

Thank you, it works.

BTW, 'make realclean' in nhc does not delete script/hmake-PRAGMA.{o,hi}.

Since the bug in Addr I reported previously makes FFI unusable on the
released nhc-1.00, I will not bother with supporting that version
of nhc, and thus any changes in nhc will be reflected directly in
QForeign without conditional support for the previous state, until
a version of nhc is released.

-- 
 __("<  Marcin Kowalczyk * qrczak at knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTÊPCZA
QRCZAK





More information about the FFI mailing list