C-structs: C-Structs implementation for Haskell

[ c, data, foreign, library, mit, structures ] [ Propose Tags ]

C-structs lets you create correct C structs in Haskell. These can be used for FFI calls, import as well as exports. This package is part of the development efforts for the Python library Pythas. Pythas provides an interface to import Haskell modules.

Note: As of GHC 8.10 structs cannot be passed by value, only by reference.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.1, 0.2.0.1, 0.2.0.2, 0.2.0.3
Change log CHANGELOG.md
Dependencies base (>=3.0.0 && <5.0.0), template-haskell (>=2.2 && <2.17) [details]
License MIT
Copyright (c) 2020 Simon Plakolb
Author Simon Plakolb
Maintainer s.plakolb@gmail.com
Category foreign, c, structures, data
Home page https://github.com/pinselimo/cstructs-in-haskell#readme
Source repo head: git clone https://github.com/pinselimo/cstructs-in-haskell
Uploaded by SimonPlakolb at 2021-03-30T13:36:33Z
Distributions
Downloads 644 total (13 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2021-03-30 [all 1 reports]

Readme for C-structs-0.2.0.2

[back to package description]

C-Structs in Haskell Haskell CI Hackage CI Hackage Version Dependencies of latest version on Hackage

C-structs lets you create dynamically typed and correctly padded C structs in Haskell. These can be used for FFI calls, imports and exports. This package is part of the development efforts for the Python library Pythas. Pythas provides an interface to import Haskell modules.

Note: As of GHC 8.10 structs cannot be passed by value, only by reference.

Usage

You can use these types as a classic hackage package. The library has no other dependencies than some of the Foreign.* modules contained in base.

Basics

λ> import Foreign.C.Structs
λ> s = Struct2 1 2 :: Struct2 Int Int

can be interpreted as an equivalent to:

struct Struct2 {
    int s21st;
    int s22nd;
};

struct Struct2 s;
s.s21st = 1;
s.s22nd = 2;

or with Python's ctypes:

>>> from ctypes import Structure, c_int
>>> class Struct2( Structure ):
...     _fields_ = [("s21st", c_int), ("s22nd", c_int)]
...
>>> s = Struct2(1,2)

On memory all of these examples should have the exact same representation. A pointer to either s can then be exchanged with the other and used in a foreign call.

FFI usage

The following shows an example of a foreign import of a struct Struct2 as defined above:

struct Struct2 *foo (void) {
    struct Struct2 *val;
    val = malloc (sizeof (struct Struct2));
    val->s21st = 42;
    val->s22nd = 63;
    return val;
}

can be imported in a Haskell module as follows:

{-# LANGUAGE ForeignFunctionInterface #-}

import Foreign.Ptr (Ptr)
import Foreign.Storable (peek)
import Foreign.Marshal.Alloc (free)
import Foreign.C.Types (CInt)
import Foreign.C.Structs (Struct2)

foreign import ccall "foo" foo :: Ptr (Struct2 CInt CInt)

main = do
    putStrLn "Reading values from C.."
    s <- peek foo
    free foo
    putStrLn "Received:"
    putStrLn $ show s

For a more elaborated usage examples checkout Pythas in conjunction with Pythas-Types. It uses Foreign.C.Structs to declare its storage functions for Haskell tuples. In addition, its Array and Linked List instances are based on this library.

More fields

Currently C-structs exports types featuring up to six fields. If you require more, you can easily create them using Template Haskell and the structT function:

structT 8

will create:

data Struct8 = Struct8
    { s81st :: a
    , s82nd :: b
    , s83rd :: c
    , s84th :: d
    , s85th :: e
    ...
    } deriving (Show, Eq)

instance Storable Struct8 ...

Accessors

The naming scheme of the accessor functions follows the names of the ordinal numbers. This can be inconvenient in a Template Haskell context. For these situations Foreign.C.Structs exposes the acs function:

$(acs 8 2)

This expression will be spliced into a function taking a Struct8 and extracting its second field.

Testing

Identity properties are tested with QuickCheck to ensure that peek and poke are reversible. The result of sizeOf is dependent on the order of types. Its correctness can only be tested with HUnit. The alignment function is trivial and only tested implicitly through sizeOf.

Imports from C are tested in CTest.hs and together with the identity tests form the guarantee that also exports to C are consistent. Until Travis CI became unusable for FOSS projects all tests were performed for all available GHC/CABAL/Stack versions through the Stack CI script on both Linux and OSX to ensure maximum compatibility. Now only the latest GHC versions are checked on Linux, macOS and Windows using cabal through GitHub Actions. Compatibility with older versions of GHC should however be kept.

License

This part of Pythas is licensed under the MIT License. Please be aware that the full Pythas package is under LGPLv3. Refer to the accompanying LICENSE or COPYING files for details.