[Haskell-cafe] FFI Ptr Question

Michael Jones mike at proclivis.com
Mon Apr 6 04:28:49 UTC 2015


Ok, I’ll give some details and since I made it work using your description of Ptr a, I'll describe the solution. And it will leave one question at the end.

There is a class in wxWidgets called wxGridTableBase. It has callbacks and definitions of signatures that are C typed.

C++ CLASS WITH CALLBACKS

extern "C"
{
typedef int   _cdecl (*TGridGetInt)(void* _obj);
typedef int   _cdecl (*TGridIsEmpty)(void* _obj, int row, int col);
…
}

class ELJGridTable : public wxGridTableBase
{
	private:
		void* EiffelObject;
		TGridGetInt EifGetNumberRows;
		TGridGetInt EifGetNumberCols;
...
	public:
		ELJGridTable (void* _obj,
		              void* _EifGetNumberRows,
		              void* _EifGetNumberCols,
…                          ): wxGridTableBase()
		{
			EiffelObject = _obj;
			EifGetNumberRows = (TGridGetInt)_EifGetNumberRows;
			EifGetNumberCols = (TGridGetInt)_EifGetNumberCols;
...
		};
		
		int GetNumberRows() {return EifGetNumberRows(EiffelObject);};
		int GetNumberCols() {return EifGetNumberCols(EiffelObject);};
...
};

WXHASKELL WRAPPER

wxcGridTableCreate :: Ptr  a -> Ptr  b -> ... ->  IO (WXCGridTable  ())
wxcGridTableCreate _obj _EifGetNumberRows _EifGetNumberCols _EifGetValue _...
  = withObjectResult $
    wx_ELJGridTable_Create _obj  _EifGetNumberRows  _EifGetNumberCols  ...  
foreign import ccall "ELJGridTable_Create" wx_ELJGridTable_Create :: Ptr  a -> Ptr  b -> Ptr  c -> ... -> IO (Ptr (TWXCGridTable ()))

The question is how to call wxcGridTableCreate with Haskell functions.

So here are a few callbacks:

CALLBACK FUNCTIONS

getNumberOfRows :: Ptr CInt -> CInt 
getNumberOfRows p = 1

foreign import ccall "wrapper"
  wrapNumberOfRows :: (Ptr CInt -> CInt) -> IO (FunPtr (Ptr CInt -> CInt))

getNumberOfCols :: Ptr CInt -> CInt 
getNumberOfCols p = 1

foreign import ccall "wrapper"
  wrapNumberOfCols :: (Ptr CInt -> CInt) -> IO (FunPtr (Ptr CInt -> CInt))

getValue :: Ptr CInt -> CInt -> CInt -> CWString
getValue p r c = do
  unsafePerformIO $ newCWString “Str"

foreign import ccall "wrapper"
  wrapGetValue :: (Ptr CInt -> CInt -> CInt -> CWString) -> IO (FunPtr (Ptr CInt -> CInt -> CInt -> CWString))

MAKE WRAPPERS

  wGetNumberOfRows <- wrapNumberOfRows getNumberOfRows
  wGetNumberOfCols <- wrapNumberOfCols getNumberOfCols
  wGetValue <- wrapGetValue getValue

CREATE TABLE

  table <- wxcGridTableCreate n
                              (castFunPtrToPtr wGetNumberOfRows)
                              (castFunPtrToPtr wGetNumberOfCols)
                              (castFunPtrToPtr wGetValue)

The key to making it work was to make a FunPtr and then use the castFunPtrToPtr. This was the main break through.

Now the question. There is one function with CWString:

getValue :: Ptr CInt -> CInt -> CInt -> CWString
getValue p r c = do
  unsafePerformIO $ newCWString “Str”

The problem is newCWString creates a string that must be freed, and wxWidgets does not free it. This results in a memory leak.

In a real application, I’ll probably store a String in a TVar so that some thread can keep it up to date. I could use other TVars to hold the CWString and free it each time a new value is created. But, it would be better if there was some way to guarantee it is freed, even with exceptions, etc. The best would be if when the function returns, it automatically freed the string.

Is there a way express the callback function so that it frees the string after the return?

Mike




On Apr 5, 2015, at 9:12 AM, Aldo Davide <aldodavide at gmx.com> wrote:

> Sorry but I am having trouble understanding your post, but here's some information you might find useful:
> 
> * If you want to pass a callback to a C function, you need to use a FunPtr. In particular, you need to create a "wrapper" foreign import that will allow you to convert a haskell function to a FunPtr that can be then passed to C and called by C. The docs on FunPtr [1] explain how to do this.
> 
> * Ptr is not a data constructor, its a type constructor, so e.g. `Ptr CInt` is a valid type, but `Ptr 4` is not a valid expression. If you want to store a value in the heap and then create a pointer to it, you can use the `with` function [2]. So e.g. in `with 5 $ \p -> ...`, p is a `Ptr CInt`. Remember that `Ptr`s are to useful for passing callbacks though.
> 
> 
> [1] https://hackage.haskell.org/package/base-4.8.0.0/docs/Foreign-Ptr.html#t:FunPtr
> [2] https://hackage.haskell.org/package/base-4.8.0.0/docs/Foreign-Marshal-Utils.html#v:with
> 
> Michael Jones, wrote:
>> I am having trouble figuring out how to pass callbacks to C.
>> 
>> Given the definition below it is not clear how to define a function and pass it. I tried:
>> 
>> getNumberOfRows :: CInt 
>> getNumberOfRows = 1
>> 
>>  table <- wxcGridTableCreate getNumberOfRows…
>> 
>> but the compiler barks at me:
>> 
>> src/MainGui.hs:577:32: Not in scope: data constructor ‘Ptr’
>> 
>> even through I do the imports:
>> 
>> import Foreign
>> import Foreign.C
>> 
>> There is also a _obj as the first value of wxcGridTableCreate and the callbacks, and I am not sure how to make a this* for it. I would have throughout that wxcGridTableCreate would return a Ptr.
>> 
>> The goal is to pass haskell functions into wxcGridTableCreate so the grid can call back to haskell.
>> 
>> Can someone show an example of just this one function, how to wrap a Ptr around it, and what to do with _obj?
>> 
>> 
>> DEFINITION
>> 
>> wxcGridTableCreate :: Ptr  a -> Ptr  b -> Ptr  c -> Ptr  d -> Ptr  e -> Ptr  f -> Ptr  g -> Ptr  h -> Ptr  i -> Ptr  j -> Ptr  k -> Ptr  l -> Ptr  m -> Ptr  n -> Ptr  o -> Ptr  p -> Ptr  q ->  IO (WXCGridTable  ())
>> wxcGridTableCreate _obj _EifGetNumberRows _EifGetNumberCols _EifGetValue _EifSetValue _EifIsEmptyCell _EifClear _EifInsertRows _EifAppendRows _EifDeleteRows _EifInsertCols _EifAppendCols _EifDeleteCols _EifSetRowLabelValue _EifSetColLabelValue _EifGetRowLabelValue _EifGetColLabelValue 
>>  = withObjectResult $
>>    wx_ELJGridTable_Create _obj  _EifGetNumberRows  _EifGetNumberCols  _EifGetValue  _EifSetValue  _EifIsEmptyCell  _EifClear  
>>    _EifInsertRows  _EifAppendRows  _EifDeleteRows  _EifInsertCols  _EifAppendCols  _EifDeleteCols  
>>    _EifSetRowLabelValue  _EifSetColLabelValue  _EifGetRowLabelValue  _EifGetColLabelValue  
>> foreign import ccall "ELJGridTable_Create" wx_ELJGridTable_Create :: Ptr  a -> Ptr  b -> Ptr  c -> Ptr  d -> Ptr  e -> Ptr  f -> Ptr  g -> Ptr  h -> Ptr  i -> Ptr  j -> Ptr  k -> Ptr  l -> Ptr  m -> Ptr  n -> Ptr  o -> Ptr  p -> Ptr  q -> IO (Ptr (TWXCGridTable ()))
>> 
>> typedef int   _cdecl (*TGridGetInt)(void* _obj);
>> typedef int   _cdecl (*TGridIsEmpty)(void* _obj, int row, int col);
>> typedef void* _cdecl (*TGridGetValue)(void* _obj, int row, int col);
>> typedef void  _cdecl (*TGridSetValue)(void* _obj, int row, int col, void* val);
>> typedef void  _cdecl (*TGridClear)(void* _obj);
>> typedef int   _cdecl (*TGridModify)(void* _obj, int pos, int num);
>> typedef int   _cdecl (*TGridMultiModify)(void* _obj, int num);
>> typedef void  _cdecl (*TGridSetLabel)(void* _obj, int idx, void* val);
>> typedef void* _cdecl (*TGridGetLabel)(void* _obj, int idx);
>> 
>> EWXWEXPORT(void*,ELJGridTable_Create)(void* self,void* _EifGetNumberRows,void* _EifGetNumberCols,void* _EifGetValue,void* _EifSetValue,void* _EifIsEmptyCell,void* _EifClear,void* _EifInsertRows,void* _EifAppendRows,void* _EifDeleteRows,void* _EifInsertCols,void* _EifAppendCols,void* _EifDeleteCols,void* _EifSetRowLabelValue,void* _EifSetColLabelValue,void* _EifGetRowLabelValue,void* _EifGetColLabelValue)
>> {
>> 	return (void*)new ELJGridTable (self,
>> 
>> 
>> 
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> 




More information about the Haskell-Cafe mailing list