[Haskell-cafe] StablePtr's and castStablePtrToPtr
Duncan Coutts
duncan.coutts at worc.ox.ac.uk
Fri Jul 28 08:01:54 EDT 2006
On Tue, 2006-07-25 at 22:16 -0400, DeeJay-G615 wrote:
> I have a query which is asked out of interest's sake...
>
> I'm essentially looking for an affirmation of what I think I already
> understand (or some info if I'm deluded ;)).
>
> To put this in context...
>
>
> I have some C code...
>
> typedef int func(void *);
>
> void from_maybe_int(void *val, func *my_func)
> {
> int i;
> i = my_func(val);
> printf("value within C: %d\n", i);
> }
For greater clarity you might like to use HsStablePtr in place of void*.
> And some Haskell code...
>
> type FromMaybeInt = StablePtr (Maybe Int) -> IO CInt
>
> foreign import ccall "wrapper"
> wrapFromMaybeInt :: FromMaybeInt
> -> IO (FunPtr FromMaybeInt)
>
> foreign import ccall "from_maybe_int"
> cFromMaybeInt :: StablePtr (Maybe Int)
> -> FunPtr GetJust
> -> IO ()
>
> functionToPass :: FromMaybeInt
> functionToPass sPtr = do
> m <- deRefStablePtr sPtr
> case m of
> Nothing -> return (-1)
> Just i -> return (fromIntegral i)
>
> main :: IO ()
> main = do sPtr <- newStablePtr (Just 3) -- for example
> funPtr <- wrapFromMaybeInt functionToPass
> cFromMaybeInt sPtr funPtr
> freeStablePtr sPtr
>
>
> The compiled program works fine. However I wanted to check this was
> correct usage. As in, is perfectly fine to pass a value of type
> StablePtr a into C?
Yes, that's exactly the point of a StablePtr, to be able to pass it to C
and then get it back and get a Haskell value out of it.
Your usage of it looks fine to me.
> Am I correct in thinking that StablePtr is defined as a void pointer in
> C?
Right. The FFI spec defines it in HsFFI.h as:
typedef void * HsStablePtr;
> From my very limited understanding of C, it is also the case that you
> can implicitly cast a void pointer to any other pointer type and
> vice-versa. Some appear to deem it bad practice if you explictly give
> the cast.
True. In this case it hardly matters because you are not allowed to
directly dereference the pointer in C anyway as it's not guaranteed to
point to any valid location. Indeed in GHC's implementation it doesn't.
It's just a token which you can pass back to Haskell land.
> So therefore I am somewhat hazy on the use for castStablePtrToPtr. I
> found the ghc docs to be quite cryptic for this function.
>
> Google dug up a few examples of it's use in PUGS... which has lead me to
> think that the function is purely for type 'convience' in Haskell. Is
> this the case or am I missing a use case here?
So when you export a StablePtr to C using an FFI declaration like your
one:
foreign import ccall "from_maybe_int"
cFromMaybeInt :: StablePtr (Maybe Int)
-> FunPtr GetJust
-> IO ()
The StablePtr is automatically converted to the C void *. The
castStablePtrToPtr function just allows you to do that same conversion
but inside Haskell.
This might be useful if the StablePtr has to be put into or removed from
a C structure.
> Disclaimer: My knowledge and experience of C is somewhat limited.
> Ironically I have started playing with C by way of Haskell. (Sick and
> twisted I know).
I find C & Haskell a good combination for practical stuff. Their
strengths and weaknesses complement each other quite well.
Duncan
More information about the Haskell-Cafe
mailing list