Re: Import, how to

2010-07-18 Thread Malcolm Wallace
I'm a beginner at haskell and ffi. I was trying to import and use is  
haskell

one C function, but I can't manage to do that.

Can someone show me an example how to create an import and a use  
example for

such a C function:
char functionName(char *, unsigned int, char *)


{-# LANGUAGE ForeignFunctionInterface #-}
module FOo where

import Foreign
import Foreign.C
import Data.Word

foreign import ccall functionName functionName_inC
:: CString - Word - CString - IO CChar

-- Assuming you really want to use Haskell Strings and Ints etc
-- and furthermore if the C function is really pure,
-- add the following wrapper.

functionName_h :: String - Int - String - Char
functionName_h s0 i s1 =
unsafePerformIO $
withCString s0  $ \cs0-
withCString s1  $ \cs1-
do cchar - functionName_inC cs0 (fromIntegral i) cs1
   return (castCCharToChar cchar)


Regards,
Malcolm

___
FFI mailing list
FFI@haskell.org
http://www.haskell.org/mailman/listinfo/ffi


Re: Force single evaluation?

2006-12-18 Thread Malcolm Wallace
Axel Jantsch [EMAIL PROTECTED] wrote:

 I call a C function from a Haskell program. I am using unsafePerformIO
 to use it outside a monad. 
 
 Even though the C function does not have any side effect, I absolutely
 don't want to evaluate it more than once for performance reasons. But
 my impression is that it is evaluated several times.
 
 1. Can I monitor somehow how often it is evaluated?

You could wrap it (in C) with another function that keeps a counter of
invocations in a static local variable.

result_t  originalFn (arg1_t arg1, arg2_t arg2);
result_t  wrappedFn  (arg1_t arg1, arg2_t arg2) {
  static int i = 0;
  i++;
  fprintf(stderr,originalFn called %d times\n,i);
  return originalFn(arg1,arg2);
}

 2. Can I ensure that the function is evaluated only once?

How about stating in the type of the FFI decl that the C function is
pure (even if it is not)?  Then be sure to bind its result in only one
place.  That should guarantee it is called only once.

foreign import ccall originalFn :: Arg1T - Arg2T - IO ResultT
becomes
foreign import ccall originalFn :: Arg1T - Arg2T - ResultT

Regards,
Malcolm
___
FFI mailing list
FFI@haskell.org
http://www.haskell.org/mailman/listinfo/ffi


Re: The Errno Story

2003-07-25 Thread Malcolm Wallace
Dean Herington [EMAIL PROTECTED] writes:

  foreign import ccall_errno unistd.h chdir :: Ptr CChar - IO (CInt,CInt)
 
 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?

The first and most obvious disadvantage is that the basic FFI currently
has no direct mechanism to return a pair of values.  The idiomatic way to
achieve the same effect is to store the two values in a C structure
and return a pointer to it, unpacking the structure again on the
Haskell side of the interface, and de-allocating the structure
somehow afterwards.

Obviously this is a tedious and mechanical job to go through, but this
is exactly the province of tool support, rather than the basic FFI.
There are already tools that support this idiom (e.g. GreenCard),
and you can already write your errno bindings this way if you want to.
For instance:

  %#include errno.h
  %fun chdir :: Ptr CChar - IO (CInt,CInt)
  %call   (ptr cd)
  %code   res=chdir(cd);
  %result (cint res, cint errno)

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


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

2003-06-05 Thread Malcolm Wallace
* 6.2:   All the types in CTypes must be newtypes that are exported
 abstractly. 
  
  How about exporting them non-abstractly for nhc98 only, and adding a
  comment to explain why the workaround is necessary?
 
 That's what I prefer, too.

OK, that's what I've done.  The spec can stand as it is.

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


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

2003-06-05 Thread Malcolm Wallace
  Let's be clear about the role of Point here:  it is a dummy type
  argument to Ptr, used to disambiguate the type 'Ptr Point' from any
  other kind of Ptr.  It is for type-safety in the Haskell code.
  
  It doesn't matter how many values of the type Point there are.  I could
  use any Haskell type with the same results.
 
  There definitely aren't any values of type Point, so I don't see why it
  needs a semantics.

OK, I think I agree with all of this.

 My main problem with this extension is the following:
 
 * As we have learnt, nhc98 and Hugs use `data T' for an
   entirely different purpose than the one proposed by John
   (namely to represent primitive external types).  It may be
   possible to abuse nhc98 and Hugs `data T' also in the way
   John wants it (and GHC provides it), but this sounds less
   straight forward than initially where the impression was
   given that the three systems already implement the same
   extension.

Actually, I think both Hugs and nhc98 straightforwardly allow
John's use.  All three systems do implement the same extension.

In fact it is the current usage of 'data T' for primitive types that
is tricky.  At the moment, basically they must be *internal* types,
i.e. types already known to the Haskell runtime system.  The idea
of using them for external, previously unknown, types is entirely
speculative.  It would require somehow specifying storage sizes, and
routines to marshal values into the heap, and perhaps more.  None of
these mechanisms yet exist.  The question was raised as to whether we
might one day want those facilities, because the natural place to
specify them is in the FFI.  But no-one even has a proposal for how
it might work, so I think we can safely dismiss it at this stage.

 data Point
 foreign import getMousePos :: Ptr Point -  IO ()
 foreign import getX :: Ptr Point - IO Int
 foreign import getY :: Ptr Point - IO Int

vs

   data Point = Point (Ptr Point)
   foreign import getMousePos :: Point -  IO ()

I like the second idiom.  You are right that there is no need for
the application programmer to know whether pointers are involved,
because even in the first style, it is not possible to 'peek' inside
a Ptr Point to get the `actual' Point value.  So why not hide the
pointer altogether?  Yes.

Regards,
Malcolm
___
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 Malcolm Wallace
John Meacham wrote:

  This was discussed here before and there seemed to be some support for
  it, but how about adding the empty data declaration extension to the FFI
  spec?

I agree, it would be a suitable addition to the FFI, since it is the
place where such types make most sense.


Alastair Reid [EMAIL PROTECTED] writes:

 The correct semantics has to be something roughly like:
 
 [[
   The declaration
 
 data T
 
   declares a type T whose set of values are defined externally to the
   language. [optional sentence: There are no legal Haskell operations 
   on values of type T.]
 ]]

I don't really like the optional sentence, since it suggests that
a foreign imported function that operates over such values is not
legal Haskell.  How about something like:

  The declaration
  data T
  declares an abstract datatype T, whose values and operations are
  defined external to the Haskell language.  Values of T follow
  the semantics of the foreign language, in particular, with respect
  to mutability and the admission of the undefined value.

This raises the question of whether it should be possible to declare
foreign functions directly over such types, rather than through
pointers, e.g.

data T
foreign import mkT  :: IO T
foreign import fooT :: T - T

rather than

data T
foreign import mkT  :: IO (Ptr T)
foreign import fooT :: Ptr T - Ptr T

Obviously the former is much less safe than the latter.  However,
I know that nhc98 internally at least uses the former style in order
to implement built-in types like arrays, big integers, etc.  I'm not
suggesting we should necessarily formalise that hack as part of the
FFI standard - I'm just raising the question for consideration (and
probable rejection), so that our choice is an informed one.

 I'm not especially keen to change the syntax (especially since the existing 
 syntax is so trivial to implement) but if we're going to add this to the
 language, we should make sure the syntax and semantics are tolerably
 clear and in agreement with each other.

I'm not keen to change the syntax either.  The current style is pretty
clear to my mind.  But it is right that we should think about it.

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


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

2003-05-27 Thread Malcolm Wallace
Manuel M T Chakravarty [EMAIL PROTECTED] writes:

 -=- Changes since RC 9
 
 * 6.2:   All the types in CTypes must be newtypes that are exported
  abstractly. 

This change makes things highly inconvenient in nhc98.  A newtype
can only be passed across the FFI in nhc98 if we have enough
information to determine the original type that is being renamed.
If Foreign.C.Types exports them abstractly, then currently we do not
have that information, and so these types cannot be used at all!

I am not suggesting that the newtype constructors should necessarily
be part of the API seen by the user, but the problem comes down to a
known deficiency in nhc98's interface file conventions.  

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


Re: deriving instances of Storable

2003-02-05 Thread Malcolm Wallace
mike V [EMAIL PROTECTED] writes:

 Is there any merit in the idea of allowing instances of Storable to be 
 derived in a similar fashion to Show, providing that constituents are of
 class Storable.
 
 The benefits would be significant - automatic marshalling of structures.
 uses: storing to disk, passing over network etc etc..

For storage and transmission needs, what you really want is binary
serialisation.  There are a couple of implementations of class Binary
out there already - have a look at the [EMAIL PROTECTED] list for
the most recent discussion.

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



Re: newForeignPtr

2003-02-03 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

  However, only Hugs implements this part of the spec at the moment.
 
 It will be implemented in GHC before the next major release.  I'm not
 intentionally dragging my heels on this one, just haven't got around to
 it yet :-)

And of course the ghc-5.04 branch will keep the existing (non-standard)
signature, because there are no API changes permitted in bug-fix releases.

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



Re: Re-exporting modules in the Foreign hierarchy

2003-01-20 Thread Malcolm Wallace
Sven Panne [EMAIL PROTECTED] writes:

 Yet another change request for the FFI libraries: For reasons of
 consistency, I propose to introduce an intermediate module
 Foreign.Marshal, which re-exports the modules:
 
 Foreign.Marshal.Alloc
 Foreign.Marshal.Array
 Foreign.Marshal.Error
 Foreign.Marshal.Pool
 Foreign.Marshal.Utils

Seems reasonable.  It is a useful addition, with a trivial implementation,
so there's not much to go wrong I think.

 While I'm at it: What was the reason for the decision that Foreign.C
 re-exports
 
 Foreign.C.Types
 Foreign.C.String
 Foreign.C.Error
 
 but not Foreign.C.TypesISO? If there wasn't a good one, I propose to
 add this for consistency again.

I was recently pondering the same question.  The answer is that
Foreign.C.Types already re-exports everything from Foreign.C.TypesISO,
and therefore, transitively, Foreign.C also does so.

I do seem to remember a proposal at one stage to remove Foreign.C.TypesISO
altogether by incorporating it fully into Foreign.C.Types.  Given that
the latter re-exports everything from the former, is there any reason
for TypesISO to remain separate?

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



Re: Finalizers: conclusion?

2002-10-21 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 Ok, I'm sad to say that the problem we recently uncovered to do with
 finalizers sharing values with the rest of the program essentially kills
 off the possibility of doing Haskell finalizers in systems without
 proper concurrency support.

Well, I'm not yet totally convinced that we can't do it, but I'll happily
leave it for another time to work out how.

 Let's keep C finalizers for the FFI spec.  In GHC I imagine we'll
 continue to offer Haskell finalizers as an extension, but I haven't
 decided on an interface yet (suggestions welcome).

Since ghc-5.04.x already has the published interface

  module Foreign.ForeignPtr
newForeignPtr  :: Ptr a - IO () - ForeignPtr a
addForeignPtrFinalizer :: ForeignPtr a - IO () - IO ()

I suggest we keep those names for the Haskell finaliser extension.
This would eliminate version configuration questions for both existing
and future code that uses the interface.

I quite liked the suggestion of

newUnsafeForeignPtr  :: Ptr a - FunPtr (Ptr a-IO ()) - ForeignPtr a
addUnsafeForeignPtrFinalizer :: ForeignPtr a - FunPtr (Ptr a-IO ()) - IO ()

for the C-finaliser standard.

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



Re: Finalizers etcetera

2002-10-11 Thread Malcolm Wallace

Simon Peyton-Jones [EMAIL PROTECTED] writes:

 | takeMVar#   :: SynchVar# s elt - State# s - (# State# s, elt #)
 | putMVar#:: SynchVar# s elt - State# s - State# s
 
 Bad idea to look at the primops.

(a) It was the first mention of MVars that I found in the docs.
(b) I only really mentioned it because the type sigs are wrong.

 | readMVar :: MVar a - IO a
 | This is a combination of takeMVar and putMVar; ie. it takes the
 | value from the MVar, puts it back, and also returns it.
 | 
 | It specifically avoids describing the combination as atomic ...
 
 False.   readMVar is completely described by
   readMVar m = do { v - takeMVar m; putMVar m v; return v }
 
 If it gets pre-empted between the take and the put, no matter; anyone
 trying to take from that same MVar will block.

Doesn't it block if another thread manages to sneak a putMVar into
the middle?  Maybe I should read your Awkward Squad paper to find
out if this matters.

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



Re: Finalizers strike back

2002-10-11 Thread Malcolm Wallace

George Russell [EMAIL PROTECTED] writes:

 it would normally be a good idea for implementations and programmers to
 provide and use MVars, even if they do not provide and use concurrency,
 ...   If NHC does not provide MVars, I think it should.

I don't think MVars make any sense without concurrency, so I don't see
the point of implementing the one without the other.  I'm willing to
be persuaded otherwise.  (It would be nice to have some concurrency
in nhc98, of course, but I don't foresee that happening soon.)

 I apologise to Malcolm, but in any case I doubt if implementing
 MVars in a world with only one thread would cost him a great deal of
 effort.

Well it would be simple enough provided you didn't mind your
computation halting with deadlock rather unpredictably.  :-)

Actually, I'm just wondering whether I can use the GC as a poor-man's
scheduler.  If a finaliser blocks on an MVar, save its state, keep
the finaliser in the pending queue, and return to the main thread.
Then on the next GC, try the same finaliser again, ad infinitum until
it succeeds.

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



Re: Finalizers etcetera

2002-10-09 Thread Malcolm Wallace

Simon Peyton-Jones [EMAIL PROTECTED] writes:

 You didn't respond to my proposal, perhaps because it didn't seem like
 one (I've changed a few words).

I think I agree with your proposal as far as nhc98 is concerned.

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



Re: Finalizers etcetera

2002-10-07 Thread Malcolm Wallace

Some comments on the question of finalisers.

Firstly, a retraction.  In nhc98, it *is* possible to implement Haskell
finalisers, by creating a `pending' list of finalisers during the GC,
and then running them immediately the GC finishes.  I see several
messages in the archive where I claimed the latter was impossible.
I was wrong.  (The key issue is deciding when GC has really finished -
not as obvious as it looks, but I got there in the end.)

What is more, I am now pretty convinced that it is relatively trivial
to permit those finalisers to call foreign code that calls back into
Haskell, possibly triggering a further GC, and for everything still
to play nicely.  (A mutex lock is required to ensure that the pending
queue is not traversed more than once, but that is all I think.)

At the moment nhc98 still has the ability, as per recent changes in the
FFI spec, to call a foreign language finaliser (FunPtr (Ptr a - IO ()))
rather than a Haskell one.  However, our GC currently calls such a
finaliser immediately it finds it, i.e. in the middle of the GC cycle.
I am now certain that this is wrong, because the foreign code could
call back into Haskell, which of course would be disastrous in the
middle of a GC.  So just like with a Haskell finaliser, a foreign code
finaliser must be placed on a `pending' list and run only after GC
has finished.

Hence, I think the really key issue for the safety of finalisers is
not what language the finaliser is written in, but when it is run.

Now, how about concurrency?

nhc98 has no concurrency model, so all its interactions with foreign
code must be within a single thread.  This is true even if the foreign
code has concurrent threads internally.  Because nhc98 produces only
sequential code, all interaction with the Haskell program must take
place within that thread alone.  The sequential Haskell RTS simply
has to ensure is that when a Haskell GC is in progress, no foreign
code can run in the same thread.  (This is the reason for delaying any
finalisers until the GC is complete.)

For systems that do have concurrency, George points out that a
concurrent foreign thread might call into Haskell at any moment,
even when the Haskell RTS is in the middle of a GC.  True enough.
But this has nothing to do with finalisation per se, it is just a
general feature of any concurrent system where there is a combination
of languages.  Just apply the usual mechanism in the Haskell RTS to
exclude other activity during a GC.

I understand that there are more tricky issues in concurrency, to do
with shared access to resources, and scheduling policy.  However I am
still not sure of all the details, so Alastair's concerns are probably
well-founded.  I *think* the problem in Hugs is that the scheduler is
co-operative, so the GC cannot simply place a triggered finaliser into
a new thread and ignore it.  (The co-operative scheduler might delay
the running of the finaliser thread for an arbitrarily long time.)
The GC also cannot make the triggered finaliser into a new thread and
start running it immediately GC is finished.  (This would amount to
overriding the scheduler - pre-empting it in fact.)

Is this a fair characterisation Alastair?  If so, then I have two
questions:
  (1) Why is it a disaster for a finaliser to be delayed for
  an arbitrary amount of time?  As things stand, there is no
  guarantee on when a finaliser will run anyway, just that it
  will do so before the end of the computation.
  (2) Why is it a disaster to have an occasional change of scheduling
  policy (from co-operative multi-tasking to pre-emption)?
  Does it change the semantics of the concurrency model?
  Does it lead to a possible loss of termination?
  Does it disrupt some in-built assumptions in the runtime system?

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



Re: isNull{Fun,}Ptr

2002-09-11 Thread Malcolm Wallace

Manuel M T Chakravarty [EMAIL PROTECTED] writes:

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

No, the definition of null is
null [] = True
which is quite different from (==[]) because it has a less-constrained type.
null   :: [a] - Bool
(==[]) :: Eq a = [a] - Bool

Likewise,
isNothing   :: Maybe a - Bool
(==Nothing) :: Eq a = Maybe a - Bool

So there are good reasons for having separate predicates testing
the null/empty case at those polymorphic types, but no reason (except
consistency of naming) for a pseudo-polymorphic type like Ptr a.

However, consistency of naming is perhaps sufficient reason to add them
anyway.

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



Re: module Data.Bits

2002-09-10 Thread Malcolm Wallace

Manuel M T Chakravarty [EMAIL PROTECTED] writes:

 So, I would propose to
 change the FFI spec.  The main reason being that there is
 already plenty of code which relies on the current
 definition in GHC's Bits and there is no good reason to
 break that code.  Objections?

That's fine with me.

Another conflict between the FFI spec and the current
library implementation:  the spec says

The function bitSize returns 0 for types that don't have a
 fixed bitsize (e.g. Integer).

whereas the current ghc implementation defines bitSize of Integer
as a runtime error.

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



Re: Updates to FFI spec: hs_init() friends

2002-09-10 Thread Malcolm Wallace

Alastair Reid [EMAIL PROTECTED] writes:

  So, my proposal is to:
  [...]
 
 I think only GHC implements anything like this (correct me if wrong,
 Malcolm) and they haven't used it in the way John Meacham is
 interested in.

At the moment, nhc98 provides a routine

void haskellInit (int argc, char **argv)

which collects the command-line args intended for (1) the nhc98 runtime
system, and (2) the response to System.getArgs.  It does not strip any
arguments from the given set, on the basis that the calling C routine
may be interested in the same arguments that nhc98 is interested in.

Also, if the controlling C routine wants to alter the argument
set before Haskell sees it, that is perfectly catered for by this
interface.

Regards,
Malcolm

P.S. The nhc98 internal names will change shortly to match those defined by
 the FFI spec.
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: Proposed change to ForeignPtr

2002-09-10 Thread Malcolm Wallace

George Russell [EMAIL PROTECTED] writes:

 Unfortunately some sort of cascade is exactly what we want and need when
 the Haskell finaliser indicates that Haskell is no longer interested in
 some Foogle object, which means Foogle can run a GC which indicates
 Foogle is no longer interested in some Haskell object and so on . . .

Yes.  The key thing is just to delay the steps of the cascade so
that you are not trying to call Haskell/Foogle code whilst there is
no Haskell/Foogle heap available to run it.

  After that, it doesn't matter when the Foogle finaliser decides to run.

 But surely Foogle has no way of knowing when the Haskell GC is over?

When sequential control returns to the Foogle world, that is when
the Haskell GC is guaranteed to be complete.

 Suppose Haskell does
 
 [enter GC]
 ...
 [run finaliser 1]
 ...
 [run finaliser 2]
 ...
 [leave GC]
 
 Then you want Foogle to delay any Haskell calls consequent on finaliser
 1 until [leave GC], don't you?  How can it?

Because the Haskell calls don't happen until the Foogle GC invokes them.

Ok, you have a Haskell ForeignPtr which is really a Foogle object.
It becomes garbage.  At the next Haskell GC, its finaliser is run.
The finaliser is not Haskell code.  The finaliser is Foogle code.
This finaliser runs and a Haskell StablePtr contained within the
Foogle object becomes garbage.  Although the Haskell object is
regarded as a StablePtr in Haskell land, it is a Foogle ForeignPtr.
Hence, its finaliser does not run yet.  The Haskell GC finishes.
Computation proceeds.  At some later moment, Foogle exhausts its heap
and starts a GC.  The finaliser for the garbage object is now run.
This is not Foogle code, it is Haskell code.  In fact, it is the Haskell
routine freeStablePtr.  This is ok, because we have sufficient heap to
run the finaliser.  The StablePtr is released.  The Foogle GC finishes.
Computation proceeds.

 Is it really so difficult to create some queue of delayed functions
 which can be appended to from C and which nhc checks every time it does
 leave GC?

I did implement this, once.  The problem is that we don't know when to
run the delayed finaliser.  The moment Haskell GC finishes is *not*
a good time.  Some arbitrary reduction step is in mid-progress,
and running another process at this moment corrupts the context.
What you really need is some kind of scheduler that can decide when
it is safe to run an independent thread.

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



Re: Proposed change to ForeignPtr

2002-08-12 Thread Malcolm Wallace

Alastair Reid [EMAIL PROTECTED] writes:

 I'm not sure which position you're preferring here.  I lean a bit
 towards using the old names for the new functions (the ones with free
 functions) and finding new names for the old functions (the ones with
 closure arguments).

That would be my preference as well.  Keep the existing standard names,
but change their type signatures to reflect what Hugs and nhc98 can
actually implement.  Add new names with the old signatures for what
ghc can additionally implement via its concurrency model.

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



Re: Generating Function Prototypes

2002-07-04 Thread Malcolm Wallace

Alastair Reid [EMAIL PROTECTED] writes:

   foreign import foo :: Float - Char
 
   extern HsChar ffi_generated_foo(HsChar arg1);

Errm, shouldn't that be:

extern HsChar ffi_generated_foo(HsFloat arg1);
^^^
??  Or is there some other trick involved here?
Regards,
Malcolm

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



Re: Generating Function Prototypes

2002-07-03 Thread Malcolm Wallace

Alastair Reid [EMAIL PROTECTED] writes:

 Shouldn't we encourage people to use the compiler-independent
 mechanism instead (and exclusively)?

Yes, you are right.  I'm all in favour of standard mechanisms.

 That is, you put all your flags, includes, prototypes, etc. into a 
 header file, ... and then mention foo.h in all relevant foreign imports:
 
 foreign import foo.h x :: ...

Yup, this approach is the most platform-independent we managed to
come up with.  Now I just need to catch up with ghc and Hugs by
implementing it in nhc98...

 They still have to use compiler-specific mechanisms to specify
 #include search paths, linker options, etc.

Indeed, but these things are not only compiler-specific, they are
also often OS-specific, so it is right that they should not be in
the program source.

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



Re: Minor tweaks to ffi addendum

2002-06-03 Thread Malcolm Wallace

It's going to be really hard to implement ForeignPtr as specified.
The problem is that invocation of the cleanup function is triggered
by the garbage collector.
 
 Malcolm can comment on exactly how nhc98 handles the finalizers, but I
 believe that there's a list of pending finalizers maintained by the RTS
 which are run on re-entry to Haskell land.

That's the theory, yes.  In practice, I've never been able to get it
to work correctly, so the only finalisers that are guaranteed to run
in nhc98's runtime system are ones written in C rather than Haskell.
The underlying problem is when do you run a Haskell finaliser in a
non-concurrent system?  You can't run it when you discover it (in
the middle of a GC).  When the GC is called, the mutator is probably
right in the middle of some reduction step.  If I run the finalisers
immediately the GC finishes, then I'll probably corrupt the reduction
that was already in progress.  So the pending finalisers need to be
held off until a safe moment, but I haven't yet been able to find a
way to determine when that is.

In any case the most likely definition of a Haskell finaliser is just
a call into C-land anyway, so cut out the middle-man is what I say!

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



FFI Report comments

2001-08-21 Thread Malcolm Wallace

Manuel,

Here are my comments on the draft FFI Report itself.  It looks very
good to me, and there are just a few things to mention.

Lexical Structure
~
The lexical syntax adds 'foreign' as a keyword (reservedid).  I'm not
entirely convinced this is necessary.  Certainly in nhc98 we treat
'foreign' as just a specialid, and so like with other specialids you
can name a variable 'foreign' if you wish.  In other words, is there
any real reason to exclude the possibility of

module F (foreign, as) where

foreign :: X - Y
foreign ... = ...

foreign import ccall something as :: CInt - CInt - CInt

which nhc98 currently accepts, but ghc -fglasgow-exts rejects?


Standard C Calls

The productions

fdecl  - 'import' callconv [safety] entity var '::' ftype
entity -  ['static'] [fname] [''] ['['lib']'] [cid] 

suggest that the entity string must always be present, but could be
.  I was wondering if there is any real difficulty in permitting
an empty entity string to be omitted altogether?  The idea would be
to be able to write

foreign import ccall sin :: CFloat - CFloat

as at present rather than

foreign import ccall  sin :: CFloat - CFloat

It isn't a big deal, and it might be worth enforcing the literal string
quotes just for uniformity, but I thought I'd raise the issue anyway.


Int and Word

You want to drop the assertion that arithmetic is performed
modulo 2^n for sized Int and Word types, on the grounds that this
doesn't hold for Int.  But Int is not of fixed size, so how could it
require modulo arithmetic!  I happen to think the fact that Int is of
unspecified size 30 bits, with undefined behaviour on overflow, was
something of a mistake in Haskell.  Now that we have the opportunity
to define a sensible overflow behaviour for fixed size types, I think
we should take it.


module Ptr
~~
The statement alignPtr yields the next higher address that fulfills
the alignment constraint  slightly conflicts with the following one
that this operation is idempotent.  I think the first statement
really means to say alignPtr yields an address, the same or next
higher, that fulfills the alignment constraint.


module StablePtr

It seems a little strange that there is an instance of Storable
for StablePtr, yet we are forbidden to use the methods of Storable
to dereference a StablePtr.  In other words, I'm not quite clear on
exactly what is being forbidden.


C-Specific Marshalling
~~
HS_FLOAT_ROUND is called HS_FLOAT_ROUNDS in table 3.


Typos
~
There are a few typos and mis-spellings.  Would it be easiest for
someone like me to fix these directly via CVS, or is it better to
just give you a list privately?  I must admit that my experience of
using CVS for LaTeX documents was not a happy one, compared to how
useful it is for source code.

Regards,
Malcolm

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



RE: FFI Definition

2001-05-16 Thread Malcolm Wallace

Simon PJ writes:
 I thought we agreed to remove the specification of libraries from the
 FFI, and leave it to some compiler-dependent mechanism.  As Sven points
 out, there are going to be times when you really don't want a library at
 all, or in any case not one with the same name as the header file, and
 there will be cases where you want several libraries in some
 system-dependent order that shouldn't be placed in the source code.

I'm certain that at least one person (me) disagreed with removing any
library specs from the FFI.  I tend to the view that if the compiler
needs to know about something (and can't work it out for itself) the
information should be in the source code.  Putting it in a Makefile
or some other auxiliary structure (package configuration?) is not
really clean enough for me.  I don't want to have to write three
different Makefiles, one for each possible compiler I could use.
Please let's aim for portability.

Having said that, it is true that the FFI may not be the best place
for a specification of link libraries or whatever.  Maybe we should
agree on some pragmas for this sort of information?  In any case,
I'd like to have a compiler-independent standard, whether or not it
is part of the FFI.

Regards,
Malcolm

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