Stéphane Laurent
Stéphane Laurent

Reputation: 84529

Passing static array between C and Haskell with hsc2hs

Here is a simple h file:

/* file marchingcubes.h */
typedef struct {
   double x,y,z;
} XYZ;

To define the analogous type in Haskell, I'm using hsc2hs. I write this file CTypes.hsc:

{-# LANGUAGE ForeignFunctionInterface #-}
module CTypes 
  where
import           Foreign
import           Foreign.C.Types

#include "marchingcubes.h"

data CXYZ = CXYZ {
    __x :: CDouble
  , __y :: CDouble
  , __z :: CDouble
}

instance Storable CXYZ where
    sizeOf    __ = #{size XYZ}
    alignment __ = #{alignment XYZ}
    peek ptr = do
      x' <- #{peek XYZ, x} ptr
      y' <- #{peek XYZ, y} ptr
      z' <- #{peek XYZ, z} ptr
      return CXYZ { __x = x'
                  , __y = y'
                  , __z = z' }
    poke ptr (CXYZ r1 r2 r3)
      = do
          #{poke XYZ, x} ptr r1
          #{poke XYZ, y} ptr r2
          #{poke XYZ, z} ptr r3

No problem with and after the conversion to hs using hsc2hs.

Now I have another struct, containing a static array:

typedef struct {
   XYZ p[3];
} TRIANGLE;

How do I define the analogous type in Haskell in a hsc file ? Can I have something like:

data CTRIANGLE = CTRIANGLE {
  __p :: [CXYZ]
}

? How would I define the Storable instance ? I've found a couple of questions of SO about arrays and the FFI but nothing allowing me to solve this question.

UPDATE

I've done:

data CTRIANGLE = CTRIANGLE {
  __p :: [CXYZ]
}

instance Storable CTRIANGLE where
  sizeOf    __ = #{size TRIANGLE}
  alignment __ = #{alignment TRIANGLE}
  peek ptr = do
    p' <- peekArray 3 $ #{ptr TRIANGLE, p} ptr
    return CTRIANGLE { __p = p' }
  poke ptr (CXY r1) = do
    pokeArray (#{ptr TRIANGLE, p} ptr) r1

And hsc2hs generates:

instance Storable CTRIANGLE where
  sizeOf    __ = (72)
{-# LINE 37 "CTypes.hsc" #-}
  alignment __ = 8
{-# LINE 38 "CTypes.hsc" #-}
  peek ptr = do
    p' <- peekArray 3 $ (\hsc_ptr -> hsc_ptr `plusPtr` 0) ptr
{-# LINE 40 "CTypes.hsc" #-}
    return CTRIANGLE { __p = p' }
  poke ptr (CXY r1) = do
    pokeArray ((\hsc_ptr -> hsc_ptr `plusPtr` 0) ptr) r1
{-# LINE 43 "CTypes.hsc" #-}

Now I have to test to see whether this works.

Upvotes: 2

Views: 198

Answers (1)

St&#233;phane Laurent
St&#233;phane Laurent

Reputation: 84529

The code I gave in the update works :)

In marchingcubes.hsc:

data CTRIANGLE = CTRIANGLE {
  __p :: [CXYZ]
} deriving Show

instance Storable CTRIANGLE where
  sizeOf    __ = #{size TRIANGLE}
  alignment __ = #{alignment TRIANGLE}
  peek ptr = do
    p' <- peekArray 3 $ #{ptr TRIANGLE, p} ptr
    return CTRIANGLE { __p = p' }
  poke ptr (CTRIANGLE r1) = do
    pokeArray (#{ptr TRIANGLE, p} ptr) r1

foreign import ccall unsafe "testTriangle" c_testTriangle
  :: CDouble -> CDouble -> CDouble 
  -> IO (Ptr CTRIANGLE)

Now let's check. I do a file marchingcubes.c:

#include <stdlib.h>
#include "marchingcubes.h"

TRIANGLE* testTriangle(double a, double b, double c){
  XYZ xyz;
  xyz.x = a;
  xyz.y = b;
  xyz.z = c;
  TRIANGLE *tri = malloc(sizeof(TRIANGLE));
  tri[0].p[0] = xyz;
  tri[0].p[1] = xyz;
  tri[0].p[2] = xyz;
  return tri;
}

And I do a module:

module Lib
  where
import           CTypes
import           Foreign

someFunc :: IO CTRIANGLE
someFunc = do
    ptr <- c_testTriangle 1 2 3
    peek ptr

Test:

Prelude Lib> someFunc
CTRIANGLE {__p = [CXYZ {__x = 1.0, __y = 2.0, __z = 3.0},CXYZ {__x = 1.0, __y = 2.0, __z = 3.0},CXYZ {__x = 1.0, __y = 2.0, __z = 3.0}]}

This is the desired result :)

And don't forget

  include-dirs:        C
  C-sources:           C/marchingcubes.c

in the cabal file.

Upvotes: 2

Related Questions