[Haskell-cafe] [ANN] Haskell FFI Tutorial
Evan Laforge
qdunkan at gmail.com
Thu Nov 13 18:49:49 UTC 2014
On Wed, Nov 12, 2014 at 10:23 PM, Donn Cave <donn at avvanta.com> wrote:
> Maybe it does, and I only need a clue to the syntax. I have seen
> it used only for the size of the struct; I'm looking for the size
> of a field - and devoid of parentheses or other adornments, so I
> can tack it onto something like Word or Int. You could define
> type aliases for other variable-size foreign types, like Float8
> etc. and use #fieldsize to select them.
Oh I see. Maybe this:
#let fieldsize t, f = "%lu", (unsigned long)sizeof(((t *)0)->f)
c :: Word#{fieldsize example, c}
Of course you will wind up with Word64 for a double which is not that
great, and you lose signedness. The hsc_type macro has some
ridiculous but effective hackery to figure that out. So I bet a
#fieldtype macro can be defined without too much trouble, perhaps
without even having to modify hsc2hs.
> I don't know language-c. Lots of interesting potential there
> if it works well.
Just because I was curious, I wrote up an implementation last night.
It converts:
typedef int xy_t;
struct example { xy_t a; };
to
module Example_generated where
import qualified Example as M
#let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t
(y__); }, y__)
-- struct example
sizeOf_example :: Int
sizeOf_example = #size example
alignment_example :: Int
alignment_example = #{alignment example}
poke_example_a :: (#type xy_t) -> Ptr M.Example -> IO ()
poke_example_a = (#poke example, a)
peek_example_a :: Ptr M.Example -> IO (#type xy_t)
peek_example_a = (#peek example, a)
Of course now it occurs to me that if instead I emitted the typedef as
'type Xy_t = CInt' then I could hardcode the primitive C types and not
need #type anymore. I'd want to emit type synonyms anyway for
function typedefs. And naturally further complexity is in store for
declarations like 'char c, *const *s'. One thing is I just ignore
unnamed structs, since I couldn't figure out how to write a #poke for
them.
And then of course I want to filter by header so I don't always
generate 50 zillion declarations from system headers, and now using
#type instead of type synonyms looks better, otherwise I wind up
needing hs versions of all system headers.
So it seems feasible, but is naturally fraught with details that will
turn it into a real project rather than a quick hack. Since I don't
really plan to write any more FFIs in the near future, that's where
I'll leave it :)
Your #fieldtype macro certainly seems more practical to get something
useful working quickly.
More information about the Haskell-Cafe
mailing list