[Haskell-beginners] which typefor this FFI call
PICCA Frederic-Emmanuel
frederic-emmanuel.picca at synchrotron-soleil.fr
Wed Jun 28 13:27:02 UTC 2017
Hello, I end up with this and it works :) thanks
type H5Iterate a = HId_t -> CString -> In H5L_info_t -> InOut a -> IO HErr_t
foreign import ccall "wrapper" mkOp :: H5Iterate a -> IO (FunPtr (H5Iterate a))
nxEntries ∷ FilePath → IO [String]
nxEntries f = withH5File f $ \h → do
state <- newIORef []
statePtr <- newStablePtr state
let opData = InOut $ castStablePtrToPtr statePtr
let startIndex = Nothing
let indexType = ByName
let order = Native
iop <- mkOp callback
_ <- withInOut_ (maybe 0 hSize startIndex) $ \ioStartIndex ->
h5l_iterate (hid h) (indexTypeCode indexType) (iterOrderCode order) ioStartIndex iop opData
freeHaskellFunPtr iop
freeStablePtr statePtr
-- retrieve the final state
readIORef state
where
callback ∷ H5Iterate a
callback _g n _i (InOut dataptr) =
do
let opData = castWrappedPtr dataptr
-- get the state
stRef <- deRefStablePtr (castPtrToStablePtr opData)
st <- readIORef stRef
-- compute the new state
name <- peekCString n
let newSt = st ++ [name]
print st
print name
print newSt
-- store the new state
writeIORef stRef newSt
return $ HErr_t 0
BUT I lose the type checking at the callback interface.
the ffi call of the h5l_iterate method is
#ccall H5Literate, <hid_t> -> <H5_index_t> -> <H5_iter_order_t> -> InOut <hsize_t> -> H5L_iterate_t a -> InOut a -> IO <herr_t>
where H5L_iterate_t a = H5Iterate
So the call back should keep the information of the type via a
my question is, when I write this
let opData = InOut $ castStablePtrToPtr statePtr
I have InOut (Ptr ()) is it possible to have somthing more like InOut (Ptr a) instead ?
Thanks
Fred
More information about the Beginners
mailing list