haskell / c2hs

c2hs is a pre-processor for Haskell FFI bindings to C libraries
http://hackage.haskell.org/package/c2hs
Other
198 stars 50 forks source link

Cannot recognize C type aliases #169

Open kseo opened 8 years ago

kseo commented 8 years ago

Here is a snippet of the C header file that I want to create a binding for:

#include <stddef.h>

typedef struct _my_string_utf8_t {
  char* str;
  size_t length;
} my_string_utf8_t;

typedef my_string_utf8_t my_string_t;

void my_string_free(my_string_t* value);
void my_string_utf8_free(my_string_utf8_t* value);

my_string_t is a type alias for my_string_utf8_t.

{-# LANGUAGE ForeignFunctionInterface #-}

#include "foo.h"

module Foo where

import Foreign.C.Types
import Foreign.Marshal
import Foreign.Ptr
import Foreign.Storable

data MyStringUtf8 = MyStringUtf8
  { str'MyStringUtf8 :: Ptr CChar
  , length'MyStringUtf8 :: CSize
  }
{#pointer *my_string_utf8_t as MyStringUtf8Ptr -> MyStringUtf8#}

instance Storable MyStringUtf8 where
  sizeOf _ = {#sizeof my_string_utf8_t#}
  alignment _ = {#alignof my_string_utf8_t#}
  peek p = MyStringUtf8
    <$> {#get my_string_utf8_t->str#} p
    <*> {#get my_string_utf8_t->length#} p
  poke p x = do
    {#set my_string_utf8_t->str#} p (str'MyStringUtf8 x)
    {#set my_string_utf8_t->length#} p (length'MyStringUtf8 x)

type MyString = MyStringUtf8
{#pointer *my_string_t as MyStringPtr -> MyString#}

{#fun unsafe my_string_free as ^ {id `MyStringPtr'} -> `()' #}
{#fun unsafe my_string_utf8_free as ^ {id `MyStringUtf8Ptr'} -> `()' #}

I created a Haskell type alias MyString and used its pointer type, MyStringPtr in defining the function hook for my_string_free. However, the binding for my_string_free fails to recognize my_string_t type and used Ptr () instead of MyStringPtr. It seems c2hs cannot recognize the C type alias typedef my_string_utf8_t my_string_t;.

foreign import ccall unsafe "Foo.chs.h my_string_free"
  myStringFree'_ :: ((C2HSImp.Ptr ()) -> (IO ()))

The binding for my_string_utf8_free is created as I expected:

foreign import ccall unsafe "Foo.chs.h my_string_utf8_free"
  myStringUtf8Free'_ :: ((MyStringPtr) -> (IO ()))

I am not sure why c2hs used MyStringPtr instead of MyStringUtf8Ptr though.