[Haskell-beginners] which typefor this FFI call

Sylvain Henry sylvain at haskus.fr
Mon Jun 26 06:18:08 UTC 2017


Hi,

I would use IORef and StablePtr:

import Foreign.StablePtr
import Foreign.Ptr
import Data.IORef

type H5Iterate = Hid -> CString -> Ptr () -> Ptr () -> IO ()

-- see https://wiki.haskell.org/Foreign_Function_Interface#Function_pointers
foreign import ccall "wrapper" mkOp :: H5Iterate -> FunPtr (H5Iterate)

foreign import ccall "H5Lvisit" h5iterate :: Hid -> Index -> Order -> 
FunPtr H5Iterate -> Ptr () -> IO ()

main = do
   state <- newIORef []
   statePtr <- newStablePtr state

   let
     callback :: H5Iterate
     callback hid name infoptr dataptr = do
         -- get the state
         stRef <- deRefStablePtr (castPtrToStablePtr dataptr)
         st <- readIORef stRef
         -- compute the new state
         newSt <- ...
         -- store the new state
         writeIORef stRef newSt

   h5iterate gid idttyp order (mkOp callback) (castStablePtrToPtr statePtr)

   -- retrieve the final state
   finalState <- readIORef state


- Sylvain


On 24/06/2017 15:47, PICCA Frederic-Emmanuel wrote:
> Hello
>
> I would like to create a binding for this function [1].
>
> herr_t H5Literate( hid_t group_id, H5_index_t index_type, H5_iter_order_t order, hsize_t *idx, H5L_iterate_t op, void *op_data )
>
> My "only" problem is with the op and op_data part.
> Here the C op signature[2]
>
> op ->  herr_t (*H5L_iterate_t)( hid_t g_id, const char *name, const H5L_info_t *info, void *op_data)
>
> What I would like to do is to create an Haskell function which allows to return what is contained under the op_data.
> What I understand from this is that I give the H5Literate function an op function which is executed for each group of my hdf5 file.
> So the op method is called with the releavant parameters.
> The op_data can be use to accumulate things during the traversal.
>
> H5Literate :: Hid -> Index  -> Order -> Maybe HSize -> H5Iterate -> _ -> _
>
> type H5Iterate = Hid -> ByteString -> Info -> _ -> _
>
> So it seems to me that I need to use a State inorder to do the accumulation.
>
> For exemple,I want to collect each group names and accumulate then in a list.
>
> Somy questioniswhat should be the signature of both function.
>
> I have also the fealing that the return type MUST have a Storableinstance.
>
>
> Thanks for your help
>
> Frederic
>
>
> [1] https://support.hdfgroup.org/HDF5/doc/RM/RM_H5L.html#Link-Iterate
> [2] https://support.hdfgroup.org/HDF5/doc/RM/RM_H5L.html#Link-Visit
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



More information about the Beginners mailing list