[Haskell-cafe] FFI: Creating a Storable for a C-struct composed of char arrays

2008-05-09 Thread Olivier Boudry
Hi all,

I'm trying to make RFC calls to SAP using the nwsaprfc library. Some structs
defined in the library contains arrays (byte or word arrays). For example:

typedef struct _RFC_ATTRIBUTES
{
SAP_UC dest[64+1];  /* RFC destination  */
SAP_UC host[100+1]; /* Own host name*/
SAP_UC partnerHost[100+1]; /* Partner host name*/
SAP_UC sysNumber[2+1]; /* R/3 system number*/
SAP_UC sysId[8+1];  /* R/3 system name  */
SAP_UC client[3+1]; /* Client   */
SAP_UC user[12+1];  /* User */
SAP_UC language[2+1];   /* Language */
   ... continued
}}RFC_ATTRIBUTES, *P_RFC_ATTRIBUTES;

I would like to create a Haskell Storable counterpart of this structure.
Using http://therning.org/magnus/archives/tag/hsc2hs as an starting point, I
could create Storable for structures containing fields with basic types.

Before working on the real data structures I wrote a more simple example to
play with:

-- File: ArrayStruct.h --
typedef struct _ArrayStruct
{
char a[10+1];
char b[20+1];
char c[30+1];
} ArrayStruct, *P_ArrayStruct;

-- File: ArrayStruct.c --
#include ArrayStruct.h

void
print_array_struct(ArrayStruct *f)
{
printf(%s\n, __FUNCTION__);
printf(f-a: %s\n, f-a);
printf(f-b: %s\n, f-b);
printf(f-c: %s\n, f-c);
}

-- File: HArrayStruct.hsc
{-# OPTIONS -ffi #-}
module Main
  where

import Foreign
import Foreign.C.Types

#include ArrayStruct.h

data HArrayStruct = HArrayStruct { a :: String, b :: String, c :: String }
type HarrayStructPtr = Ptr HArrayStruct

foreign import ccall static ArrayStruct.h print_array_struct
f_print_array_struct :: ArrayStructPtr - IO ()

instance Storable HArrayStruct where
  sizeOf _ = (#size ArrayStruct)
  alignment _ = alignment (undefined :: CInt)
  peek _ = error peek is not implemented
  poke ptr (HArrayStruct a' b' c') = do
(#poke ArrayStruct, a) ptr a'
(#poke ArrayStruct, b) ptr b'
(#poke ArrayStruct, c) ptr c'

printArrayStruct as = with as f_print_array_struct

main = printArrayStruct $ HArrayStruct { a=some, b=test, c=data }

-- End of files

Of course it won't work as HArrayStruct in file HArrayStruct.hs uses Strings
and String is not an instance of Storable.

Ideally I would need some sort of Storable array of char. Is
Data.Storable.Array the type I'm looking for? Could someone point me to some
code using the same kind of structures?

Thanks,

Olivier.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI: Creating a Storable for a C-struct composed of char arrays

2008-05-09 Thread Brandon S. Allbery KF8NH


On 2008 May 9, at 9:42, Olivier Boudry wrote:

Of course it won't work as HArrayStruct in file HArrayStruct.hs uses  
Strings and String is not an instance of Storable.


Ideally I would need some sort of Storable array of char. Is  
Data.Storable.Array the type I'm looking for? Could someone point me  
to some code using the same kind of structures?



You want CString (Foreign.C.String).

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI: Creating a Storable for a C-struct composed of char arrays

2008-05-09 Thread Olivier Boudry
Hi Brandon,

Thanks for your help, CString will work great for Char arrays, but what
about the 16bit-Word arrays? I was not clear in my previous post but the
structures used in the nwrfcsdk library can use 8bit or 16 bit chars
depending on a #define (#define SAPwithUNICODE).

Reading another post on FFI in this mailing list I found a link to the
following page http://haskell.org/haskellwiki/Modern_array_libraries with a
section on StorableArrayS. I'm now trying to use this example code to get
StorableArray to work.

I will try to use Data.Encoding to convert Haskell StringS to ASCII or UTF16
ByteStringS. Then unpack those ByteStringS to Word8 list and populate
StorableArrayS with the bytes. I hope it'll do the job for both Word8 and
Word16 arrays.

Olivier.

On Fri, May 9, 2008 at 9:52 AM, Brandon S. Allbery KF8NH 
[EMAIL PROTECTED] wrote:


 On 2008 May 9, at 9:42, Olivier Boudry wrote:

 Of course it won't work as HArrayStruct in file HArrayStruct.hs uses
 Strings and String is not an instance of Storable.

 Ideally I would need some sort of Storable array of char. Is
 Data.Storable.Array the type I'm looking for? Could someone point me to some
 code using the same kind of structures?


 You want CString (Foreign.C.String).

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
 system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
 electrical and computer engineering, carnegie mellon universityKF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] FFI: Creating a Storable for a C-struct composed of char arrays

2008-05-09 Thread Bulat Ziganshin
Hello Olivier,

Friday, May 9, 2008, 6:28:38 PM, you wrote:

 Thanks for your help, CString will work great for Char arrays, but
 what about the 16bit-Word arrays?

TString. they are used a lot for interfacing with Win32 API

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe