Re: Strict arguments with foreign import

2005-03-16 Thread Marcin 'Qrczak' Kowalczyk
Andre Pang <[EMAIL PROTECTED]> writes:

> I'm just wondering -- for "primitive" C types (int, float, char, etc),
> why was the decision made in the FFI to have function declarations
> look like e.g.
>
>   foreign import ccall "math.h sin" sin :: CDouble -> CDouble
>
> rather than
>
>   foreign import ccall "math.h sin" sin :: !CDouble -> !CDouble

Haskell doesn't reflect strictness of functions in their types,
no matter whether foreign or not.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
FFI mailing list
FFI@haskell.org
http://www.haskell.org/mailman/listinfo/ffi


Re: Haskell PPL bug fix

2004-10-15 Thread Marcin &#x27;Qrczak' Kowalczyk
Axel Simon <[EMAIL PROTECTED]> writes:

> the Haskell compiler GHC replaces the memory allocator in GMP with
> one that allocates from the Haskell heap. Pedro managed to link the
> PPL with a private version of GMP but that is not a feasible
> solution in the long term.

I second this. I would like to make a bridge between Haskell and my
language Kogut, but my runtime uses GMP for big integers. I don't
change the allocation functions from the default, to make possible
to have multiple libraries using GMP in a single program, as long as
others are similarly cooperable. Unfortunately GHC does change them,
and without checking I can say that it will not work.

I don't think that I should make a private copy of GMP for my
language. After all, it doesn't change the default settings,
and it's GHC which breaks the GMP interface. IMHO it should either
have a private copy of GMP with changed names, or stop changing
GMP allocation functions, accepting the slowdown.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: C.Types

2004-09-06 Thread Marcin &#x27;Qrczak' Kowalczyk
"Daniel Müller" <[EMAIL PROTECTED]> writes:

> foreign import ccall calc :: CInt -> CInt -> CInt
>
> calculate :: Int -> Int -> CalcType
> calculate a b 
> | ...
> | ...
> | otherwise = calc a b
>
>
> Unfortunately I got an error. What shall I do?

Use fromIntegral to convert between CInt and Int, and something for
CalcType depending on what it is.

(It would help if you told *what* error, but I guessed.)

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: [Haskell] ANNOUNCING: The Haskell Bookstore

2004-06-25 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z pią, 25-06-2004, godz. 12:30 +0200, Daan Leijen napisał(a):

> It seems to me that returning the old value is always good
> enough right?  Here is an implementation of "atomicModifyIORef"
> with the current type in terms of a function "proposedModifyIORef" with
> type (2).
> 
> atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
> atomicModifyIORef ref f
>= do old <- proposedModifyIORef ref (fst . f)
> return (snd (f old))

It applies f twice, which may duplicate work.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


RE: Extension to the FFI to allow macro expansions to be avoided

2004-04-16 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z pią, 16-04-2004, godz. 15:25 +0100, Simon Marlow napisał:

> I wondered about that (while writing my last post) but it still seems
> like a hefty price to pay for the small number of problematic cases we
> have, and given that you can already write the C stubs by hand to get
> the desired effect.  Hmm, perhaps this falls in to the category of
> something we expect an external tool to do?

I think the preferred way to interface to a C library is via a
typechecked C source, not via binary linking.

But if it's made harder, programmers are tempted to avoid that.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: Extension to the FFI to allow macro expansions to be avoided

2004-04-16 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z czw, 15-04-2004, godz. 18:14 -0700, Fergus Henderson napisał:

> When using the "--target asm" option, which tells the Mercury compiler to
> compile directly to assembler, the Mercury compiler will generate some
> C glue code to handle the FFI interfacing pragmas.

Which - in case it's a plain function - is an unnecessary extra function
call.

Perhaps we should differentiate by a calling convention between linking
to a function directly and generating a source-level C call?

The calling conventions we know would correspond to linking to them
directly. They would perform the necessary magic to turn off macros when
compiling via C, and they would not need a C compiler when compiling via
assembler. There is no need for specifying a C header in this case.

Another calling convention would generate a function wrapper with proper
argument types. It would need "foreign type" declarations and included
headers. The wrapped calling convention in this case is of course
irrelevant, so it's a calling convention rather than a separate flag.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 13

2003-11-02 Thread Marcin &#x27;Qrczak' Kowalczyk
W liście z sob, 01-11-2003, godz. 02:16, John Meacham pisze:

> my implementation converts unrepresentable characters to '?'. But
> a case could be made for throwing a CharsetConversion exception of some
> sort or simply eliding invalid characters. I am not sure what is best,

It depends on the application:

- When displaying email on screen, it's best to transliterate by
  removing accents etc.

- When communicating with a database, it's best to report an error
  so configuration can be fixed (perhaps charsets are wrongly set).

- When converting HTML, it's best to provide a hook to replace
  unrepresentable characters with &#;

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: CWString

2003-08-28 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia czw 28. sierpnia 2003 12:34, Simon Marlow napisał:

> The only right way to do this, it seems, is to generate the tables from
> UnicodeData.txt.  However, I'm prepared to live with the current
> solution as long as we document its shortcomings.  After all, it does
> the right thing on the majority of our installed base.

I have some UnicodeData.txt-generated predicate functions & toUpper/toLower 
in QForeign. There doesn't seem to be an official mapping from Unicode 
character categories to various predicates (I've once tried to find one 
asking on Unicode groups with no success - I was told that for good 
definitions of some predicates character categories are not precise 
enough), or even the set of useful predicates, and it's not clear which 
predicates should recognize only ASCII characters (most probably isDigit). 
It's all to be designed, perhaps even by changing Haskell 98 a bit.
QForeign at least has some machinery to generate tables and functions from 
UnicodeData and some proposals of predicate definitions.

I think these functions should all be locale-indepentent, and ideally 
Haskell should have a portable definition - perhaps in terms of character 
categories.

Usable wcwidth requires it to be the same on both sides of a remote 
terminal;  suggests
a definition of wcwidth. wcwidth was removed from the ANSI C addendum which 
defined other wide character functions, but it's in some POSIX standards.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: CWString

2003-08-26 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia wto 26. sierpnia 2003 02:04, John Meacham napisał:

> my implementation is pretty hairy, but can be improved. it currently
> only works on systems where __STDC_ISO_10646__ is defined, but
> fortunatly, I have never come across a system where it was not defined
> and it implemented wchar_t at all.

AFAIK on FreeBSD wchar_t is not Unicode. It generally has broken locale and 
Unicode support in other respects as well.

> the localized versions of the CString routines are named with LCString,
> which stands for localized C string...

In future they should replace current CString functions which can be 
renamed to Latin1CString.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: The Errno Story

2003-07-25 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia pią 25. lipca 2003 16:52, Dean Herington napisał:

> John's first suggested alternative above seems very appealing to me, as it
> seems neatly to fix the fundamental design flaw in `errno`: that
> determining the success/failure of a system call is separated from the call
> itself.  I'm surprised more sentiment in its favor has not shown up.  What
> are the disadvantages of such a solution?

That you usually wrap functions which set errno in higher order functions 
which translate it to exceptions (there are such functions ready in FFI 
libraries), so it doesn't matter how it's implemented under the hood. And the 
current mechanism, with the change for threads, is simpler.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: stdcall

2003-07-22 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia wto 22. lipca 2003 13:52, Ross Paterson napisał:

> The proposal was to have this in addition to ccall.  This convention
> is currently called CALLCONV in the network, GLUT and OpenGL packages,
> with hacks to turn it into ccall or stdcall.  I think it makes sense to
> regularize it as stdcall.

In gcc on Unix you can declare a function as "stdcall" and it will change the 
calling convention accordingly. I don't know of any library that uses it, but 
this shows that "stdcall" is used as a name of this particular calling 
convention for ix86 even on Unix.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: More Finaliser Trouble

2003-07-13 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia nie 13. lipca 2003 21:20, Alastair Reid napisał:

> We dropped Haskell finalizers because neither Hugs nor NHC could implement
> them and implementing them would pretty much require them to implement
> preemptive concurrency (i.e., multiple threads each with their own stacks).

Not necessarily preemptive. Hugs-like concurrency would be OK. The point is to 
be able to protect mutable structures by mutexes.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 9

2003-06-09 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia wto 10. czerwca 2003 01:00, Ross Paterson napisał:

> I meant to say that you can't pass an HsDouble to a "polymorphic" C
> function expecting (void *),

You can pass a pointer to double.

Imagine a hashtable implemented in C. It will most probably store void *
as values. You can use it for any concrete value type by storing pointers
to values, probably living in malloced memory, unless they already are 
pointers, in which case it's implicitly convertible to and from void *.

Imagine a C API which gives you handles to pictures as opaque values.
You are supposed to use its functions only to work on the picture data.
You want to store pictures in a hashtable. If it gives you type Picture and 
doesn't say how the type is represented, you must malloc(sizeof Picture)
and store the pointer in the hashtable. But if it explicitly says that Picture
is a pointer, or it even uses Picture *, then you can store them without 
additional wrapping.

> so why should you be able to pass an HsStablePtr?

Because we can arrange that you don't need to wrap it in an additional 
pointer. Even if it was safe to cast them void *, you could not be sure -
you can't portably conclude it from the fact that it's an integral value.
Why not to provide the convenience?

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: ANN: H98 FFI Addendum 1.0, Release Candidate 10

2003-06-02 Thread Marcin &#x27;Qrczak' Kowalczyk
Dnia nie 1. czerwca 2003 23:55, Alastair Reid napisał:

>   introduces a type T whose only value is bottom.
> ]]
>
> This semantics is obviously flawed though because it would suggest that any
> two values of type T are equal (and equal to bottom) and that optimizations
> based on that equality are valid.

Since no values of type T are ever created or manipulated, what difference 
does it make?

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi


Re: Finalizers: conclusion?

2002-10-22 Thread Marcin &#x27;Qrczak' Kowalczyk
22 Oct 2002 01:32:55 +0100, Alastair Reid <[EMAIL PROTECTED]> pisze:

>   -- keepAlive x y ensures that the finalizer for y is not run
>   -- until after the finalizer for x has run to completion.

What if I do keepAlive p1 p2 >> keepAlive p2 p1?
They will never be collected?

-- 
  __("<  Marcin Kowalczyk
  \__/ [EMAIL PROTECTED]
   ^^http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Updates to FFI spec

2002-09-13 Thread Marcin &#x27;Qrczak' Kowalczyk

12 Aug 2002 11:33:41 +0100, Alastair Reid <[EMAIL PROTECTED]> pisze:

> (In the image processing example, images were megabytes and an
> expression like (x + (y * mask)) would generate 2 intermediate images
> (several megabytes) while doing just 2 reductions in Haskell.)

OCaml allows the programmer to specify an approximate amount of
foreign memory in its wrapped C pointers. Maybe it's a good idea?

-- 
  __("<  Marcin Kowalczyk
  \__/ [EMAIL PROTECTED]
   ^^http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: isNull{Fun,}Ptr

2002-09-11 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 11 Sep 2002 16:42:55 +1000 (EST), Manuel M T Chakravarty <[EMAIL PROTECTED]> 
pisze:

> Sure, but there is also 
> 
>   null = (== [])
> 
> in the Prelude and `Maybe.isNothing'.

Because they work even if list element type or the type argument of Maybe
isn't Eq. There is no analogous need for null pointers (as for numeric 0).

-- 
  __("<  Marcin Kowalczyk
  \__/ [EMAIL PROTECTED]
   ^^http://qrnik.knm.org.pl/~qrczak/

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Report, CVS Id 1.11

2001-08-24 Thread Marcin &#x27;Qrczak' Kowalczyk

24 Aug 2001 12:20:41 -0600, Alastair David Reid <[EMAIL PROTECTED]> pisze:

>   Let's add some asserts to the affected code so that we'll get warnings
>   when we try to compile the code on a system that breaks these assumptions.
>   Something like this:
> 
>   #if SIZEOF_INT != SIZEOF_PTR
>   #error "Pointer difference operation could overflow - please fix"
>   #endif

In ghc Int always has the same size as the pointer. Or did you mean
something other?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Report, CVS Id 1.11

2001-08-21 Thread Marcin &#x27;Qrczak' Kowalczyk

Sun, 19 Aug 2001 23:14:59 +1000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> * I am still not convinced that we need
>   `Storable.destruct'.  For deallocating special purpose
>   structures that need a deep traversal, shouldn't we just
>   use a custom function?

Without destruct code like

with haskellValue $ \ptr -> do
just use ptr, no allocation nor deallocation

would be correct in 99% of cases, except that for some types it
leaks memory (when the only reasonable implementation of poke is not
idempotent wrt. allocated memory).

These cases include char* inside a struct, assumed to point to
a memory private to this struct.

Yes, it can be called by hand, just as C++ destructors could be
called by hand. But places where it should be called are automatically
predictable, as long as it is well defined which memory is initialized
and which is not. Since with* functions automatically call poke, they
should automatically call something which undoes side effects of poke.

You might avoid Storable instances for such types and only use
opaque ForeignPtrs to heap-allocated objects. In this case, if all
the allocation and deallocation is handled by foreign code, destruct
is not needed.

It makes sense however for more complex types which are made instances
of Storable, i.e. where memory allocation is done by Haskell. I
imagine that allocation in Haskell will be especially good idea now
when Simon Marlow made alloca faster than malloc.

A Haskell-C++ interfacing tool would hook destructors to destruct.

> * I am also not really convinced about
>   `MarshalUtils.withMany'.  There may be situations, where
>   such a function is handy, but should it really be in the
>   standard libraries?

It's not so easily written by hand. Explicit recursion is needed,
AFAIK it can't be simply written in terms of foldr, mapM etc. So it
requires a variable definition, and thus would be written in this
very form where needed, instead of "inlined".

It's the mapM of the continuation monad, where the monad is
/\a. (a -> res) -> res
and thus can't be made instance of class Monad without wrapping in
a newtype. FFI uses the "(a -> IO b) -> IO b" type pattern much.

>   Moreover, it isn't really marshalling specific - it is JAFL
>   (Just Another Function on Lists).

Yes, but it's not available elsewhere.

> PtrDiff
> ~~~
> Maybe after all, `PtrDiff' wasn't that bad an idea.  To
> assume that a pointer difference fits into an `Int' (what we
> do at the moment) is pretty dodgy.  Remember that all that
> H98 requires of an `Int' is that it has >=30 bits.  IMHO,
> this is pretty weak for a general representation of a
> pointer difference.

Haskell already uses Int for these kinds of lengths: array indices
are mapped to Int, default implementations of list functions use Int
for measuring lengths.

On 64-bit processors Int is 64-bit (or 63-bit when targeting OCaml
etc.), so the need of handling objects larger than a gigabyte in 32-bit
architectures is temporary, if at all. Haskell has the advantage over
C that there is no temptation to express all sized integer types as
{char,short,int,long}, so there is no reason for Int to be too small.

On 32-bit processors C implementations generally don't allow objects
larger than 32 bits anyway.

> The annoying thing about our old use of `PtrDiff' was that
> it made `plusPtr' a pain to use (as we had to cast the
> offset to a `PtrDiff' first).  A simple solution would be
> 
>   plusPtr :: Integral i => Ptr a -> i -> Ptr b

It would make "ptr `plusPtr` 1" use Integer by default (with a warning
with -Wall).

What about peekArray etc.? It's not clear where to stop.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: comments on FFI 1.4

2001-06-13 Thread Marcin &#x27;Qrczak' Kowalczyk

On Wed, Jun 13, 2001 at 04:22:16AM +1000, Fergus Henderson wrote:

> - Should `CInt' be guaranteed to have the same representation
>   as C's `int', or just the same range of values?

You can't discover the actual representation anyway. What it
guaranteed is that you can write CInt on the Haskell side and it
will correctly call a C function declared with int, and vice versa
for exporting, with all values preserved, and that the Bounded CInt
instance corresponds to INT_{MIN,MAX} in C, and that the Storable CInt
instance works in the same way as storing ints under pointers in C,
and some other instances should match the corresponding C behavior
(these things are probably nowhere explicitly said but should be).

How the Haskell implementation manages to provide it is its private
business. For example in ghc all Int8, Int16 and Int32 (and Int64 on
a 64-bit platform) have the same internal representation.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTĘPCZA
QRCZAK

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Report, CVS Id 1.5

2001-06-13 Thread Marcin &#x27;Qrczak' Kowalczyk

On Tue, Jun 12, 2001 at 11:00:09AM +0200, Sven Panne wrote:

> > (I still think that the "static" keyword is not necessary.)
> 
> How would you import a function named "static" then?

There can't be such a function: it's a keyword in C :-P

And even if it was allowed in C, without any special meaning of
"static" inside the external entity specification there would be
no problem with importing it - just write "static".

What the lack of static takes away is the ability to import a function
called "dynamic" or "wrapper". I don't think that it's a big limitation
considering hundreds of names which are taken away by a Haskell's
runtime system.

Anyway, we could call them "_dynamic" and "_wrapper" to indicate
that they are magical in some sense - using such names for external
function names would be a violation of ISO/ANSI C rules (they are
reserved for the C implementation).

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTĘPCZA
QRCZAK

___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Report, CVS Id 1.5

2001-06-09 Thread Marcin &#x27;Qrczak' Kowalczyk

Sat, 09 Jun 2001 23:25:08 +1000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> The new definition reduces the problem of defining exactly
> which types can be marshalled to a reference to Storable.

Being just Storable is not enough to generate a foreign call. For
example floating point arguments might be passed in different registers
than integer arguments. So what should happen when the programmer
makes a Storable instance for some weird type?

(Storable.peek would be needed for importing, not exporting, and vice
versa for poke - you wrote it backwards.)

> Consequently, Storable must be derivable.

Ok, but it's not enough.

I hope that generics will subsume some uses of deriving, but for that
they must be fixed (as I told a long time ago). In particular I hope
that generics will cover Storable and Dynamic. It seems that even if
they are fixed, it's not enough to write generic instances of these
classes:-(

> foreign import "static foo" foo :: t
> foreign import "static" foo :: t
> foreign import ""   foo :: t
> 
>   Is the last one nice?

Not nice and not necessary if the whole "" can be omitted, but it
makes rules more consistent. In particular this should be legal:
foreign import "&" foo :: Ptr t
so with "static" too...

(I still think that the "static" keyword is not necessary.)

> I have added a restriction: exported variables must be
> defined by a function or pattern binding in the *same*
> module.
> 
> This shouldn't be a serious restriction in practice, but
> may make live easier for some systems.

Why? The implementation could always generate a wrapper.

And it is possible to do a non-FFI export of entities defined in
other modules (even written qualified), so FFI exporting rules could
be consistent with it.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Report, CVS Id 1.4

2001-06-01 Thread Marcin &#x27;Qrczak' Kowalczyk

01 Jun 2001 13:35:40 -0600, Alastair David Reid <[EMAIL PROTECTED]> pisze:

> Even if rarely used, I think it is easier to teach people to use
> it if we say there are two forms of definition (safe and unsafe,
> static and dynamic, etc.)

But there are not two forms. With the new proposal you import
either an explicitly named thing or an automagically generated
converter Haskell->FunPtr or an automatically generated converter
FunPtr->Haskell.

They are not orthogonal attributes. The latter forms are like special
cases of the first form.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Report, CVS Id 1.4

2001-06-01 Thread Marcin &#x27;Qrczak' Kowalczyk

Fri, 01 Jun 2001 18:36:01 +1000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

>   http://www.cse.unsw.edu.au/~chak/haskell/ffi.{ps.gz,tex}

I like it. Minor issues:
- import is not a specialid, it's already a reservedid.
- Safeness should be optional. (And maybe s/safeness/safety/ ?)
- Would anyone really use explicit "static"?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Again: FFI syntax

2001-05-29 Thread Marcin &#x27;Qrczak' Kowalczyk

Tue, 29 May 2001 10:37:54 +0200, Sven Panne <[EMAIL PROTECTED]> pisze:

> Just to restate my position: I'm against *always* wrapping the header file name
> in double quotes, unless
> 
>#include "foo/bar.h"
> 
> implies
> 
>#include 
> 
> if the first form is not found.

It does, but having "" and (ab)using it to mean <> would be bad -
if the current directory happens to contain a file with such name
then confusion begins.

I propose adding implicit "" if <> are not given explicitly.
As -#include in ghc does (it looks for "" or <> and adds "" if neither
is found; it might even not be necessary to allow explicit "" at all,
only explicit <> or implicit "").

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: extent strings

2001-05-15 Thread Marcin &#x27;Qrczak' Kowalczyk

On Tue, 15 May 2001, Sven Panne wrote:

> Personally, I'd prefer something like the above syntax, too, restricting
> oneself syntactically to (var|string)* for any future calling
> convention's import/export specification is not that hard. Completely
> switching to string land is a little bit of hack IMHO, but perhaps the
> advocates of this solution could explain their preference a little bit.

I propose the following guideline:

* what to import / as what to export - inside the string
* how to import/export - outside the string

This would imply:
- header to #include - inside
- & or label - inside or outside
- unsafety modifier (and other modifiers) - outside
- static methods / virtual methods / constructors - inside
- dynimp/dynexp - inside

> P.S.: Still no better naming suggestions for 'dynimp' and 'dynexp'?

Hmm...

For importing:
- call
- curry
- apply
- variants mangled to distinguish from ordinary identifiers
  (probably by adding underscores)
- I'm afraid that "mnemonic" symbols like (*)() or $ are too cute to be
  clear.

For exporting:
- closure
- new_function
- fun_ptr
- export_fun

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Definition

2001-05-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Sun, 6 May 2001 11:29:18 -0600 (MDT), Alastair Reid <[EMAIL PROTECTED]> pisze:

>> foreign export dynamic is a shortcut for importing an automatically
>> generated nontrivial C function, with argument type not conforming to
>> regular imports, which could not be written by hand. 
> 
> I don't get it.  How do you use a function with a type like:
> 
>   (Int -> IO Int) -> Addr
> 
> to import a C function?

*This* is an imported function.

Well, if I wanted to make it by hand, I would have to make a StablePtr
before, because I can't pass (Int -> IO Int) to a foreign function
directly.

In other words
foreign export dynamic exp :: (Int -> IO Int) -> IO Addr
is equivalent to
exp :: (Int -> IO Int) -> Addr
exp f = exp' =<< newStablePtr f

foreign import exp' :: StablePtr (Int -> IO Int) -> IO Addr
-- exp' generated by the Haskell compiler.

> Unless you're arguing that, since it brings a name into scope it
> can be thought of as a kind of import??? (But I don't think you
> are saying that.)

I am!

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Definition

2001-05-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Sorry for lots of small messages.

'label' can be spelled '&'. It's IMHO more intuitive, and reminds
that we get a pointer in Haskell and not the dereferenced value.

foreign import "&stdscr" stdScr :: Ptr Window

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Definition

2001-05-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 07 May 2001 00:14:32 +1000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> The import/export information is needed by the name analysis,
> which we better leave independent of the whole extent mess.

Export dynamic introduces a name, export static exports an existing
name. For that reason putting this distinction in extent seems strange
for me.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Definition

2001-05-06 Thread Marcin &#x27;Qrczak' Kowalczyk

6 May 2001 15:50:16 GMT, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> pisze:

> Export dynamic introduces a name, export static exports an existing
> name. For that reason putting this distinction in extent seems strange
> for me.

Moreover, export dynamic and import dynamic don't have fname or cid.

foreign import dynamic is a shortcut for importing an automatically
generated C function which could be easily written by hand. It fits
well into regular imports with a single distinguished magical extent.
All parameters are in the type, so it can be called "dynamic" or
"curry" or "apply" or whatever, perhaps with special characters to
distinguish the name from plain functions.

foreign export dynamic is a shortcut for importing an automatically
generated nontrivial C function, with argument type not conforming to
regular imports, which could not be written by hand. So it's actually
an *import*! It could be spelled as import with a magical name - again
all parameters are in the type.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Revised FFI syntax + typing

2001-05-04 Thread Marcin &#x27;Qrczak' Kowalczyk

I know that this is a silly argument, but Word is used internally in
RULES for fromIntegral to generate good code for conversions between
sized integers.

Since Word{8,16,32} and sometimes Word64 is represented as data-wrapped
Word#, it's easy to implement many conversions by delegation to the
conversion with source or target type replaced with Word.

This was actually what triggered me to add missing instances for Word
(Num and Integral were needed).

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Revised FFI syntax + typing

2001-05-03 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 03 May 2001 22:34:50 +0200, Sven Panne <[EMAIL PROTECTED]> 
pisze:

> Hmmm, I thought that the Word type itself is a GHC extension, the
> hslibs docs for module Word only talk about the explictly sized
> variants. OTOH the implementation exports Word, but for legacy
> reasons, IIRC.

Rather the opposite: I let it export Word not so long ago, together
with adding some instances. But unboxed arrays of Words were present
long before that: ByteArray (deprecated), MArray, IArray.

I don't agree that having a type of a fixed but unspecified size is evil.
You can query the sise - you don't have to assume any particular size -
and you have explicitly sized types as well.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI Definition

2001-04-18 Thread Marcin &#x27;Qrczak' Kowalczyk

Tue, 17 Apr 2001 18:05:48 +1000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

>   http://www.cse.unsw.edu.au/~chak/haskell/ffi.ps.gz

Some minor points:

In C int can't have 8 bits. It is guaranteed to represent at least
-2^15..2^15.

Your syntax puts modifiers between the calling convention and the
external id. I agree that it's consistent. Currently ghc accepts
unsafe only between the external id and the Haskell id, and dynamic
only instead the external id.

It should not matter that C allows colons in #include. Rules of the
#include argument are implementation dependent, and it should not
be a problem if a programmer can't name a header file included into
Haskell using a colon. He will have to choose a name without a colon.

But we could also cut the last colon instead of the first: a colon
is certainly not valid in a C identifier.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



QForeign-0.65 is out

2001-04-15 Thread Marcin &#x27;Qrczak' Kowalczyk

http://prdownloads.sourceforge.net/qforeign/qforeign-0.65.tar.gz

qforeign-0.65 (Apr 15, 2001)


* Make libraries for GHCi too (HS*.o).
* hsc2hs should work on Windows too (untested).
* Works with nhc98-1.02 too. ghc-4.09 support dropped.
* hsc2hs parser rewritten. #{stuff} added (like #stuff but self-delimited).
  Now correctly handles '--' in operators and backslash-newline pairs
  in C lexical world.
* Use {-# LINE #-} pragmas for nhc98 too.
* Zlib and Bzip2 express byte lists as [Word8] instead of String.
* QCError.errnoToIOError uses strerror instead of its own error strings,
  and uses FFI.mkIOError under nhc98 if available.
* Add destruct method to class Storable (thanks Wojciech Moczydlowski
  <[EMAIL PROTECTED]> for the suggestion).
* Add QCFile: conversion between Handle and FILE * (compiled when module
  Posix is available).
* Support readline-2.2.1 as well as readline-4.x.
* Support Unicode 3.1.0 in unidata. Characters up to 0x10. Better
  definitions of some character properties. More efficient GenUnicodeData.
* README is more interesting.
* License changed from GPL to LGPL.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI progress

2001-04-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Fri, 6 Apr 2001 09:04:32 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze:

> It seems a bit odd to have static/dynamic *outside* but "new"
> inside the language-specific string.  I suppose the justification
> is that 'new' is really a static method with a funny way to call it.
> Whereas the 'self' parameter on a dynamic call is treated specially.
> 
> So that's ok, but we should agree that's what we want.

Seems OK for me in the case of importing.

But what does foreign export mean in the context of Java or .NET?
Can whole classes be created? How does static/dynamic/new fit there?
In C functions are standalone, which is unlike Java.

In the C case there is no foreign name in dynamic imports and exports.
In Java there are: there is no distinguished function pointer type,
we are going to treat all classes as kind of function pointers with
multiple entry points. Looks ok?

I'm not familiar with Java's native methods. Can both static and
non-static methods be native? Can constructors be native? Shouldn't
foreign export dynamic generate a function which creates instances
of (an inner subclass of) some explicitly specified class?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: FFI - some comments

2001-04-05 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 5 Apr 2001 07:45:44 -0700 (PDT), Ronald Legere <[EMAIL PROTECTED]> pisze:

> KDirect: Looked at it abit. Pretty sparsely documented. I could not
> figure out how it fits in with the latest tools. How does QForeign
> relate to Foreign? What is an hsc file? Also it is pretty limitted
> in the marshalling.  No callbacks etc.

Here is the story of QForeign, hsc and KDirect.

One year ago the core 'foreign' declarations were already stable and
implemented in ghc (for sure) and nhc (probably already at that time).
The FFI documentation said that support for more complex marshalling
is delegated to separate tools.

Available tools, namely HDirect and Manuel's C2HS, were too heavy for
my taste. But Sven's modules provided by ghc: FFI (later renamed to
Foreign) and Marshal, were insufficient.

I realized that a few more functions would make the basic FFI
usable directly, without sophisticated preprocessors. I also wanted
to experiment with typed 'Ptr a' instead of amorphic 'Addr'. So I
merged ideas from ghc's module FFI and C2HS with my own FFI vision,
and QForeign was born.

QForeign evolved. The basic style of calling a C function while
marshalling arguments and results changed a few times. It got examples.
It suggested how to handle structs and enums. It became my Unicode
laboratory.

Since writing lots of small C functions for getting struct fields and
constants was painful, I wrote glue-hsc: a simple preprocessor which
translates a Haskell module with embedded C bits into a C program which
outputs a real Haskell module. It allows embedding snippets of C code
which are extracted into .c and .h files to be compiled separately.
The source file extension .hsc means: .hs + bits of C included.

QForeign was following changes in ghc and it also influenced ghc.
ghc got typed pointers, alloca, withForeignObj, C array support, hsc2hs
(renamed from glue-hsc), errno handling, C string support interface.
As soon as some QForeign's feature got into ghc, QForeign switched to
use it from ghc instead of providing it itself. If a feature mutated
during its path to ghc, QForeign reflected the change. ghc's FFI
support and my FFI vision were slowly converging.

I had to write a networking program at the University, so of course
I decided to use Haskell. That's why QForeign has pcap in examples.
I asked my admin to install ghc in students' lab. The latest stable
version was 4.08.1, so I #ifdefed parts of QForeign to support
ghc-4.08* too by providing its own typed pointers and Storable again
(no Unicode, no --add-package).

Supporting several ghc versions at once happened to be easy (hsc2hs
delegates #ifdefs to cpp). So I tried to port QForeign to nhc too
and it worked, after some bugs that I reported were fixed. So I
also thought about supporting hbc, which would require writing a
preprocessor which translates 'foreign' declarations to appropriate
hbc's magic, but hbc is dead, so I forgot it. Since Hugs recently got
'foreign' declarations, it might be possible to port QForeign to Hugs
in future, but its foreign module management looks hard.

QForeign and FFI modules provided by ghc-5.00 (to be released really
soon) are now very close, after Manuel put some marshalling utilities
into ghc and I backported them to QForeign as usual. The largest
difference is that QForeign makes real use of Unicode (when the
compiler has wide Chars) by converting most strings exchanged with
the world between the specified encoding (default: locale dependent)
and Haskell's Unicode, even though Unicode support modules are still
experimental and transparent conversion on Handle IO is temporarily
hacked on top of original Handle functions. In essence QForeign
provides the interface of ghc-5.00's FFI on ghc >= 4.08 and nhc98.

My friend Wojciech Moczydlowski <[EMAIL PROTECTED]> asked me what
is the currently recommended way of interfacing between Haskell and
C. I showed him how do I do it.

He said that Greencard and HDirect were easier: you didn't have to
write marshalling code around each function, but all arguments were
magically coverted basing on a single type declaration of the function.

I replied that my solution is more general, especially if the Haskell's
interface of a C module doesn't want to exactly mirror the original C
interface, and that it's impossible to match everything automatically,
and that it's not that painful to write function wrappers by hand.

He said that a tool could handle simple cases automatically, leaving
only hard types to the programmer.

I said that I don't know how express a C interface to archieve
this, and that C libraries are too complex to be wrapped in Haskell
automatically, and thus I can't provide anything more sophisticated
than hsc2hs.

So he created KDirect.

KDirect currently works on top of QForeign and hsc2hs. I assume that
in future it will be able to use FFI modules provided by ghc >= 5.00,
and that eventually all Haskell implementations will provide common
FFI modules.

-- 
 __("<  Marcin Kowalczy

Re: FFI progress

2001-03-28 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 28 Mar 2001 12:10:46 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> If most libraries could be ffi'd without the need for additional C files, the
>  multiple header file notation would be an obvious win.
> 
> As it is, many libraries I've dealt with need one or more .c files containing
>  some support code and, in that case, it's not too big a deal to add another file.

I think that since usually there is a C header associated with the
module, it's not a problem to put original C headers there. I prefer
minimal header information at each foreign declaration, so it would
refer only to the custom module.

hsc2hs fits into this model. The user can let it choose the right form
for compilers supporting or not supporting the discussed feature, e.g.
foreign import #{fun "Foo", "f"} unsafe f :: Type
or better
#module "Foo"
foreign import #{fun "f"} unsafe f :: Type

> >   foreign import ",:f" f :: 
> >   foreign import ",:f" g :: 
> Should I report an error?

No.

> >   foreign import ":f" f :: 
> >   foreign import ":g" g :: 
> >   foreign import ":h" h :: 
> 
> can I assume that foo.h will only be included once?
> can I assume that foo.h is included before bar.h?

No. Since headers from multiple declarations can be put into one
file, they may come in arbitrary order. You may get more headers
than requested, but not less. Particularly the compiler is allowed to
collect headers from all foreign declarations and attach them to the
module itself, and to arbitrarily combine headers from various modules
when C function calls are inlined across modules. The compiler is
not forced to detect duplicates, but I would expect it to do so at
least for declarations coming from a single module (so cpp doesn't
need to process the header a hundred times).

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: unsafePerformIO and unsafeInterleaveIO

2001-03-20 Thread Marcin &#x27;Qrczak' Kowalczyk

On Tue, 20 Mar 2001, Simon Marlow wrote:

> I'm not sure about including these functions in Foreign.  Their
> location should be standardised, sure: but that's something to be
> discussed as part of the new library proposal.  I don't feel they
> belong in Foreign.

So they can be provided somewhere else and exported by Foreign as well.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: unsafePerformIO and unsafeInterleaveIO

2001-03-19 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 19 Mar 2001 11:04:43 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> > Should these functions be available through the standard FFI?
> > IMHO they should.
> 
> I don't understand the question.
> Are you asking which modules should export them?

Yes. IMHO they should be made as "standard" as the rest of FFI
and exported from module Foreign.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



unsafePerformIO and unsafeInterleaveIO

2001-03-18 Thread Marcin &#x27;Qrczak' Kowalczyk

Should these functions be available through the standard FFI?
IMHO they should.

Their functionality on a variety of concrete types can be archieved
by using C, in an ugly and inefficient way. FFI already contains the
level of unsafety they are at.

They are useful, especially in the context of FFI. They are used all
over hslibs: Concurrent, SocketPrim, Posix, MatchPS, XmlParse, Memo,
Readline, Select, QuickCheckBatch, Unique. I used them in 5 out of 8
bindings to random C libraries (Bzip2, Curses, Libgr, Readline, Zlib).

They are available in all four Haskell implementations, only through
different modules.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: cvs commit: fptools/ghc/lib/std PrelStorable.lhs fptools/hslibs/lang Storable.lhs

2001-03-14 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 14 Mar 2001 10:37:04 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> >   Add 'destruct :: Ptr a -> IO ()' method to class Storable. Thanks
> >   Wojciech Moczydlowski <[EMAIL PROTECTED]> for the suggestion.
> 
> Is this supposed to be a GHC-only extension of the FFI libraries?
> If not, why didn't we discuss it - or did I miss something?

Sorry, I should have discussed it.

In the Storable instance of a C struct sometimes poke wants to allocate
additional memory. E.g. the struct contains char* which corresponds to
String in Haskell.

It must be freed somewhere. Usually poke is idempotent, but in this
case it's not. There is always a well-defined piece of code derived
from what poke does, corresponding to C++'s destructor.

There was no good place to put it. It should be called by withObject /
withArray functions (I'm going to finish it), and sometimes explicitly
before free. Storable is IMHO a very good place. This method has a
default definition, so you can forget about it when using Storable
for trivial types.

Any objections?

If not, I'm going to add also destructArray and destructArray0 to
MarshalArray, and lengthArray0 while I am at it (it was used internally
so it makes sense to be provided separately), and document it.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modified proposal for default decls

2001-02-27 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 26 Feb 2001 07:07:55 -0800, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze:

> Most notably, Malcolm's latest proposal introduces a new form
> of abstraction (named thing), a bundle of attributes like Gtk or Bzip.
> Another environment for the compiler to manage! Soon people will
> want to export these things and import them elsewhere!

Yes, we will! :-)
What's wrong with it?

Yet another name instead of 'foreign default':
foreign module
I am specifying some details about a foreign module I want to
interface to.

> *  The "gtk:" part is a concession to (b).  It specifies a C
>package from which this procedure comes. There is then some
>compiler-specific mechanism for mapping the name of a C package
>to the location of its header files and .o file.

This gives no advantage over the current scheme. I already can
specify header names in a compiler-specific way, and I still can't
do it compiler-independently, and the compiler still won't push it
automatically to modules which inline functions infected with C calls.

> Notice that cross-module exports of inlinings are now
> straightforward: the foreign call carries its package name with it.

How the package is defined?

> You may think this is too minimalist,

I would say: too incomplete.

> Do we really need the elaboration of Malcolm's proposal?

Yes, unless a simpler design provides what is needed.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modified proposal for default decls

2001-02-27 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 26 Feb 2001 11:17:07 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> I just remembered that my project (Knit - a C component language)
> has severe problems with use of macros in header files.

With hsc2hs it's easy enough to wrap macros:

foreign import "hs_incRef" unsafe incRef :: Object -> IO ()
#def inline void hs_incRef (PyObject *o) {Py_INCREF (o);}

If you are lucky, everything will be inlined across languages and
modules.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modified proposal for default decls

2001-02-24 Thread Marcin &#x27;Qrczak' Kowalczyk

Fri, 23 Feb 2001 18:38:20 +, [EMAIL PROTECTED] <[EMAIL PROTECTED]> 
pisze:

> foreign_decl ::= 'foreign' what [conid] [attributes] [foreign_name]
>varid '::' prim_type
>| 'foreign' 'library' conid attributes

I like the idea.

Putting attributes before foreign_name is incompatible with current unsafe.

> I also prefer to change
> 
> attribute::= varid | varid string_literal
> to
> attribute::= varid | varid=string_literal

Intuitively juxtaposition binds more strongly than '=', so
foreign import keyword = value keyword = value varid :: type
looks like divided into three parts separated by '=':
foreign import keyword
value keyword
value varid :: type

Some time ago I proposed to separate 'keyword = value' pairs by commas,
but it was incompatible with the placement of 'unsafe'.

> You can have as many library decls as you like - think of them
> simply as named collections of features.

In this case there can be no [conid] in the grammar, only user-defined
attributes. Consistency in unifying them with atomic attributes
requires the ability to include multiple user-defined attribute sets in
one foreign declaration, to define attribute sets in terms of others,
and to export them (explicitly).

This may be overly general. This may also be really convenient. When
a foreign library requires configure magic to determine headers and
libraries and other system-dependent attributes, it may be placed
in a single preprocessed module, and all other modules will just use
the named set of attributes defined in one place.

Syntax proposal:

foreign library Gtk = header  ""
  header  ""
  dll "libGTK.dll"
  stdcall
  unsafe

foreign import "gtk_text_widget" Gtk
textWidget :: String -> GtkWidget

The foreign_name can be seen as a value for the keyword 'import'.

Using conids instead of varids for library names ensures that old
code will not break when further attributes are defined. Usually
the module name is a good choice.

I don't propose to be able to bind parameters on the lhs of '=',
although the syntax would easily allow that.

If at some time we decide to have 'foreign type' declarations which
tell how to translate Haskell types to C types, they should be attached
to 'library' contexts instead of being put in a global pool, which
solves the problem of conflicting translations coming from different
modules and how they are exported:
data RangeTag
type Range = ForeignPtr RangeTag
foreign type "GtkRange *" Gtk Range
It does not mean to _use_ Gtk attributes here, but to _add_ this
definition to Gtk's type translation dictionary.

> By the way, this implies that certain single-word features must be
> invertible - 'unsafe' can be overridden by 'safe', 'nonblocking'
> can be overridden by 'blocking', or whatever.

Yes. And it should be more precisely said what does it mean to
"override", e.g. are both
Gtk safe
and
safe Gtk
legal, meaning to override whatever safety switch is in Gtk?

If the order does not matter but they are overridable, then there
are ambiguities when e.g. we include multiple library ids which
define conflicting safety switches. It becomes more complex than
really needed.

One way to solve this is to drop the idea that library ids have the
same rights as atomic attributes. At most one library per foreign
declarations, no libraries defined as extensions of others, and the
library name can be required to be written at the first position
because extra syntax freedom doesn't buy anything in this case.

Another way is to say that the order matters and later attributes
override earlier ones, no matter how they came from flattened library
specifications. This is very nice and consistent, except that stupid
declarations like 'unsafe safe' are legal.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: Summary of current change suggestions

2001-02-23 Thread Marcin &#x27;Qrczak' Kowalczyk

On Fri, 23 Feb 2001, Simon Marlow wrote:

> I agree.  Would it be fixed by just #including Stg.h after any
> -#includes, or would that create more problems?

If HsFFI.h indirectly includes system headers, then I'm afraid it's
not enough for hsc2hs, which automatically includes HsFFI.h before
user-specified #includes (because it cannot reliably determine where
#includes end and code which relies on HsFFI.h begins).

Can HsFFI.h be made self-contained?

Requiring to include HsFFI.h explicitly (after system includes) would
work, but I hope it can be avoided.

Generally I can't fit the whole picture of files included at all places in
my head at once.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Summary of current change suggestions

2001-02-23 Thread Marcin &#x27;Qrczak' Kowalczyk

On Fri, 23 Feb 2001, Fergus Henderson wrote:

> OK, now how about things where you need to #define symbols before
> including the header file?

Choose one:
1. Write a forwarding header which #defines and #includes.
2. Use compiler-specific switches to get #defines (-D and -optc-D in ghc).
3. Extend the proposed FFI to have define as well as include.

Unfortunately option 1 doesn't always work well on ghc, because Stg.h
(included into .hc files) indirectly includes headers like  
*before* user-specified -#include options, so symbols like _BSD_SOURCE
are defined too late to have any effects. This should be fixed.

hsc2hs provides a mix of option 1 and option 2. You write #define in .hsc
source before #include and it usually works, but sometimes it's too late.
I hope this mess can be somewhat sorted out; symbols go into several
files and it is messy.

> Or where the header file to include varies depending on the system?

When you have conditional compilation (either via hsc2hs or via cpp),
wrap the proposed 'foreign default include "..."' in appropriate #ifdefs.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: cpp

2001-02-22 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 22 Feb 2001 14:07:04 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> An output file or files which can be used as input to cc/ghc/Hugs/etc.
> (i.e., which doesn't require greencard, c2hs, hsc2hs, etc.) and which
> contains ifdefs to handle any portability issues.

Ah, now I see. hsc2hs could have an option to not delete the source
of the C program which outputs the Haskell source. In this case it
would be possible to make a distributable source package which doesn't
require hsc2hs to compile. I will add this option.

(Except that I pass some file through hsc2hs twice, because C macros
can't expand to preprocessor directives. For this case the scheme
would not help. But it's very rare.)

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: cpp

2001-02-22 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 22 Feb 2001 11:41:20 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> 2) Have any desire to spend half a day installing lots of
>Haskell-related tools (greencard, c2hs, happy, etc.) on their
>machine before they can try out my tool.  Getting them to install
>a GHC binary is about the limit of what I can reasonably expect.

hsc2hs is in ghc-4.11.

> In this case, it is very useful to be able to distribute the output
> of all those useful support tools (greencard, c2hs, happy, etc.).

The output can depend on versions of C libraries they have installed
and other details of their system which are detected at configure time.
You would lock the distributed package to a concrete binary-compatible
environment.

> What would (perhaps) be nice is for the support tools to implement
> conditional compilation themselves and for the output file to use
> conditional compilation too.

Sorry, I don't understand this.

For example hsc2hs transforms a .hsc file with #ifdefs and other things
into a .hs file and sometimes also .h and .c files. The .hs file has
conditional compilation resolved; the .h and .c files contain #ifdefs
which mirror the #ifdef structure of the source.

hsc2hs doesn't implement #ifdefs itself, but uses cpp to compile a
C program which outputs the Haskell source.

What would you like to obtain?

> ps Or maybe I should just hack up a perl script that runs greencard
> and friends 2^N times and then packs the results (using diff,
> etc as appropriate) into a convenient file for shipping to users.

Do you mean considering every possible combination of #ifdefed
expressions? Sorry, it won't work. One of my modules contains 98
#ifdefs in a row (generated by macros), which check availability of
errno constants. I will not distribute 316912650057057350374175801344
variants of this file.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Summary of current change suggestions

2001-02-22 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 22 Feb 2001 11:27:20 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> In fact, I expect that having dlopen do a search through the
> libraries that it thinks are relevant instead of Hugs performing a
> search through the list of libraries that it knows to be relevant
> probably makes things worse because it increases the gap between
> the programmer's mental model and what actually happens.

Unider Linux it needs not to be specified in which library a symbol
is defined. It's enough to say: #include these headers, link in
these libraries, and you will get the following functions. (And even
libraries need not to be specified by name, as in gtk+ example.) So we
can't *require* specifying the exact library for individual functions.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Summary of current change suggestions

2001-02-22 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 22 Feb 2001 12:08:22 -, Simon Marlow <[EMAIL PROTECTED]> pisze:

> Don't forget you might need multiple includes, eg.  &
>  for socket(), and ordering is important.

Easy with my proposal:

foreign import "socket" include "" include ""
socket_c :: CInt -> CInt -> CInt -> IO CInt

include options accumulate instead of being overridden.

I insist on being able to write:

foreign default include "" include ""

> Marcin: I guess hsc2hs should have some magic to insert the include
> specs automatically :)

Ugly magic. 'foreign default' is better.

#let my_includes name = "\"::%s\"", name

foreign import #my_includes "socket"
socket_c :: CInt -> CInt -> CInt -> IO CInt

How would I omit the foreign name (to be derived from the Haskell name)
but specify headers?

No, making it a part of a string is bad. Optional attributes should be
expressed with an open set of defaultable pseudo-keywords like current
'unsafe'.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: Summary of current change suggestions

2001-02-22 Thread Marcin &#x27;Qrczak' Kowalczyk

On Thu, 22 Feb 2001, Simon Peyton-Jones wrote:

> I must say that I like Manuel's proposal below.

Please don't force to put header names in *every* foreign declaration!

For header names which are detected at configure time, we would have to
write forwarding headers in separate files and install them with the
package. When a header name changes from constant to not constant, every
reference to it must change. Because nobody wants to have #ifdef around
every foreign declaration.

This scheme is not quite open for future defaults, because if every
attribute has its own ad hoc syntax in the string, the way in which
local definitions are overridden by defaults cannot be described
language-independently.

Here is a more backwards compatible variant of my proposal:

foreign_decl ::= 'foreign' what foreign_name attributes
 varid '::' prim_type
   | 'foreign' 'default' attributes
what ::= 'import' | 'export' | 'label'
foreign_name ::= empty | string_literal
attributes   ::= empty | attribute attributes
attribute::= varid | varid string_literal

Attribute names to be defined now:
'dynamic'
'ccall'
'stdall'
'unsafe'
'safe'
'include'
In future:
'java'
the blocking issues
Uncertain what to do with:
'noproto'

As a deprecated compatibility feature, calling conventions can also be
specified before the foreign_name, in which case a string following them
is not their argument but the foreign_name.

What I find ugly is that 'dynamic' does not really fit here. It changes
whether the name is created or exported (for foreign export), it does not
make sense as a default, it makes the presence of foreign_name illegal.

-- 
Marcin 'Qrczak' Kowalczyk




___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: Summary of current change suggestions

2001-02-22 Thread Marcin &#x27;Qrczak' Kowalczyk

On Thu, 22 Feb 2001, Simon Marlow wrote:

> The package spec format is designed to be used with "read" (i.e. it's
> Haskell syntax), so Hugs could just read it using its built-in parser.

The format should be extensible, i.e. adding future fields should not
break old code which does not use these fields. IMHO each field which
is a list should be allowed to be skipped, defaulting to the empty list.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Summary of current change suggestions

2001-02-22 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 21 Feb 2001 15:51:35 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> User defined defaults are really tempting to add (my component
> programming language had them briefly and I am under constant
> pressure to add them back in) but they are kinda messy because:

They are sometimes bessy, but it's not that bad in this case.

Think about the FFI defaults as special variable definitions which
are spelled differently, and proper FFI declarations that use whatever
special variables are in scope.

> 1) You have to resolve (or forbid) use of multiple defaults.

Forbid. You can't have two variables with the same name at the toplevel.

> 2) You need a way to override the default.
>Do you override the whole default (includes, libraries, etc.) at once or
>only the bits you don't specify.

Only the bits you don't specify. You can shadow a name locally
(as in SML's 'local' declarations which create a local environment
for some definitions).

> 3) A small change to code in one place can have unexpected results (and it is
>hard to detect the consequences using typechecking or from a failed link or
>whatever).

The same can be told about changing a function body. It influences
the meaning of all code which uses it.

> 4) Cutting and pasting some code from one context to another context results in
>very different behaviour because the defaults don't carry over.

The same can be told about the environment of defined names. You
can't cut and paste without considering the visible names anyway.

A difference between FFI defaults and Haskell 'default' is that it
is used in clearly visible places - foreign declarations - and not
at any point the type inference has a specific problem.

Specifying include files in each foreign declaration is not an option.
We must have a foreign declaration which tells something about the
context in which this module and modules importing this module must
be compiled.

Instead of 'foreign context' or 'foreign language' we may use
'foreign default' and think about it as specifying the defaults which
could be specified in foreign declarations if somebody really wanted
I.e. using 'foreign default' is not mandatory - you could write
everything at each foreign declaration if you wish.

I think that the set of attributes is open enough that we must design
some keyword/value scheme or such, insead of relying on extending the
grammar each time a new kind of attribute is needed.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modification to foreign import/export

2001-02-21 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 21 Feb 2001 11:41:07 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> The point of me mail was that instead of using half the features
> of cpp (Marcin gave an example which used #ifdef) and extending the
> ffi spec to do the other half, he could use all the features of cpp
> (#ifdef and #define) and avoid the ffi extension.

Applying cpp to a Haskell source is problematic, because it doesn't
have the same lexical syntax as C. Apostrophes in identifiers
and string gaps cause most trouble. And it does not solve all FFI
problems for which some preprocessing is needed, e.g. expanding numeric
constants defined in C headers (you can't include a C header full of
function prototypes into a Haskell source, although it could probably
be worked around by wrapping in comments).

My example using #ifdef was meant to use hsc2hs instead of cpp.
I don't use cpp for Haskell.

I understand that making official FFI depending on an extra tool
(which may be considered an ad-hoc solution) is problematic in itself,
so I don't propose making hsc2hs a part of the standard now. But I
found it practical for FFI - definitely more appropriate than cpp.

> If we want to rule cpp as out of bounds (a very worthwhile but
> difficult goal), then we need to think about how to avoid conditional
> compilation too.

Unfortunately it is sometimes needed. We can try to isolate it etc.,
but it will be needed because we don't live in a perfectly portable
world.

I am making a wrapper for the Python interpreter in Haskell programs,
or Haskell<->Python binding if you like. I already used the following
features of hsc2hs:

* #include 
* C functions written inline in Haskell source, for wrapping C macros.
  Warnoing: their prototypes should be #included into modules which
  import modules which define them, because ghc inlines calls to C
  functions across modules.
* Conditional compilation for broken Haskell compilers, e.g.
  non-working foreign label and broken newtype handling in foreign
  export.
* Definition of a C struct and accessing its fields and sizeof inline
  in Haskell source.
* Conditional compilation for non-standard ghc modules:
  Exception.justDynExceptions was renamed to Exception.dynExceptions
  in ghc-4.09.
* Conditional compilation for Python interpreter versions: some
  functions were added in Python 2.0, some were renamed (old names
  are available as macros, but they would need preprocessor support
  anyway).

I will also use conditional compilation for being able to use either
native ghc FFI modules or versions provided by QForeign. Using versions
from QForeign has two advantages for me here: works with ghc-4.08* and
allows to play with charset conversions and Unicode.


The last point leads to the following problem. I would like to be able
to override modules found in -package lang with my modules, i.e. use
modules with the same names, and have minimal control which are used
(relying on ordering of -package options suffices).

The problem is that these modules use features from original modules
that I want to shadow. It seems to work with nhc98, but ghc is confused
when several modules of the same name are indirectly imported to
the same module - in this case a module reexports a function from
a module with the same name. I also expect problems with internal
__init_Module functions.

Note that I don't directly import both modules at the same time.
I tried to have my modules under different names importing original
modules, and then in a separate directory compiling my modules with
shadowing names which just reexport previously defined modules with
different names. But it does not work if original functions are really
defined in modules of the same name (it seems to work when functions
come from yet other ghc private modules).

We could just say that using multiple modules of the same name is
evil and will never be supported. Nevertheless in my case it would
be very useful. My modules have the same functionality as original
modules and reexport their contents in most cases, but sometimes they
have a slightly different implementation. Currently my modules have
different names, so code using them must explicitly call for them.
It's not a matter of switching -package options, but either conditional
compilation or playing with directories containing reexporting
modules having non-standard names *in a package which uses my modules*
(requiring to play tricks would be OK for my modules which play tricks
with shadowing, but not everywhere they are used).

If ghc internally fully qualified functions with packages, not only
with modules, then it should work.

Do you too think that ghc should enable a package to reuse module names
from different packages, even if it indirectly uses these packages?

Perhaps it should be integrated with proposed Malcolm's scheme of
structured module hierarchy. It's not obvious how ghc's packages fit
into this idea.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
 

Re: Summary of current change suggestions

2001-02-20 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 21 Feb 2001 16:01:48 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> So, how about the following.

I must admit that I like my own proposal better :-)

> So, as Marcin pointed out, the only use for a library object
> spec for ccall is so that interpreters know which handle to
> pass to dlsym().  I am not too fond of the idea that the
> interpreter has to try a dlsym() on all library objects that
> it did dlopen().  Or is this maybe not too bad?

As I see in ghc/rts/Linker.c, in the ELF case dlopen (NULL, RTLD_LAZY)
and dlopen (filename, RTLD_NOW | RTLD_GLOBAL) can be used to let the
linker find the library for each symbol. I don't know about Windows DLLs.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Summary of current change suggestions

2001-02-20 Thread Marcin &#x27;Qrczak' Kowalczyk

Tue, 20 Feb 2001 18:54:05 +, [EMAIL PROTECTED] <[EMAIL PROTECTED]> 
pisze:

> Since I believe backward compatibility is very important, would
> anyone like to either modify Marcin's proposal, or make a new
> concrete proposal that is perhaps slightly more conservative but
> still achieves our goals?

One point: the syntax should be such that adding future languages,
calling conventions, attributes etc. does not break old code which
uses these names as e.g. foreign function names.

Since sets of languages, attributes etc. are open, it's advantageous
when foreign declarations can be parsed without knowledge about
these sets. It's for better error messages ("I don't support calling
convention foo" vs. "parse error"), for the ability to ignore unknown
attributes (should all attributes be ignorable, with a warning? or
should they be explicitly marked as ignorable or not? I think we
may specify that all are ignorable, for simplicity), and for parsing
preprocessors which output foreign declarations unmodified.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Typing f.e.d.

2001-02-12 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 12 Feb 2001 15:49:45 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> 1) Trying to support a complex language like Java in the same design
> (or in any design, really)

Java support has no impact on C support: you can ignore it if you like.
The design as is is quite language-independent (and proposed to be yet
more independent, by moving some C-specific bits to a better place).

> 2) Moving library specs, etc. out of the individual ffi decls.

Why would you want to require to repeat the same words with every
declaration?!

> >* Pointers to code and data need not have the same size.
> 
> I understand this argument though I'm not sure which architectures
> this applies to.

AFAIK IA64. And MS-DOS.

> How often do you have to create two Haskell types which really
> ought to be just one type just so that you can use the overloading?

I can't remember I've ever done this.

> Is pointer arithmetic on Ptr's useful?  (It's obviously useful for
> arrays but can you use it (safely and portably) to access fields
> of structs or do you have to add an explicit byte count to get
> predictable/safe results.)

For structs the type of the pointer to the struct plays no role.
You can use hsc2hs and write
uid <- (#peek struct stat, st_uid) ptr
Otherwise you have to use a C wrappper.

> What's the preferred way to represent an opaque C data type which
> happens to be a pointer?

I prefer this:
data FooTag = FooTag
-- IMHO should be: data FooTag, but this is not supported.

type Foo = Ptr FooTag
-- Sometimes ForeignPtr, sometimes both.

When the pointer points to known data with unknown representation
(data which can be extrated and used to recreate such object),
instead of FooTag you can represent the data as a Haskell type and
write appropriate Storable instances. It has not happened to me but
I guess that some glib types (gstring?) could be treated that way.

Sometimes I use just Ptr (), when it's used once or twice locally.

> What libraries is the evolving design being tried out on (I know
> about your OpenGL library).

In QForeign  you can
see it applied to bzip2, curses, db3 (incomplete), glob (function),
libgr, pcap, readline, zlib, and a bunch of functions mostly from libc
(tests/Varia.hsc).

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modification to foreign import/export

2001-02-12 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 12 Feb 2001 11:39:12 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> > The ability to specify #include files in a portable way,
> 
> Can this not be done with one small extension instead of a much
> larger general purpose extension?

I prefer a not too large but generic feature - to one small extension
here, one small extension there, and debates how to express yet
another small detail again.

> The ffi spec already has a way to specify this: list it with each
> ffi decl. There's no need to invent anything new.

This is a C-specific feature added to the general FFI spec. My proposal
makes the FFI simpler by expressing all optional tuning parameters
(like unsafe and the calling convention, and e.g. the compiler if
a foreign language has binary-incompatible implementations that we
want to support) in a single unified syntactic framework.

> I'm looking for a compelling argument that the convenience of adding
> all these extra declarations outweighs the costs of a more complex
> design, introducing more keywords into the language, etc.

It does not introduce more keywords!

> Can't you just add the required functionality (global library
> declarations, global calling convention declarations, order-dependent
> overriding, etc.) to hsc2hs?

It's much simpler and more reliable to implement it in the compilers.

> Why not write a preprocessor that turns ffi/Java into ffi/C?

It's much simpler and more reliable to implement it in the compilers.

> Chances are that one of the existing calling conventions (i.e.,
> stack and register layouts) and the existing set of types is going
> to be a pretty good fit.

Correct programs must not rely on chances.

> If you find yourself using a Haskell implementation that runs
> on a JVM and want to optimize it (e.g., support some Java types
> more directly), you can tweak ffi/Java to generate native Java or
> marshall some types more intelligently or whatever.

Sorry, I don't understand.

>   Keep the ffi standard simple so that:
> 
>   1) An already hairy piece of code doesn't become unmaintainable.

Which piece of code do you have in mind? Existing libraries using
the FFI? My proposal is perfectly backwards-compatible.

>   2) Incompatabilities between different implementations can be kept to
>  a minimum.

My proposal reduces existing incompatibilities in a concrete way
(nhc98's noproto can be written such that it does not break ghc) and
keeps future incompatibilities to a minimum (header files needed by
ghc will not break nhc98 which does not use them).

>   And the way to achieve this is to put any proposed complexity in
>   tools rather than in the ffi.

Not everything can or should be put in tools.

> > Of course they are not keywords in any context except foreign
> > language declaration. That's why I wrote "pseudokeywords".
> 
> I hope you don't mean anything like Haskell 98's "as", "qualified"
> and "hiding" special identifiers?

It's like existing export, label, ccall, stdcall, unsafe, dynamic.
If you accept them, you must also accept this aspect of my proposal.

> Surely there's a better way?

Where?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modification to foreign import/export

2001-02-12 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 12 Feb 2001 17:27:36 +, [EMAIL PROTECTED] <[EMAIL PROTECTED]> 
pisze:

> > We can have some declaration specifying the context of *following*
> > foreign declarations. Another such declaration can change the
> > context later in the module.
> 
> Please no!

OK, my current favourite is to specify them globally but allow to
override locally.

> > foreign language "c",
> 
> I think the quotes around the language name are redundant - why not
> just
>   foreign language C
> ?

To keep the syntax consistent: a list of
keyword "string"
pairs separated by commas, including the language invocation (even
though it's special: it distinguishes the whole construct from other
foreign declarations and determines the language name).

And to allow the spelling of "c++" :-)

> > foreign language "c",
> > include "",
> > library "ncurses"
> 
> I quite like the idea of keyword/string pairs.  I'm not sure how you
> would propose to use the layout rule here.

No layout is used here. Everything is one logical declaration, which
can be split into indented lines as usual. Just as for other foreign
declarations.

> To make them slightly easier to parse, why not make them like
> named-field bindings perhaps?

My record proposal goes in the opposite direction by removing this
use of braces from the record syntax :-)  Anyway, I don't see the
reason for introducing extra punctuation. My original syntax is
trivial to parse:

 ::= foreign language  
   ::= 
 | ,   
  ::= 
 |  

Other foreign declarations can use the same  syntax at
the end:

-- A file with a bunch of Java functions and one C function:
foreign import func :: Ptr CChar -> IO CInt, language "c", library "foo"

-- Another file where the language is C and files are in the library "foo":
foreign import func2 :: IO (), library "foo1"

IMHO attributes like unsafe should be specified that way. They could
even give a warning instead of an error if they are not recognized,
so nhc98's noproto or future additions like blocking behavior discussed
on the workshop can be added without breaking the compatibility.
I had to play hsc2hs tricks to have noproto for nhc98 but not for ghc.
A programmer could make unsafe his default in a module and write safe
explicitly when needed.

> I suppose in the case where the C header was local, the string
> would need to use the Haskell double-quoting mechanism?

Yes, lexically it's a string literal. But we can adopt ghc's -#include
command line option's convention that the absence of quotes means
double quotes.

> For booleans, use booleans
> 
> flag=True
> 
> and for multiple strings, use tuples?
> 
> searchpaths=("dir1","dir2")

This unnecessarily complicates the syntax. With my version the abstract
syntax contains just
[(Keyword, [Value])]
where type Keyword = String; type Value = String
and interpretation of the strings is up to the language + keyword
combination. It is parsed complately before recognizing individual
keywords.

Here we would need to decide if True is the same as "True", there
might be the temptation to include integer literals later etc.

Since these keywords are used nowhere else and no identifiers are
expected here, they can be freely chosen. Each value of a multiway
switch of a fixed set of values can have its own keyword without
arguments (e.g. for calling conventions). Arbitrary weirdness invented
by other languages' implementers can be accommodated here without
influencing the rest of our beloved language :-)

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modification to foreign import/export

2001-02-12 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 12 Feb 2001 09:50:07 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> Note that this can be done without separating the library name from
> the ffi decl:
> 
> #ifdef UNIX
> # define LIBNAME "foo.so"
> #else
> # define LIBNAME "foo.dll"
> #endif
> 
> foreign import ... LIBNAME ...
> foreign import ... LIBNAME ...
> foreign import ... LIBNAME ...

Only if you use cpp. With hsc2hs you have #ifdef but #define like
this is harder (although possible).

> Just to be clear that I understand this argument, you're saying that:
> 
>   It is ok to severely break order independence in the ffi because it is
>   already mildly broken in normal module import?

Yes.

> This is just another source of confusion for the baffled programmer.
> (And more clutter for a language that already needs to go on a diet.)

An alternative is either a global set of options for each Haskell
module or repeating things with each foreign declaration. Both are
not quite satisfactory: the former imposes an arbitrary restriction,
the latter is inconvenient.

We could also allow to override things specified globally in individual
definitions. This should combine the best of both solutions. In this
case we just must design a nice, consistent and extensible syntax.

> > Here is a concrete proposal:
> > [proposal deleted]
> 
> Looks like a massive extension to the ffi definition.
> What does all this complexity buy us?

The ability to specify #include files in a portable way, instead of
relying on compiler-specific methods (-#include commandline option
for ghc, not needed for nhc98).

If a Haskell implementation needs to know from which library to take
which function, e.g. an interpreter using dlopen/dlsym, then again
this must be specified somehow. We could invent a way to encode it in
the foreign function name, but it has disadvantages: the name might
not be constant (e.g. ncurses or curses determined at configure time)
and it would have to be repeated for each function.

When I import many stdcall functions, I must currently write stdcall
with each declaration. Similarly when I link to another language
(this is not a problem now when the only language is C, but it will
be a problem when more languages are supported).

> Wouldn't it be better to fix on a C/Pascal-like interface on the
> Haskell side and implement a series of similar ffi's for Java, C++,
> etc. which also target a C/Pascal-like interface?  Now if I want
> to call Java code, I use ffi/Java to construct C-like exports for
> the Java library and I use ffi/Haskell to generate C-like imports
> for the Haskell library.

Why I should be require to wrap everything in C if the compiler can
be designed to do that for me?

Imagine a Haskell implementation compiled to JVM. It would be stupid
to let Java talk with Jaba through C, but otherwise it would be
unportable.

> On the plus side, this style of narrow-waisted architecture is much,
> much easier to maintain, concentrates debugging/development effort
> on just one interface, provides utility to people on both sides of
> the interface (because a C++ programmer could use the exports from
> the Java library too), is simpler, is more flexible, ...

Surely maintaining just a C compiler is easier than maintaining both
C and Haskell compilers. So what, abandon Haskell because using C
for everything is simpler for compiler writers?

> ps Could I propose that any proposed new keywords be prefixed by __
> or ffi_ or something like that.  Adding keywords like "library"
> (i.e., ordinary useful words that programmers might already be
> using as variable names) breaks a lot of code.

Of course they are not keywords in any context except foreign language
declaration. That's why I wrote "pseudokeywords".

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Modification to foreign import/export

2001-02-10 Thread Marcin &#x27;Qrczak' Kowalczyk

Nobody answered, so perhaps everybody agrees :-)

Sat, 03 Feb 2001 00:14:56 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> Re (2): In Java, we obviously want to use qualified names
>   (like "java.lang.foo"), but in the case of dynamic
>   libraries and C calls it is less clear what the syntax
>   should look like.  "gtk: gtk_new_window" to specify that
>   the dynamic library "gtk" (on Unix that would happen by
>   loading "libgtk.so") has to be loaded to call the function
>   "gtk_new_window"?

On Linux it is not specified which functions are taken from which
library - everything is linked into a flat global namespace. Similarly
for #included files (but this is during compilation, not linking,
and thus can be different for each module).

Is it true for Windows and other platforms too? Or do some platforms
require to tell from which libraries individual functions are taken?

If not, we could use this fact and specify the C library in a separate
foreign declaration rather than together with each function.

This has the advantage that when the library name is #ifdefed, the
conditional needs not to be repeated for each function. Similarly
for #included header names.

A disadvantage is that linking using dlopen/dlsym or equivalent
(in interpreted environments) is problematic, because then you must
know the library of each function. It still can be done; we assume
that a single module will not import two identically named functions
from different libraries, so if more than one library is specified,
an interpreter can try each of them for each function.

For C++ the external name would contain the namespace, but not the
library nor header.

> Is it reasonable to require that only foreign declarations of
> a *single* foreign language are allowed per Haskell module?

We can give up the irrelevance of the order of declarations (which does
not apply for regular imports anyway - they must be at the top of the
module, before all local definitions). We can have some declaration
specifying the context of *following* foreign declarations. Another
such declaration can change the context later in the module.

In this case we have both the generality and convenience. The language,
calling convention, header files, and libraries would be moved there.
My discussion above is pointless: we specify the library name once,
but logically it applies to each individual function.

Here is a concrete proposal:

foreign language "c",
#if HAVE_NCURSES_CURSES_H
include "",
#elif HAVE_CURSES_H
include "",
#else
#error Where is curses.h?
#endif
library "ncurses"

The set of meaningful pseudokeywords ('include' and 'library' above)
depends on the 'language' which is mandatory and must be specified
first. Multiple headers/libraries/etc. can be specified as separate
include/library/etc. clauses.

I hope all interesting parameters in the future will fit in the syntax
of keyword/string pairs, with the string being optional (some keywords
are just boolean switches), or perhaps with multiple strings separated
by spaces (multiple headers/libraries could be specified that way).

The calling convention is specified thus:
foreign language "c", include "", stdcall
and removed from individual functions.

All information normally found in the C header must be duplicated by
other means, because the header is used only optionally to check
the call with the prototype, and physical linking with the function
can be done without cooperation with the C compiler.

Header and library paths are specified by compiler's commandline
options as usual.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: MarshalError

2001-02-07 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 07 Feb 2001 14:33:01 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> Hmmm, signature-wise, it doesn't seem that easy (without
> introducing too much clutter).

OK, I forgot that throwIf takes the monadic computation as an argument
and nothingIf takes the value.

I still think that nothingIf would be too rarely used. Including every
possible convenience wrapper makes the library too big, harder to
maintain, harder to find functions in it, harder to understand code
which uses so many different functions etc. This one is definitely
not that necessary.

It would fit better into the Maybe module, as a reverse of the maybe
function. (And btw, void should go to module Monad.)  I know that it
can't happen now because these modules are Haskell98...

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: MarshalError

2001-02-05 Thread Marcin &#x27;Qrczak' Kowalczyk

On Mon, 5 Feb 2001, Simon Marlow wrote:

> I don't see that.  Presumably you mean overloading failIf with the Monad
> class, but `fail' takes a String and in the IO monad we want to raise a
> real IOError, not just a UserError.

MarshalError is a "portable" and language-independent error wrapping which
throws userErrors. This can easily be generalized to an arbitrary Monad.

CError translates errno to IOError. IOError's representation is private to
the Haskell's implementation. Translation of errors other than errno to
IOErrors would usually not make much sense anyway, and similarly
translation of errno to something other than throwing IOError.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: MarshalError

2001-02-04 Thread Marcin &#x27;Qrczak' Kowalczyk

Sun, 04 Feb 2001 17:15:16 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> I am just wondering whether we would want to add the
> following to `MarshalError':

Maybe throwIf should be changed to failIf? The same function would
work for both IO and Maybe.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: Let's get this finished

2001-01-15 Thread Marcin &#x27;Qrczak' Kowalczyk

On Mon, 15 Jan 2001, Simon Marlow wrote:

>   data UnsafeCString
>   withUnsafeCString :: String -> (UnsafeCString -> IO a) -> IO a
> 
> where an UnsafeCString is valid only in an argument position of an
> unsafe foreign import.

Much of the conversion stuff would have to be done in a different way.
An additional internal interface to conversions implemented in C
(with ByteArrays instead of Ptrs), pointer arithmetic moved from
Haskell to C, and in future hard to mix with Handle I/O done on
Ptrs.

All because there is no safe way to safely get a Ptr to a ByteArray to be
used in Haskell.

> I still can't think of a good way to do this in general.  Perhaps
> enhancing the garbage collector so that it could "pin" objects - but
> you've still got the problem of keeping the lifetime of the ByteArray
> in sync with the Ptr.

Lifetime is not a problem:
withByteArray :: ByteArray -> (Ptr a -> IO b) -> IO b

(And now we know that the ByteArray type should be parametrized!)

This begins looking similarly to ForeignPtr from the outside.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



qforeign-0.64 is out

2001-01-15 Thread Marcin &#x27;Qrczak' Kowalczyk

http://download.sourceforge.net/qforeign/qforeign-0.64.tar.gz

* Adapted to FFI modules introduced in recent ghc-4-11.
* For nhc98 its recent version from CVS is required, but it finally works.
* hsc2hs processes # characters only outside comments and string literals,
  processing a file twice works (.hscc -> .hsc -> .hs), removed #option
  construct, added #enum construct, added -I, --include, and --version
  parameters, appropriate LINE pragmas are generated.
* hsc2hs documentation is back.
* Use one Makefile for all subdirs. (I've read
  <http://www.pcug.org.au/~millerp/rmch/recu-make-cons-harm.html>).
* Check compiler abilities by compiling or running test programs
  instead of relying on its version.

hsc2hs in ghc-4.11 is up to date.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-09 Thread Marcin &#x27;Qrczak' Kowalczyk

Tue, 09 Jan 2001 13:59:10 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> I was thinking of having the library itself by default
> provide a set of standard encodings.  Like - as you say
> later - we usually rely on a set of standard MIME encodings
> to be available.

If an encoding is added to the database at some point of time,
a program uses it and is then recompiled on a system which does
not provide this encoding, you get a runtime error.

If conversions are referred to as plain imported values, you get
a compile error.

A database is only useful if encodings are now known individually
by the programmer and he wants his program to support everything
the Haskell's library provides for some well known name scheme. It
can be a convenience wrapper, but definitely not the basic reference
for conversions.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-09 Thread Marcin &#x27;Qrczak' Kowalczyk

On Wed, 10 Jan 2001, Manuel M. T. Chakravarty wrote:

> which, I think, is what you want, should suffice for the
> moment.

I am happy with that.

> There is, however, one constraint that I would like
> to impose on the design of the conversion library.  It must
> be possible to spot and optimise the application of cheap
> conversions like to/fromLatin1.

It is possible now, even witohut RULES (which would not catch cases which
are not recognizable statically). Conv is an abstract type.

Currently it has alternatives for a conversion implemented in Haskell
(working on lists), a conversion implemented in C (working on pointers to
C arrays and with a different chunking strategy), and a conversion
implemented in both styles, to be chosen by code using it (perhaps it's
unnecessary, I have to measure).

For example direct application of a conversion to a user-supplied String
uses the Haskell variant if available, otherwise does appropriate array
marshalling for the C variant. OTOH newCStringConv uses the C variant
directly on the returned buffer if available, otherwise runs the Haskell
variant and uses newArray0.

It would be no problem to add variants for Latin1 and let withCStringConv
not call newCStringConv in this case but treat it specially.

(Currently alloca is implemented in terms of malloc so it does not matter
anyway.)

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-08 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 8 Jan 2001 17:11:04 +0100 (CET), Marcin 'Qrczak' Kowalczyk 
<[EMAIL PROTECTED]> pisze:

> A central database can be built around conversions available as values in
> the program. But it would be a bad idea to take it as the basic
> identification and require registering to use a conversion.

An important reason is that one can never be sure that a particular
encoding has been registered. Unless it takes care to import its
module ald call the registration function, but in this case he could
as well take the conversion itself without the extra indirection.

I imagine that common charsets would be imported from modules, like

import ConvIso
...
hSetOutConv stdout Text toIso8859_2

and there could be specialized databases of e.g. MIME encodings.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-08 Thread Marcin &#x27;Qrczak' Kowalczyk
ch I believe is as efficient
as possible (roughly).

OTOH QForeign's experimental converting IO replacement, IOConv, is not
efficient at all for conversions implemented in C.

> > We already have mallocArray0 and pokeArray0. You only have to cast
> > characters to [CChar].
> 
> Sure - but why not have this as predefined functions in
> CString?  That's all I am proposing.

I would not encourage people to skip the conversion and produce code which
works only for ISO-8859-1. Latin1 is just one of many encodings.

Since string handling in Haskell is already inefficient, I hope that 
adding conversions would not make a big relative difference. It would
be a different story if strings could be passed to C functions without
marshalling.

> BTW, do you know Pango <http://www.pango.org/>? 

Not yet.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-08 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 08 Jan 2001 14:55:31 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> How about having an interface where the String marshalling
> functions take an additional argument
> 
>   data CConv = NoCConv  -- handle as 8bit chars
>| StdCConc   -- standard conversion
>| CustomCConv String -- special conversions

There are already string marshalling variants which take the conversion
as the argument. The first is equivalent to toLatin1 / fromLatin1,
the second is localOut / localIn or using functions with no explicit
conversion (names are of source subject to discussion), the third would
either require building a database of name -> conversion mappings or
just pass names to iconv, assuming iconv knows that conversion.

They make no sense when there is never any conversion, so I haven't
talked about them yet when discussing MarshalCString or equivalents.

If you know that data is always ASCII, you can use toLatin1 as the
conversion.

> Then, it is up to the programmer to decide whether to use
> conversion.

There is always a conversion. Char and CChar are not the same type.
But it can be as trivial as toLatin1.

> The idea of the last variant would be that in your conversion
> library, I can give conversions a name and identify them by
> that name.  This way the CString wouldn't depend on the exact
> conversion interface,

Textual names are not enough. Conversions can be constructed on the
fly, e.g. by improving an existing conversion by substituting some
strings for characters which can't be handled by it.

Currently the type of the additional withCStringConv's argument is
IO (Conv Char Byte). It's IO because this is how "not started yet
conversions" are expressed. Conv Char Byte itself is an anstract type
of a stateful conversion which is taking place.

> Routines like mallocCString and pokeCString would only make sense
> for `NoCConv', then.

We already have mallocArray0 and pokeArray0. You only have to cast
characters to [CChar].

> Another example is configuration management in libraries
> like the Gnome library.  A program can dump its session data
> into an ASCII file using these libraries, so that it doesn't
> have to mantain its own preferences and resource files.  Do
> we really want all this stuff to go through the converter?

In what encoding are natural language texts in this dump?
If it's ASCII, use fromLatin1.

I have yet to benchmark conversions.

> Furthermore, to be honest, I am not really sure why we have
> to do the conversion anyway.  When I am having a Haskell
> program like [1]
> 
>   main = putStrLn "$B:#F|$O(B"
> 
> then, there are two possibilities.  Either I have a system
> configured with the locale jp_JP and I happen to run this
> Haskell program in kterm or an Mule/(X)Emacs subshell, or I
> will get mojibake[2] anyway.

You can have another terminal capable of displaying Japanese, e.g.
UTF-8-patched xterm (I don't know how well it works in practice
for Japanese, but they are using it for harder scripts like Arabic
so I guess it's just OK). The the same compiled program will then
display correctly (as long as the locale is set appropriately for
the terminal).

You can have Japanese texts in the source in any encoding, as long as
the Haskell compiler is able to understand various source encodings,
and the right encoding was specified in some way.

UTF-8-patched xterm has an advantage over Mojibake that it displays
not only Japanese, but about any charset which is possible to display
in a fixed-with font (including double-width characters).

> [2] Mojibake is the Japanese term for Japanese text
> displayed through software that cannot handle it.
> Mojibake is written as "^[$BJ8;z2=$1^[(B" in Japanese and if
> your mail reader can't handle Japanese, you'll see just
> that ;-)

Unfortunately I don't see that. But if I used a (nonexistant yet)
newsreader and editor written in Haskell which made nontrivial use
of the conversion machinery, I would probably see that :-)

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-07 Thread Marcin &#x27;Qrczak' Kowalczyk

Sun, 07 Jan 2001 12:16:15 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> I think, we need the alloca and realloc versions, too.

We can't have malloc, alloca, realloc or poke. Only peek, with and new.

We can't have poke because in general the space needed for the
converted string is not known. Well, we could have poke with a
parameter saying how long the buffer is, so the function never writes
more. Is that functionality needed? Then OK for it.

mallocCString and allocaCString would be exactly the same functions as
mallocArray0 and allocaArray0, only with a more specific type. There
is a little point in providing the same function under multiple names,
unless it really makes things consistent, or unless they can diverge in
future. But nobody has proposed freeArray, freeArray0 and freeCString
(equivalent to free).

Wait, in the Sven's message I see that mallocCString with String as
the parameter. Then how it is different from newCString?

For handling parts of C strings manually, reallocation of CString
buffers and converting them to Haskell's lists in terms of C characters
there are always *Array0 functions. *CString functions work on whole
strings, and do some conversion to translate between CChar and Char.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-07 Thread Marcin &#x27;Qrczak' Kowalczyk

Sun, 07 Jan 2001 13:15:21 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> > When someone really wants to use mallocCString and pokeCString now
> > (knowing that there is a little point of doing that in the case of
> > conversions), he can use mallocArray0 and pokeArray0, after casting
> > characters of the string to [CChar].
> 
> To be honest, I don't like this.  It is nice having the interface
> such that we can switch to using conversions at some point, but
> I still want to be able to conveniently deal with 8bit characters
> (because this is what many C libraries use).  So, I want a fast and
> convenient interface to 8bit strings *in addition* to the interface
> that can deal with conversions.  In particular this means that
> I don't want to deal with CChar in the Haskell interface only to
> circumvent conversion.

I understand everything except the last sentence. Why it is bad to
deal with CChar in Haskell?

It could be confusing if some String values represented texts in
Unicode and others - in the C's encoding. (Especially if the programmer
uses ISO-8859-1 for C encoding and does not care about the difference,
and then somebody using ISO-8859-7 tries to run his code!)

IMHO most strings on which C functions work (those ending with
'\0') are either in the default local encoding (if they are texts
in a natural language or filenames) or more rarely ASCII (if they
are e.g. names of mail headers, identifiers in a C program, or
commandline switches of some program). Sometimes the encoding is
specified explicitly by the protocol or is stored in data itself.

For ASCII the default local encoding can be used too, with a speed
penalty; practically used encodings are ASCII-compatible. You can
explicitly specify fromLatin1 or toLatin1 if you really want C
characters to map to Haskell's '\0'..'\255' - it should be faster
(does not call iconv or the like). You can also use CChar.

So most of the time strings should be converted to native Haskell's
encoding of Unicode, to be compatible with other parts of libraries
which expect the text to be in Unicode, and to let "words" and
"toUpper" and "length" work correctly (if by "length" you understand
the number of characters, not bytes in the physical encoding). It's
hard to do conversions in one place and not do it in others if you
mix data between those places.

What cases do you have in mind when strings should be passed to C
libraries unconverted?

> How about `advancePtr'?  But I am wondering whether this
> shouldn't go into MarshalArray?  It is used for array
> access, isn't it?

It's indeed only for arrays (where plusPtr is for structs, where the
offset is in bytes).

> `mapCont' makes a lot of sense.  I am less sure about
> `sequenceCont'.

mapCont is indeed more common (I used it only on withCString yet).
Uses of sequenceCont:

sequenceCont (replicate n $ allocaArray m) $ \rows -> ...

sequenceCont [
if s == "" then ($ nullPtr) else withCString s
| s <- listOfStrings] $
\stringPtrs -> ...

> How about calling `mapCont` simply `withMany'.

I like it. sequenceCont could be allocaMany.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-07 Thread Marcin &#x27;Qrczak' Kowalczyk

Sun, 07 Jan 2001 16:16:00 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> BTW, shall we really seperate CString and CStringLen into
> two different modules?  I am all for modularisation, but in
> this case I am not sure whether it is worth it.

I would put them in one module, especially if mallocCString and
pokeCString are dropped.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Sat, 06 Jan 2001 00:24:14 +0100, Sven Panne <[EMAIL PROTECTED]> 
pisze:

> For performance there's always #ifdef (well, at least if we
> consider piping Haskell sources through cpp as "standard"/H98).

hsc2hs used instead of cpp provides #ifdef too, and avoids lexical
analysis of Haskell source as C source.

> ! The current MarshalUtils uses
> !peekArray :: Storable a => Ptr a -> Int -> IO [a]
> ! but the signature below looks more consistent with peekArray0:
> peekArray:: Storable a => Int -> Ptr a -> IO [a]
> peekArray0   :: (Storable a, Eq a) => a   -> Ptr a -> IO [a]

OK.

>! Charset conversions are a diff{erent,icult} story and should
>! be handled by a separate module, so only the well-known
>! ignore-the-upper-half variants are given here.

I think the conversion story should proceed thus:

- For now the implementation will not do any conversion.

- At some point of time all IO and C string handling will switch
  to do the conversion, keeping the same interface for the case of
  the default encoding, and providing additional means for using
  different encodings.

It is important do introduce the conversion in all places at once,
otherwise reading a filename containing non-ASCII characters from
a file and using it to open another file will fail.

Unfortunately it means that parts of the FFI functionality will have
to go to ghc's lib/std, to properly handle strings and I/O in standard
libraries. The more of convenience functions will be kept in hslibs,
the less fun will be to fix standard libraries.

The interface of string handling functions must allow that move
in future without incompatible changes. We can't have separate
mallocCString and pokeCString after the conversion switch, because
the size depends on the contents, because a conversion can change
the length. So we should not provide them now either.

When someone really wants to use mallocCString and pokeCString now
(knowing that there is a little point of doing that in the case of
conversions), he can use mallocArray0 and pokeArray0, after casting
characters of the string to [CChar].

>! Haven't thought very deeply about this, but Marcin's QErrors
>! probably looks OK after a little polishing (use strerror,
>! provide a more complete throwXXX family, ...). And remember:
>! errno *is* a thread-local thing.  :-)

A little warning: strerror will want to translate strings, and
even do the conversion (the result of strerror is in the default
byte encoding). I had a module dependency loop when I wanted to use
strerror and at the same time handle errno in iconv's wrapper.

> -- MarshalUtils --
> 
> fromBool   :: Num a => Bool -> a
> fromBool = fromIntegral . fromEnum

I think that
fromBool :: Num a => Bool -> a
fromBool False = 0
fromBool True  = 1
is more clear (and easier to compile efficiently) :-)

> !   mbInt<- maybeNull peekptr1
> !   mbString <- maybeNull peekCString ptr2
> !   .
> !   maybeNothing withObject Nothing$ \ptr -> ...
> !   maybeNothing withCString (Just "foo!") $ \ptr -> ...
> !
> ! Does anybody have better names for these two functions?
> ! They sound OK for me, but I'm not a native speaker...

maybeNothing looks very cryptic for me, but I don't have a better
proposal...

> ! Do we really need this?
> indexPtr :: Storable a => Ptr a -> Int -> Ptr a

I used it once in Libgr, 3 times in QString and 5 times in
conversions. I would definitely keep it. Perhaps the name movePtr
would be better.

Let me repeat a proposal of two functions for MarshalUtils
(better names are welcome):

sequenceCont :: [(a -> res) -> res] -> ([a] -> res) -> res
sequenceCont [] cont = cont []
sequenceCont (f:fs) cont = f (\x -> sequenceCont fs (\xs -> cont (x:xs)))

mapCont :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
mapCont f = sequenceCont . map f

Example:
mapCont withCString a_list_of_Haskell_strings $
\a_list_of_C_string_pointers ->

Without them one has to write an explicit recursive function each
time for passing an array of things-to-be-allocated-on-the-stack to
a C function.

I would like to write
instance Monad (/\a. (a -> res) -> res)
instead of them. Unfortunately it's not possible.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Sat, 06 Jan 2001 22:37:35 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> If there were a faster alloca, it would still speed up the
> common case where there is no conversion or the initial size
> estimate is correct.

I'm afraid the common case includes a conversion.

It would indeed speed up the case when the size estimate is correct,
and slow down the case where it is not correct (wasting some memory).
Most of the time the estimate will be correct, but it will have to
be measured if the speedup is worth the compilcation (when we have
a faster alloca at all)...

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Sat, 06 Jan 2001 21:58:26 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> > type CString= Ptr CChar
> > type CStringLen = (CString, Int)
> 
> Hmmm, yes, although pointer/length pairs are not very common
> in C and this module is a language dependent module (and so
> should be called `MarshalCString').

I added the explicit-length variants when I needed them for the Python
interface, after I realized that it's not possible to express them
with variants which always stoped on input '\0' and didn't mark the
output length besides writing a '\0'. The '\0' variants are now small
wrappers around the explicit-length variants.

> But SimonM said that he doesn't want to make errno Haskell thread
> local...

It would force wrapping every C function which may set errno in another
C function which returns the error in a thred-safe way. The wrapper
would have to check for errno and pass it in some way to Haskell
together with the proper result - either through a pointer (which needs
extra alloca per C function call) or special thread-local variables.
It would be really bad to not have thread-local errno.

> > withObject   :: Storable a => a -> (Ptr a -> IO b) -> IO b
> 
> BTW, can't we just use `with' now.  IIRC, the only reason Marcin
> used `withObject' was because of a clash with the implicit parameter
> extension.

Indeed.

> This has been changed now, hasn't it?

Everybody agreed that "let" should be used instead of "with",
but the change has not been made yet.

> There is one exception: MarshalCString shouldn't be
> re-exported by Foreign (like CTypes).

If language separation is realistic, we would also keep errno handling
outside basic Foreign. But it yields several separate C-specific modules...

module CForeign?

It would reexport Foreign, CTypes, CTypesISO, MarshalCString and CErrors
(or whatever they will be called).

BTW, why are CTypes and CTypesISO separate?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-05 Thread Marcin &#x27;Qrczak' Kowalczyk

Sat, 06 Jan 2001 02:24:00 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> Actually, given this unicode mess, how are we supposed to
> handle individual `Char's?  A Haskell `Char' may expand to a
> sequence of 8bit `char's.  That's a problem when the C side
> only expects a `char' and not a `*char'.

And BTW: many languages have strings only and don't work on individual
characters at all. Libraries usually work on strings. IMHO it's
not a problem at all to not provide much of support for individual
characters. Only strings are important in practice.

Conversion which changes the length might be a problem only if a
library works on positions within text. For example readline can show
the whole line being read, and the cursor position. But conversion
of the whole line to Haskell does not allow determining the right
cursor position in terms of Haskell characters.

Well, readline does not support multibyte encodings anyway, and
it can be assumed that positions will match in practice. (I once
hacked bash to work on a UTF-8 terminal but I don't think the patch
is used anywhere.)

Handling strings in C is so "manual" that I don't think much fun
can be provided besides withCString / mallocCString / peekCString.
Somebody might wrap a string in ForeignPtr CChar to avoid a conversion
to a Haskell string, but it's already easy enough, and IMHO strings
don't need yet another type just for interfacing with C.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: Let's get this finished

2001-01-05 Thread Marcin &#x27;Qrczak' Kowalczyk

On Sat, 6 Jan 2001, Manuel M. T. Chakravarty wrote:

> I think that this is a good idea.  Especially, because of
> the encoding business, Strings are special and it is better
> to make this explicit in the types.

I'm not sure if this is a good idea. I haven't seen convincing arguments
yet. Let's keep it simpler.

> Actually, given this unicode mess, how are we supposed to
> handle individual `Char's?

Depending what do you want to do. You may pass it as Char and get HsChar
in C. You may convert [ch] to a C string (which may be longer than one
character) and get char * in C. You may need it in an ASCII context (e.g.
a commandline flag) and cast it to CChar (there is castCharToCChar in
QForeign); "cast" in the name suggests that it preserves the physical
contents rather than the meaning.

> A Haskell `Char' may expand to a sequence of 8bit `char's.  That's a
> problem when the C side only expects a `char' and not a `*char'.

No library will be able to represent Char or wchar_t in a single char.

> > Could you explain the motivation for these?  I can see the need for some
> > way to convert Bool<=>CInt (which is defined by ISO C), but can't the
> > others be just fromIntegral?
> 
> One reason for extra functions is that we might want to
> handle overflows differently.

We would need to use a different interface to signal the overflow. Some
exception monad (Maybe or IO). These additional functions don't provide it
anyway and I will stick with fromIntegral - the most natural Haskell's way
of converting integers.

> Furthermore, I have 
> 
>   instance IntConv Char where
> cToInt   = ord
> cFromInt = chr

No external C library will want either HsChar or HsInt. When we are
writing the C part ourselves, we may choose the type on the C side without
conversion in Haskell. For working internally to Haskell ord and chr are
sufficient.

> Now, the current routines in MarshalUtils are overloaded via
> `Storable', which works fine for the primitives (in fact C2HS uses a
> default method for the primitives).  It becomes interesting for more
> complex types.

When there is more than one way to pass a complex type, I would just use
separate functions if a Storable instance does not fit.

I would represent a pointer to a C string as Ptr CChar in Haskell and use
different functions for distinguishing what we want to do with it. Passing
the string to C functions is not the only thing we might want to do with
it - e.g. we could wish to realloc it, or work on [CChar] in Haskell, or
convert it to an aray of bytes, or pass a pointer to the middle to a C
function. IMHO it's better and less constraining to be explicit, keep the
type and make approprate functions as needed. withCString is not that
harder than toAddr. There are too many possible operations to express them
in one overloaded function on different types.

> For example, remember the case where Marcin had to store a nullFunPtr
> on the C side and explicitly test for it before calling
> freeHaskellFunPtr.  I think, it was Malcolm who argued that Marcin
> should better use `Maybe (FunPtr a)' on the Haskell side.  One reason
> that Marcin didn't do that might be that he didn't have
> ToAddr/FromAddr, but only functions overloaded via `Storable'.

ToAddr/FromAddr would not help here, unless they provided some
appropriately overloaded variant of peek.

[...]
> This transparently handles the `Maybe' representation for
> NULL pointers, without cluttering the marshalling code with
> special code for `Maybe'.

Passing Maybe as a maybe-null pointer is easy already:
maybe ($nullPtr) withCString maybeString $ \ptr -> ...

For the other direction a single function could be added:
maybeNull :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybeNull f ptr
| ptr == nullPtr = return Nothing
| otherwise  = liftM Just (f ptr)

Use it as such:
do
maybeString <- maybeNull peekCString ptr
...

-- 
Marcin 'Qrczak' Kowalczyk



___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-04 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 4 Jan 2001 02:59:05 -0800, Simon Marlow <[EMAIL PROTECTED]> pisze:

> Actually I consider the current libraries to be on the verge
> of usability, modulo the missing string marshalling and error
> functionality.

For both subjects I have a proposal in QForeign. I have no doubts
about the strings story, except the internals of the charset conversion
machinery. Error handling functions are more arbitrarily chosen.

> I've been wondering whether we should have something like
> 
>   newtype CString = CString (Ptr CChar)
> 
> which would allow GHC to replace the representation with a ByteArray
> leading to a much more efficient implementation of withCString.

Do you have the overhead of malloc in mind? If so, perhaps a generic
stack allocator would be better.

Anyway, conversions between strings which involve charset conversions
require a more sophisticated pattern of memory allocation. It is
not known how much space will be needed in advance, it can only be
estimated. It is known when the string has already been stored in
some memory directly accessible to C functions (in the common case of
using the default conversion).

Doing it on ByteArrays would be very tricky. There is no reallocByteArray
and ByteArrays are not convertible to Ptrs (I currently assume that
a conversion implemented in C will be exposed as a function working
on Ptrs).

My current strategy is to use malloc directly instead of alloca.
If there was a faster alloca allocator, it could make sense to make
a guess about the size and use alloca, resorting to malloc if it
didn't fit. It would have to be significantly faster to think about
making it more complex at all. The conversion itself can be a larger
overhead than malloc.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: nhc98-1.{00,01} produce crashing programs

2001-01-04 Thread Marcin &#x27;Qrczak' Kowalczyk

Thu, 4 Jan 2001 14:22:52 +, Malcolm Wallace <[EMAIL PROTECTED]> pisze:

> I don't understand - can you explain?  Surely the Num instances for
> Word/Int 8/16/32/64 mean that a literal integer 3 in the source code
> becomes (fromInteger 3) in reality, and this should be fine in
> case comparisons.

module Test where
newtype I = I Int
instance Eq I
instance Show I
instance Num I
test:: I -> Bool
test 0 = True
test _ = False

Fail: What? matchAltIf at 7:10

> As to dynamic import and export, I have never had any luck playing
> with dynamic loading of libraries in C.

They have nothing to do with dynamically loaded libraries.

foreign import dynamic is a plain generic "apply" operator in C:
take a pointert to a function and its arguments, return the value
returned by the function.

foreign export dynamic is harder. It must wrap a Haskell function
(closure) in a C function pointer. It is not possible to do this
portably in C: function pointers are normally only pointers to elements
of the finite set of (toplevel) functions. It should allocate a
block of unmovable memory on the heap (perhaps using malloc), attach
an equivalent of StablePtr of the function to it on a known offset
(to be able to free it later using freeHaskellFunPtr), write there a
constructed machine code which has this stable pointer hardcoded in
its body and applies it to parameters passed from C, and return the
pointer to the block as a function pointer.

> However, as far as I am aware, we agreed to remove the idea of
> *multiple* finalizers from the common FFI spec, because they have
> too many potential semantic problems.

I don't remember what the official spec says. Perhaps
addForeignPtrFinalizer should be dropped at all; I never used it.
It is present in ghc so I carried it on to QForeign.

Recently a bug in its implementation was fixed (which was discovered
because of a change in the typechecker). Did it work at all previously?
If not, I would just drop it.

> The next release of nhc98 will include GetOpt, Parsec, and a whole
> host of other libraries.

Parsec currently uses local universal quantification in one module to
simulate first-class modules. (I haven't uses that module in hsc2hs.)

> Yes, nhc98's Bit library follows version 1.3 of the Haskell Library
> Report,

I didn't know it was standarized.

> Fortunately, the next release of nhc98 can provide both interfaces
> if you wish.

Well, I used Bits on ghc because it is the only version it provides, so
to port library wrappers in QForeign to nhc I had to port Bits as well.
Some people say that Bits is ugly. I don't have an opinion how it should
really look like.

> > nhc does not provide CTypes and CTypesISO modules, nor HsFFI.h
> 
> CTypes and HsFFI.h exist as of yesterday.  CTypesISO will follow shortly.

I haven't found CTypes in CVS.

> Haskell characters are represented internal to nhc98 as 32-bit
> values, and always have been.

(maxBound::Char) is '\255', characters are cut to 8 bits in string
literals, HsChar is char, instance Storable Char use only 8 bits.

But they indeed seem to work otherwise. I will try to port Curses'
Unicode and perhaps my charset conversion machinery to nhc.

> > Is it possible to let hmake generate dependencies with that assumption?
> > Or could hmake be changed to support such scheme?
> 
> Yes, it is possible.  I've just committed a small patch to CVS
> which does what you want.

Thank you, it works.

BTW, 'make realclean' in nhc does not delete script/hmake-PRAGMA.{o,hi}.

Since the bug in Addr I reported previously makes FFI unusable on the
released nhc-1.00, I will not bother with supporting that version
of nhc, and thus any changes in nhc will be reflected directly in
QForeign without conditional support for the previous state, until
a version of nhc is released.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Let's get this finished

2001-01-04 Thread Marcin &#x27;Qrczak' Kowalczyk

On Thu, 4 Jan 2001, Manuel M. T. Chakravarty wrote:

> (1) It isn't H98 and in fact its interface cannot be
> implemented with H98[1].

It can.

>   malloc :: Storable a => IO (Ptr a)
>   malloc :: IO (Ptr a) = mallocBytes (sizeOf (undefined::a))

malloc :: Storable a => IO (Ptr a)
malloc = malloc' undefined
where
malloc' :: Storable a => a -> IO (Ptr a)
malloc' undef = mallocBytes (sizeOf undef)

>   alloca :: Storable a => (Ptr a -> IO b) -> IO b
>   alloca (act :: Ptr a -> IO b) = allocaBytes (sizeOf (undefined::a)) act

alloca :: Storable a => (Ptr a -> IO b) -> IO b
alloca = alloca' undefined
where
alloca' :: Storable a => a -> (Ptr a -> IO b) -> IO b
alloca' undef = allocaBytes (sizeOf undef)

> (2) pokeArray, peekArray, etc are really part of what should
> go into the high-level marshalling.

IMHO MarshalUtils exported by Foreign is the right place for it.
But I don't care how functions will be split into modules.

String handling will be needed. It would be silly to provide strings but
not provide arrays in general.

> The C2HS IntConv, BoolConv, etc classes.  Marcin just
> uses `fromIntegral' here, but I think that this is too
> limited - eg, it doesn't handle Bool.

You handle Bool by converting True to -1. I think that most libraries
would expect 1 as True. Anyway, IMHO it's ok to leave this out, because
it's easy to write (/= 0) in one direction, and (\b -> if b then 1 else 0)
in the other.

Well, for the latter it could make sense to provide a function which is
related to Bool as maybe is related to Maybe. It's a plain if with
a different order of arguments:
bool :: a -> a -> Bool -> a
-- Or the name cond might be better.
Then the conversion from Bool is: bool 1 0. Or bool 0 1. I'm not sure
which order is better (false true: consistent with maybe and ordering
on Bool, true false: consistent with plain if).

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: freeHaskellFunctionPtr

2001-01-03 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 3 Jan 2001 15:31:43 -0700, Alastair Reid <[EMAIL PROTECTED]> pisze:

> Which is all just my long-winded way of saying I agree with Simon
> that we should not do this.  Even if f.e.d. could return nullFunPtr,
> we should not do this because we can express it better using a Maybe.

I retrieve the value from a C struct, so I can't just use Maybe.
I must explicitly compare with nullFunPtr, which is not a big deal,
but IMHO the only sensible thing freeHaskellFunPtr could do with
a null pointer is to ignore it, rather than crashing.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: extended foreign decls

2001-01-03 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 3 Jan 2001 21:44:03 +1100, Fergus Henderson <[EMAIL PROTECTED]> pisze:

> Personally I'd rather have a single well-designed convenient foreign
> language interface as a standard part of the language, rather than
> having a minimalistic foreign language interface in the language
> standard and having convenience provided by a separate tool (or by
> several competing separate tools).  But I understand why you might
> differ on that point.

I would prefer that too if it was possible, but it does not look well.
Interfacing to C is complex enough, it's yet worse for other languages.

A problem: HsFFI includes some C headers (stdint.h, which includes
among others features.h on glibc). There are headers like stdio.h (if
I remember correctly) which provide certain prototypes or macros only
when certain macros are defined, like _XOPEN_SOURCE and _GNU_SOURCE.

If I #define these constants after inclusion HsFFI.h, it's too late:
features.h already determined what should be visible and it will not
be processed again. But hsc2hs does not distinguish between #defines
which should go before HsFFI.h and those which should go after. So
I had to define them via {-# OPTIONS -optc-D_XOPEN_SOURCE=500 #-}
instead of #define, or rather hsc2hs's #option (because it generates
its own {-# OPTIONS #-} and only one such pragma used to be accepted by
ghc), to be visible early enough. But hsc2hs needs them defined during
its job of preprocessing (for constants), so #define is needed too,
protected by #undef because symbols will be already defined when
#defines are processed in the generated C header (they are put in
multiple places):

#option -optc-D_GNU_SOURCE -optc-D_XOPEN_SOURCE=500
#undef _GNU_SOURCE
#define _GNU_SOURCE 1
#undef _XOPEN_SOURCE
#define _XOPEN_SOURCE 500

Ugly, isn't it?

Better ugly than impossible, assuming that the compiler provided only
a single elegant way of handling #defines.

Would a builtin support predict all possible uses of C features?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: extended foreign decls

2001-01-03 Thread Marcin &#x27;Qrczak' Kowalczyk

On Wed, 3 Jan 2001 [EMAIL PROTECTED] wrote:

> I am about to add something like {-# CCODE #include  #-}
> to nhc98 as a stop-gap.  Yes, this inevitably differs from whatever
> mechanism ghc currently uses.  So yes, tools like hsc2hs will have
> to know which compiler they are generating for.  Unless anyone wants
> to have a rethink now?  :-)

ghc has -#include  command-line option (if the header name is not
in "" or <>, "" are assumed).

Any command-line options can be put in the source thus:
{-# OPTIONS -#include  #-}

(These options currently have to be at the very top of the file
and AFAIK recently ghc was changed to accept more than one OPTIONS line.)

If nhc adopts that way, it must not generate prototypes itself of course.
A signature of a C function derived from Haskell is precise enough to call
the function in the right way via a native code generator, but not to
generate prototypes with exact constness etc.

hsc2hs inserts OPTIONS pragma when generating for ghc. QForeign comes with
wrappers for some libraries and a script to output hcflags, ldflags,
ldlibs. The script outputs appropriate -#include options for requested
libraries. Installation also runs ghc --add-package (on ghc >= 4.09) to
specify C includes among other things, and then e.g. -package
qforeign-curses option causes inclusion of curses.h, which makes the
former script unnecessary.

Having correct includes is especially important for ghc, because calls to
C functions may be inlined across Haskell modules. A user module doing
"import Curses" and being compiled with optiimzation and without
appropriate -#include options may cause the C compiler to call function
without prototypes, which is not legal in C99 and does not work for
argument types like char.

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: freeHaskellFunctionPtr

2001-01-03 Thread Marcin &#x27;Qrczak' Kowalczyk

On Wed, 3 Jan 2001, Fergus Henderson wrote:

> By "they", I mean the Haskell routines under discussion.

OK, I always thought that Haskell's FFI docs should document what they
assume about the C implementation which is not guaranteed by ISO/ANSI.

For example that pointers are physically amorphic, i.e. that
sizeof (int *) == sizeof (char *), and that
void poke1 (int **p, int *x) {*p = x;}
void poke2 (int **p, int *x) {*(char **) p = (char *) x;}
are equivalent, etc. - this follows from the existance of
instance Storable (Ptr a)

foreign export dynamic is not implementable portably at all. This is a
different kind of assumption - Haskell's FFI assumes that there exist a
way do implement this on the C implementation in question. Usually it is
processor-specific (unless the C implementation provides some generic
means which would allow that - I haven't heard of it and gcc does not
provide them).

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: freeHaskellFunctionPtr

2001-01-03 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 3 Jan 2001 21:12:54 +1100, Fergus Henderson <[EMAIL PROTECTED]> pisze:

> Well, if they are left, then at very least they should be
> very clearly documented as being non-portable.

They should, they aren't. Perl internally relies on the fact that
memsetting all bits to 0 produces null pointers (at least in one
place). Libraries use identifiers from the namespace reserved
to the C implementation. Libraries use Posix functions, Single
Unix Spec. functions, BSD functions, Linux functions etc. without
documenting what interfaces they require.

> > Yes: me, for the readline library.
> 
> Could you be more specific?

typedef struct {...} KEYMAP_ENTRY;
typedef KEYMAP_ENTRY *Keymap;
typedef int Function();


int rl_generic_bind (int type, char *keyseq, char *data, Keymap map)

If type == ISFUNC:
data should be a value of type Function *, cast to char *.
It will be applied to two int values.
If type == ISMACR:
data should be a string.
If type == ISKMAP:
data should be a value of type Keymap, cast to char *.


Function *rl_function_of_keyseq (char *keyseq, Keymap map, int *type)

Returns data as set by rl_generic_bind, cast to Function * this time,
and sets type appropriately.

> Why was the cast needed?

Because the library is designed and written in a horrible way.

> > Another example is dlopen.
> 
> I think you mean dlsym().

Sure.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: freeHaskellFunctionPtr

2001-01-03 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 03 Jan 2001 12:27:20 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> This means that we should not provide
> 
> castFunPtrToPtr :: FunPtr a -> Ptr b
> castPtrToFunPtr :: Ptr a -> FunPtr b

It does not mean that, because existing C libraries are usually
non-portable and some do require using such casts, however meaningless
they could be.

> Has anybody ever used these casts?

Yes: me, for the readline library.

> As long as `FunPtr' is used for f.e.d., I don't see much use in
> these casts.  It certainly doesn't make much sense to peek and poke
> an address produced by f.e.d.

But it's used to pass either a function pointer cast to a data pointer
or a real data pointer to a function, together with an enumeration
value indicating which one is this. Ugly, but that's life.

Another example is dlopen.

We could remove these casts, but they will be used anyway: they
would have to be produced by wrapping a C function (relying on the
implementation of both in terms of Addr forever might be not the
best practice, especially if function pointers on IA-64 are 16 bits -
I'm for 90% sure about this).

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: extended foreign decls

2001-01-02 Thread Marcin &#x27;Qrczak' Kowalczyk

Tue, 2 Jan 2001 22:28:02 +1100, Fergus Henderson <[EMAIL PROTECTED]> pisze:

> Doing it in a separate tool will lose efficiency in some important
> cases.  If the compiler is compiling via C, then it can insert
> inline C code directly in the generated code, and thus get
> inlining.  But I think a separate tool would have to put the C code in
> a separate C file, which would prevent inlining.

hsc2hs creates a .c file and a .h file for snippets of C code.
The .h file is included into the .hc file generated by ghc.
If you mark functions as inline, they will be really inlined.

BTW. gcc understoods the word "inline" differently than ISO/ANSI C99
defines it. The following files are produced from a simple source:
#include 
#def inline HsInt get_errno (void) {return errno;}
It works with gcc and should work with a hypothetical C compiler which
understands inline correctly.

 .h file 

#ifndef TEST_HS_H
#define TEST_HS_H
#if __GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ < 409
#include 
#endif
#include 
#include 
#ifdef __GNUC__
extern
#endif
inline HsInt get_errno (void) {return errno;}
#endif

 .c file 

#include "Test.hs.h"
#ifndef __GNUC__
extern
#endif
inline HsInt get_errno (void) 
#ifndef __GNUC__
;
#else
{return errno;}
#endif

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: freeHaskellFunctionPtr

2001-01-02 Thread Marcin &#x27;Qrczak' Kowalczyk

On Tue, 2 Jan 2001, Simon Marlow wrote:

> > I would let freeHaskellFunPtr accept and ignore nullFunPtr, since I
> > once had to write
> > when (ptr /= nullFunPtr) $ freeHaskellFunPtr ptr
> > and it can be seen as consistent with free.
> 
> This makes sense if nullFunPtr is really a valid value for a FunPtr.
> The FFI spec doesn't say anything about f.e.d. functions possibly
> returning nullFunPtr.

They don't return nullFunPtr. My case was seting in a C struct a function
pointer made by f.e.d. or a null function pointer, for a C interface which
takes an optional user function (db3). Later the function pointer must be
freed if it was set, and there is nothing to be freed if its absence was
marked by nullFunPtr.

Null function pointers are a non-portable concept - ANSI C does not have
them, only null data pointers. But many existing C interfaces use them,
and even the ability to cast between data pointers and function pointers
is described as a common non-standard extension in ISO/ANSI C99.

-- 
Marcin 'Qrczak' Kowalczyk



___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: freeHaskellFunctionPtr

2001-01-02 Thread Marcin &#x27;Qrczak' Kowalczyk

Tue, 02 Jan 2001 19:40:11 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> PS: It could be argued that `Ptr ()' can always be used
> instead of `Addr' and that therefore we should do away
> with `Addr' altogether.  Opinions?

I agree that Addr uses should be replaced by Ptr and FunPtr
(well, I thought it was obvious!).

Since Addr is used much in ghc and nhc and probably external libraries,
we will live with both for some time, perhaps long, and it's not
necessary to convert everything in a hurry. But I would not care if
some functionality is provided in Ptr flavor only, especially as it's
easy to convert in both directions.

newForeignObj has been converted to Ptr, but since ForeignObjs
themselves were later replaced with ForeignPtrs, it makes sense to
let newForeignObj use Addr again as in previous released versions of
ghc. For withForeignObj it could be done for consistency too (it's
new so it does not really matter).

I would let freeHaskellFunPtr accept and ignore nullFunPtr, since I
once had to write
when (ptr /= nullFunPtr) $ freeHaskellFunPtr ptr
and it can be seen as consistent with free.

It could be called freeHsFunPtr instead.

I asked once and got no response: in ghc's implementation, should it
really be foreign imported unsafe?

On IA-64 C function pointers are AFAIK twice as big as data pointers
(16 bytes!), to hold a global data pointer associated with the module
the function came from, which is a part of a model of dynamically
linked libraries. I don't know what ghc is going to do with it - it
uses function pointers internally a lot! It also means that FunPtr
will no longer be represented the same as Ptr on IA-64.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



qforeign-0.63 is out

2000-12-29 Thread Marcin &#x27;Qrczak' Kowalczyk

http://download.sourceforge.net/qforeign/qforeign-0.63.tar.gz
(Will be in CVS there soon.)

Changes since 0.62:

* Adapted to MarshalUtils and ForeignPtr introduced in ghc-4.11.
* Works on ghc-4.08 through ghc-4.11 and nhc98-1.00 through nhc98-1.01.
  Uses native modules where available, otherwise supplies missing parts
  itself if possible. (nhc is currently too buggy and produces crashing
  programs.)
* Examples split into separate packages which link the right C libraries
  and #include the right C headers. Ready for using in other people's
  programs.
* qforeign-config script for using with ghc versions without user
  packages and with nhc.
* hsc2hs (renamed from glue-hsc) implements #undef, #error, and #let
  (macros to be applied to the Haskell source, although using somewhat
  ugly stringified syntax).
* Can be used either after 'make install' or after building inplace.
* Db3 interface started (very incomplete).
* Include files CHANGES and COPYING.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: cvs commit: fptools/hslibs/lang ForeignPtr.lhs MarshalUtils.lhs Foreign.lhs ForeignObj.lhs Storable.lhs

2000-12-11 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 11 Dec 2000 02:03:27 -0800, Simon Marlow <[EMAIL PROTECTED]> pisze:

>   Change to the FFI recently discussed on the mailing list.
>   Still to come: error handling utilites.
>   
>   This is mostly untested.

Thanks. I've been sceptic about ForeignPtr, but now I like it.

In three of qforeign's library interfaces it is applied only to type
tags, but it caused a small simplification: no newtype constructor
wrapping and unwrapping. Ptr () in foreign imports changed into
Ptr TheAppropriateTypeTag, which is good.

I've been worried that in practice types become non abstract (of course
one could always use newtypes, but having both a newtype and a tag is
somewhat redundant). But it's not really a problem. One requires ghc
extensions to make instances for such types, but the whole FFI is an
extension anyway. OTOH when a different (==) than pointer equality
is needed, the type must still be wrapped in newtype.

In the fourth case, Libgr, it was a real improvement which convinced
me that ForeignPtr was a good idea. Parametrized newtyped ForeignObjs
used in overloaded functions, which required using pattern and result
type signatures to pass the type from the parameter of the newtype
to pointers extracted from the ForeignObj, changed into ForeignPtr
applied to real storable types. All types magically began fitting.

It is similar to the case of character encoding conversions, where I
originally wanted them to have a single type but distinguishing streams
of Chars from streams of Bytes caused surprising simplifications. I
learned that types acting as tags for parametrizing other types are
really nice, and Haskell likes to be statically typed!

If only it was not necessary to introduce value constructors in
definitions of type tags...

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: extended foreign decls

2000-12-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 6 Dec 2000 16:35:51 +, [EMAIL PROTECTED] <[EMAIL PROTECTED]> 
pisze:

> I *really* *really* want to be able to insert small snippets of
> foreign code into the source of a Haskell module.

You can do it with hsc2hs:

foreign import "hs_PyTuple_Check" unsafe
tupleCheck :: Object -> Bool
#def inline HsBool hs_PyTuple_Check (PyObject *o) \
{return PyTuple_Check (o);}

The C wrapper was needed here because PyTuple_Check is a macro.

Inside the body there is no need of \ at the end of every line.
Until the matching } everything belongs to the #def.

> I know that it is always possible to write a small .c file and
> compile and link it in separately, but with the new FFI that now
> seems to necessitate writing an additional .h file as well.

hsc2hs writes the .h and .c files for you. It knows how to extract
a declaration or prototype from a definition of a function (inline
or not), variable, struct and typedef. You have to compile and link
the .c file yourself.

> For instance, in the new FFI I often want to do something like
> 
> foreign code { #include  }

Includes are handled separately. You write

#include 

and it gets included where needed: into the temporary C program
which outputs the Haskell source, in the compiled Haskell module if
compiling via C, and into the .h file if it was generated because
a #def was present.

> foreign code C {
>   char *readdirent (DIR*d) {
> struct dirent *e;
> e = readdir(d);
> return e->d_name;
>   }
> }

With hsc2hs you don't have to write such wrappers for all fields.
(#peek struct dirent, d_name)
is an expression which can be used as having the type
Ptr a -> IO (Ptr CChar)

You have to ensure that its usage allows to infer the right type for
the result. It is overloaded on Storable.

> As people have pointed out, we need to avoid being totally C-centric,
> which is why there needs to be a language identifier attached.

hsc2hs is of course C centric, but for another language simply
a different preprocessor would be used.

Anyone wants to design hsc++2hs? :-)  But currently you would have
to write extern "C" wrappers for all native C++ functions, methods,
constructors, destructors, conversions, casts through virtual
inheritance...

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Proposal #2: marshalling utilites

2000-12-06 Thread Marcin &#x27;Qrczak' Kowalczyk

Wed, 6 Dec 2000 03:04:25 -0800, Simon Marlow <[EMAIL PROTECTED]> pisze:

> >* s/Marshal/MarshalUtils/
> 
> ok, that seems to be the consensus.

Not StorableUtils, to show that it's a set of wrappers and utils
extending basic Storable things?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: qforeign-0.62

2000-12-04 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 04 Dec 2000 17:17:09 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> So far, we have handled similar cases by using the inefficient
> variant as the "default" and adding a RULES pragma to get the
> efficient version.  See, for example, the various IntXX to Int casts.
> We can use the same technique here.

We can, but it will work only in some cases. It will not work
when somebody writes a function which accepts any conversion and
applies this function to a conversion where an optimization would be
preferable, unless he is very lucky in inlining and writes only code
where the conversion can be resolved statically.

> We know that the conversion interface can look like
> 
>   conv :: String -> IO [CChar]

In this case _any_ optimization making use of the representation of
particular conversions must use RULES (which is non-portable BTW).

An important application of such optimization is I/O. We don't want to
read the file contents into char[] buffers, convert them to [CChar]
only to put them back into char[] buffers to call iconv and finally
read back a String. The first buffer was already a good input to
iconv. Since a conversion will happen by default, it should not be
unnecessarily slow.

If the representation of some conversions makes the fact that they
work best on raw C arrays explicit, calling code will be efficient
no matter what was inlined and how dynamic is the place where the
conversion was specified.

I'm afraid that most of the time RULES will not fire and Haskell will
be yet slower than it is now. I don't want to force people to use
non-standard string representations to get reasonable performance
if the situation could be significantly improved by using explicit
representation of conversions implemented in C.

It should not be surprising that code which needs to convert between
Haskell strings and C strings (or Haskell strings and streams of bytes
in files) is dependent on a library which deals with these conversions.
Unfortunately the library cannot work well enough if the interface
is as simple as String -> IO [CChar]. I like making things simple
but here I cannot imagine how do do it without compromising efficiency.

> What tool?  I am not talking about a library plus tool, but
> only about the library.  The high-level library should be
> part of the FFI standard and so will come included with
> every compiler that supports the FFI (just like the `List',
> `Maybe' and so on standard libraries).

OK, so what should this library provide? My functions were a step in
this direction, even if they were not explicitly marked as a part of
a high level library proposal.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: efficiency

2000-12-04 Thread Marcin &#x27;Qrczak' Kowalczyk

Mon, 4 Dec 2000 04:15:28 -0800, Simon Marlow <[EMAIL PROTECTED]> pisze:

> Ok, so the malloc/free is the most expensive part.  I'm moderately
> surprised:)  Perhaps we could do a better job, but we'll never do
> better than ByteArrays as long as the bracket is required.

BTW, withCString in my implementation which handles charsets does not
use alloca but malloc. It's because we don't know the length of the
resulting char[] until we convert it, so we cannot preallocate it.
We must guess an initial size and realloc the array as needed.

Hence unfortunately speeding up alloca won't speed my implementation
of the common need of allocating C objects.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: efficiency

2000-12-04 Thread Marcin &#x27;Qrczak' Kowalczyk

On Mon, 4 Dec 2000, Simon Marlow wrote:

> Thread stacks fall into the category of "large objects" in GHC's storage
> manager, and therefore aren't normally moved.  However, they have to be
> able to grow on demand, so we occasionally have to relocate them.

Maybe the storage for use by alloca could be allocated as a linked list of
large memory blocks. It should still make use of efficient stack-like
allocation within the block.

> because I recon eliminating the exception handler is more important than
> speeding up the actual malloc/free.

Hmm...

-- 
Marcin 'Qrczak' Kowalczyk


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Proposal #2: marshalling utilites

2000-12-02 Thread Marcin &#x27;Qrczak' Kowalczyk

Sat, 02 Dec 2000 13:49:52 +1100, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> pisze:

> And because the greatest fun of all is to argue about names,
> I propose to rename `throwIf_EINTR', `throwIfNull_EINTR',
> and `throwIfMinus1_EINTR' to `throwIfEINTR',
> `throwIfNullEINTR', and `throwIfMinus1EINTR', respectively.

Perhaps testing for (== -1) and (== nullPtr) is not worth their own
functions and throwIf (== -1) is enough to keep the interface smaller.

It must be stressed that these functions translate errno - this fact
is not visible in their interface. They can easily be misused if a
library function just returns something in case of an error but does
not set errno at all.

Anyway, I think that the following functions are more important :-) than
throwIfMinus1 and throwIfNull (perhaps under better names):

sequenceCont:: [(a -> z) -> z] -> ([a] -> z) -> z
mapCont:: (a -> (b -> z) -> z) -> [a] -> ([b] -> z) -> z

Example of usage:

execv:: [String] -> IO a
execv args = do
mapCont withCString args $ \argPtrs@(arg0Ptr:_) ->
withArray0 nullPtr argPtrs $ \argsPtr ->
execvC arg0Ptr argsPtr
throwErrno "execv"
foreign import "execv" unsafe
execvC :: Ptr CChar -> Ptr (Ptr CChar) -> IO CInt

Without them one has to write a recursive helper function.
Unfortunately plain mapM does not work for continuation-style
allocations.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: errno again

2000-12-02 Thread Marcin &#x27;Qrczak' Kowalczyk

Sat, 2 Dec 2000 13:13:08 +1100, Fergus Henderson <[EMAIL PROTECTED]> pisze:

> > 1. Is it possible to have the second kind from the level of the
> >Haskell compiler at all (done in an sufficiently elegant way to
> >think about it as a candidate proposal for the official FFI)?
> 
> I think so.

I hope that improvement there is possible, because even importing
plain C functions to ghc is not perfect:

- When using the native code generator, there is no type checking
  across languages at all.

- When compiling via C, the C function sometimes gets inlined in the
  interface file and called directly from other modules which did
  not include the C header. It results in a warning about implicit
  function definition (which is illegal in C99 BTW) and will not work
  at all for foreign labels.

So we don't really have a choice: there should be some notion of
a "C preprocessor and declaration environment" needed by a Haskell
module. It must be robust enough to make it possible to automatically
reproduce the environment for other modules which use the module
which introduces the environment.

Maybe it should not be transferred unnecessarily. When no C function
is inlined in an exported Haskell function, it does not buy anything
to transfer the C environment, and there is always the danger of
conflicts with other C headers.

One minor but annoying thing: when a function is declared in a C
header only when a given preprocessor symbol is defined, and the
header gets included automatically by ghc's rts, it is too late if
the symbol is defined e.g. in another C header which is included
using ghc's -#include option. It must be passed to ghc command line
as e.g. -optc-D_XOPEN_SOURCE. I'm afraid that such glitches may become
a pain if the machinery is automatized in a wrong way.

It will surely get worse when aiming at other languages :-)

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



  1   2   >