Ptr and ForeignPtr Questions
Manuel M. T. Chakravarty
chak@cse.unsw.edu.au
Thu, 20 Sep 2001 23:55:03 +1000
Ashley Yakeley <ashley@semantic.org> wrote,
> At 2001-09-19 23:45, Manuel M. T. Chakravarty wrote:
>
> >> What if the type is polymorphic (e.g.
> >> declared as 'Storable a => Ptr a' rather than something like 'Ptr Word8')?
> >
> >Also possible, as the argument to `Ptr' is just dummy.
>
> What? What about 'withObject'? A Haskell 'Ptr a' is a C array-pointer of
> whatever corresponds to 'a'. I don't think the argument is dummy.
The argument constrains the type of functions that mention
the type variable in more than one place, but otherwise,
`Ptr' is nothing but
newtype Ptr a = MkPtr Addr
> Consider this:
>
> int foo (char selector,char* arg)
> {
> if (selector == 100)
> return reinterpret_cast<unsigned char*>(arg)[1];
> if (selector == 200)
> return reinterpret_cast<unsigned short*>(arg)[1];
> return 0;
> }
>
> foreign import "foo" foo :: Storable a => Word8 -> Ptr a -> IO Int32;
>
> a <- withObject ([1,2] :: [Word8]) (foo 100);
> b <- withObject ([3,4] :: [Word16]) (foo 200);
>
> Will this work as expected? I expect 'a' to be 2 and 'b' to be 4...
Yes, it works in that it resolves the overloading of
`withObject' in the way that you expect, but that's all.
> >> 3. What about ForeignPtr? Can instances of 'Storable a => ForeignPtr a'
> >> be used in FFI?
> >
> >They can be passed to C, but you can't get them back. (The
> >storange manager wouldn't know what finaliser to attach.)
>
> OK. Are ForeignPtrs intelligible in the C function as pointers to the
> named type?
The FFI does not ensure any type consistency between the
arguments to `Ptr'/`ForeignPtr' and the corresponding C
types. We have discussed this on the FFI list for quite a
while and came to the conclusion that there is no
sufficiently simple design that could achieve this goal
(consider, for example, storage specified, such as `const'
that don't have a counterpart in Haskell).
> >> 4. Does newForeignPtr work safely with null pointers, and will the
> >> finalizer get called? For instance:
> >>
> >> fp <- newForeignPtr nullPtr finalFunc;
> >> let {isNull = (foreignPtrToPtr fp) == nullPtr};
> >> r <- withForeign fp (\p -> foo p);
> >>
> >> Will foo be passed nullPtr? Will finalFunc ever get called? Is my use,
> >> above, of foreignPtrToPtr safe, and will isNull be True?
> >
> >Should work. From the storage managers point of view, a
> >`Ptr' is just an uninterpreted bit-pattern. A glorified
> >`Int'.
>
> So you are saying that the ForeignPtr code is not interested in the
> "pointer-ness" of the Ptr contents of a ForeignPtr,
Yes.
> except when a
> ForeignPtr is used as an FFI argument?
Even then - it is just a bit pattern for which the FFI
guarantees that it follows the same range constraints as
addresses in the underlying architecture.
> Presumably this also means that one can create two separate ForeignPtrs
> around the same Ptr, each with their own finaliser set.
Yes.
> Presumably they
> would not be equal (note that Eq (ForeignPtr a)). Is this correct?
Hmm, I am not sure actually. I would think that they are
equal, ie, that equality on ForeignPtr's corresponds to
equality of the included raw pointer type. That seems to me
what is usually wanted.
> Also, I assume that a ForeignPtr is eligible for garbage collection
> whenever it is no longer 'reachable', even if the Ptr it contains is
> reachable. Is that correct?
Absolutely.
> Is there anything resembling Java's 'soft' and 'weak references'?
There are weak pointers in GHC's hslibs:
http://haskell.org/ghc/docs/latest/set/sec-weak.html
Manuel