Skip to content

Can't use with* as an input marshaller #93

Closed
@RyanGlScott

Description

@RyanGlScott

I'm trying to make a function hook that marshals a Storable instance as input. To that end, I want to use the with function (which, according to the c2hs docs, is a default marshaller). I'm using the following code snippets:

-- WithC2hsBug.chs
{-# LANGUAGE EmptyDataDecls, ForeignFunctionInterface #-}
module WithC2hsBug where

import Control.Applicative

import Foreign.C.Types
import Foreign.Marshal.Utils
import Foreign.Storable

#include "with_c2hs_bug.h"

data Foo
data Bar = Bar Int Int

instance Storable Bar where
    sizeOf _ = {#sizeof bar_t #}
    alignment _ = {#alignof bar_t #}
    peek p = Bar
      <$> (fromIntegral <$> {#get bar_t.y #} p)
      <*> (fromIntegral <$> {#get bar_t.z #} p)
    poke p (Bar y z) =
         ({#set bar_t.y #} p $ fromIntegral y)
      *> ({#set bar_t.z #} p $ fromIntegral z)

{#pointer *foo_t as FooPtr -> Foo #}
{#pointer *bar_t as BarPtr -> Bar #}

{#fun unsafe mutate_foo as mutateFoo
  { `FooPtr'
  , with* `Bar'
  } -> `()' #}
// with_c2hs_bug.h
#ifndef WITH_C2HS_BUG_H
#define WITH_C2HS_BUG_H

typedef struct {
    int y;
    int z;
} bar_t;

typedef struct {
    int x;
    bar_t bar;
} foo_t;

void mutate_foo(foo_t *foo, bar_t *bar);

#endif
// with_c2hs_bug.c
#include "with_c2hs_bug.h"

void mutate_foo(foo_t *foo, bar_t *bar) {
    foo->bar = *bar;
}

However, running c2hs WithC2hsBug.chs results in the error:

c2hs: CHS module contains errors:

WithC2hsBug.chs:30: (column 5) [ERROR]  >>> Syntax error!
  The phrase `with' is not allowed here.

A simple workaround is to make a synonym for with:

import Foreign.Ptr

with' :: Storable a => a -> (Ptr a -> IO b) -> IO b
with' = with

{#fun unsafe mutate_foo as mutateFoo
  { `FooPtr'
  , with'* `Bar'
  } -> `()' #}

Then everything works as expected.

Metadata

Metadata

Assignees

No one assigned

    Labels

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions