Re: The Errno Story

2003-07-25 Thread Dean Herington
John Meacham wrote:

> I was thinking about this too but had a different idea, an alternate
> calling form which grabbed the result of errno and returned it to
> haskell land. that way the cost of geting errno is only paid for those
> foreign imports which care about it. like
>
> foreign import ccall_errno "unistd.h chdir" :: Ptr CChar -> IO (CInt,CInt)
>
> where the second CInt returned will be the value of errno after the call
> to chdir.

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?

> another solution is to do everything in C wrappers which return errno as
> well as the return value.
>
> another is some sort of blocking function which blocks context switching
> within the same OS thread temporarily..
>
> or your idea below. just thought I'd throw some alternate ideas into the
> mix. I am not a fan of having to stow errno for every ffi call..
> John
>
> On Thu, Jul 24, 2003 at 11:48:02PM +0200, Wolfgang Thaller wrote:
> > First, the "bug" part:
> >
> > None of the libraries that use errno are compatible with concurrency.
> > When a (lightweight) thread-switch occurs between the call to some
> > foreign function and the corresponding call to
> > Foreign.C.Error.getErrno, we have a problem:
> >
> > a) the RTS trashes the value of errno
> > b) another Haskell thread might call a function that sets errno
> > c) on most platforms, errno is thread-local state, with all the
> > consequences that has for the threaded RTS (bound threads required)
> >
> > Now, the "ffi" part:
> >
> > b) and c) could be solved by using bound threads, but that's probably
> > too inefficient for something that's used as frequently as errno.
> > Bound threads wouldn't solve a).
> >
> > I therefore propose that we make the RTS save & restore the value of
> > errno in the TSO, thus making errno "Haskell-Thread-Local-State", and
> > solving all of the above problems.
> > I also propose adding a note to the FFI spec (or the bound threads
> > document, I'm not sure which is the right place) that says that
> > implementations have to make sure that "Errno" is local to each
> > *Haskell* thread.

-- Dean

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


Re: new ForeignPtr without finalizers

2003-06-12 Thread Dean Herington
On Thu, 12 Jun 2003, Alastair Reid wrote:

> Manuel:
> > In other words, it seem much more likely that one would
> > partially apply `newForeignPtr' to a finaliser than to a
> > pointer that is to be finalised.  But this is a minor point.
> 
> Having written some more ffi code over the last couple of days, I agree that 
> this is much more natural so, even though it will break all the packages I 
> released in the last week, I now vote for swapping the argument order.
> 
> Since this breaks code anyway, we could adopt Dean's proposal to allow lists 
> of arguments to newFP and addFPFinalizers without making things worse.  I 
> don't think we should do this though since I believe they would always be 
> used with singleton or empty arguments and because the list-based versions 
> can be trivially added with a foldM if they prove useful.

Actually, I think I prefer Ashley's idea of separating the creation of a 
ForeignPtr from the addition of a FinalizerPtr.  So how about:

newForeignPtr  :: Ptr a -> IO (ForeignPtr a)
addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()

newForeignPtrWithFinalizer :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtrWithFinalizer f p = do p' <- newForeignPtr p
addForeignPtrFinalizer f p'
return p'

Dean

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


Re: new ForeignPtr without finalizers

2003-06-09 Thread Dean Herington
Alastair Reid wrote:

> I'm not convinced that merging them into a single function is desirable, but,
> if we wanted to, I think a better FPish solution is to use
>
>   Maybe (FinalizerPtr a)

As multiple finalizers are allowed, perhaps we should consider:

newForeignPtr :: [FinalizerPtr a] -> Ptr a -> IO (ForeignPtr a)
addForeignPtrFinalizers :: [FinalizerPtr a] -> ForeignPtr a -> IO ()

-- Dean

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


Re: New Bound Threads Proposal

2003-05-14 Thread Dean Herington
It still seems to me that too much "fuss" is being made/proposed over binding or not 
binding the main Haskell thread to the main OS thread.  I remain to be convinced that 
anything more complicated than "The main Haskell thread is bound to the main OS
thread.  Period." is justified.

Simon Peyton-Jones wrote:

> The principal downside is that naïve users might end up with
> unexpected thread switching for simple concurrent programs.

and Wolfgang Thaller replied:

> Yes. (However, for "simple concurrent programs" that cost should be negligible.)

Is it a real concern that a naive user will get significant unexpected overhead?

Besides, the example being discussed above,

| main = forkIO doLongComputation >> doAnotherLongComputation

is unrealistic.  Without coordination between the two long computations, if the main 
thread finishes its `doAnotherLongComputation` before the auxiliary thread finishes 
its `doLongComputation`, the latter will be summarily abandoned.


Simon Peyton-Jones wrote:

> So, we could arrange that runMain did the forkIO wrapping above, unless a command 
> line flag said "no, make the main thread bound" in which case we can inject a call 
> to runMain' instead, which refrains from doing a forkIO.

I think it's best to have the runtime system do as little implicit stuff as possible.  
In particular, it's unattractive for it to fork a Haskell thread (conditionally, no 
less).

> So the proposal boils down to:
> - yes, at the impl level the main thread is bound, as you suggest
> - but at the user level, the programmer can control whether or not
> his 'main' is bound
> - default is not-bound

If boundedness is not unconditional (as I prefer), I would suggest "bound" as the 
better default (favoring function over performance).

Dean

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


Re: MVar interface [was: Re: ForeignPtr-related signatures]

2002-11-18 Thread Dean Herington
I wrote:

> One might reasonably worry about the proliferation of MVar manipulation
> functions.  I think it's useful to realize that there are semantically only
> four primitives in the proposed extended interface: `newEmptyMVar`,
> `atomicModifyMVar`, `atomicTryModifyMVar`, and `addMVarFinalizer`.  All the
> other functions can be built simply out of these primitives.  In fact, I
> would recommend we include in the documentation for all the nonprimitive
> functions their definitions in terms of the primitives.

Oops, I misspoke.  There are eight primitives in my proposed set.  Here's the
full story, including the definitions I suggest for the documentation.

 -- Dean


-- primitives

newEmptyMVar :: IO (MVar v)

takeMVar :: MVar v -> IO v
putMVar  :: MVar v -> v -> IO ()
atomicModifyMVar :: MVar v -> (v -> (v,r)) -> IO r

tryTakeMVar  :: MVar v -> IO (Maybe v)
tryPutMVar   :: MVar v -> v -> IO Bool
atomicTryModifyMVar  :: MVar v -> (v -> (v,r)) -> IO (Maybe r)

addMVarFinalizer :: MVar v -> IO () -> IO ()

-- nonprimitives

newMVar  :: v -> IO (MVar v)
newMVar v=  do m <- newEmptyMVar
   putMVar m v
   return m

atomicModifyMVar_:: MVar v -> (v -> v) -> IO ()
atomicModifyMVar_ m f=  atomicModifyMVar m (\v -> (f v, ()))

readMVar :: MVar v -> IO v
readMVar m   =  atomicModifyMVar m (\v -> (v, v))

swapMVar :: MVar v -> v -> IO v
swapMVar m v'=  atomicModifyMVar m (\v -> (v', v))

atomicTryModifyMVar_ :: MVar v -> (v -> v) -> IO Bool
atomicTryModifyMVar_ m f =  do mr <- atomicTryModifyMVar m (\v -> (f v, ()))
   return (isJust mr)

tryReadMVar  :: MVar v -> IO (Maybe v)
tryReadMVar m=  atomicTryModifyMVar m (\v -> (v, v))

trySwapMVar  :: MVar v -> v -> IO (Maybe v)
trySwapMVar m v' =  atomicTryModifyMVar m (\v -> (v', v))

isEmptyMVar  :: MVar v -> IO Bool
isEmptyMVar m=  do mr <- atomicTryModifyMVar m (\v -> (v, ()))
   return (isNothing mr)

modifyMVar   :: MVar v -> (v -> IO (v,r)) -> IO r
modifyMVar m io  =  block $ do
 v  <- takeMVar m
 (v',r) <- Exception.catch (unblock (io v))
 (\e -> do putMVar m v; throw e)
 putMVar m v'
 return r

modifyMVar_  :: MVar v -> (v -> IO v) -> IO ()
modifyMVar_ m io =  block $ do
  v  <- takeMVar m
  v' <- Exception.catch (unblock (io v))
  (\e -> do putMVar m v; throw e)
  putMVar m v'

withMVar :: MVar v -> (v -> IO r) -> IO r
withMVar m io=  block $ do
  v <- takeMVar m
  r <- Exception.catch (unblock (io v))
 (\e -> do putMVar m v; throw e)
  putMVar m v
  return r


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



MVar interface [was: Re: ForeignPtr-related signatures]

2002-11-18 Thread Dean Herington
Simon Marlow wrote:

> > Simon Marlow wrote:
> > > [...] There was this, from Dean Herrington:
> > >
> > >   http://haskell.cs.yale.edu/pipermail/ffi/2002-October/000940.html
> > >
> > > I don't have any strong feelings (I rarely do, where names are
> > > concerned).
> >
> > I would be happy with his proposal. We can leave the IORef
> > stuff in IOExts
> > as it is and use the new signatures and functions in
> > Data.IORef. The only
> > annoying thing is the signature of Data.IORef.modifyIORef,
> > but we could
> > declare the old signature as a bug...  :-]
>
> Actually, looking at the proposal again, I don't think I like the
> changes to the MVar interface.  atomicModifyMVar seems strange, because
> modifyMVar is already atomic.  We have to be careful about trying to
> smooth over differences between IORef and MVar where those differences
> are real and important.

The current `modifyMVar`, though "exception safe", is not "atomic" in the
same way that the proposed `atomicModifyMVar` would be.  Unless I
misunderstand, during the execution of `modifyMVar`'s second argument, the
mvar is empty and could be filled by some other thread.  With
`atomicModifyMVar`, the contents of the mvar are changed atomically, based
on the given (pure) function; no other thread can intervene.

The difference described above is noticeable in the implementation of
`readMVar` and `swapMVar`.  As currently implemented, these functions are
not atomic as one might expect.  They would better be implemented in terms
of `atomicModifyMVar`.

Thinking about `readMVar` and `swapMVar` reminds me that `tryReadMVar` and
`trySwapMVar` are missing from the interface.

Thinking about the "try" and "atomic" variants suggests that we ought also
to add:

atomicTryModifyMVar :: MVar a -> (a -> (a, b)) -> IO (Maybe b)
atomicTryModifyMVar_ :: MVar a -> (a -> a) -> IO Bool

with semantics that I think are obvious.

> I don't mind changing modifyIORef to have a signature which is more
> similar to modifyMVar, and I think adding atomicModifyIORef_ is a good
> idea (although it needs a new primitive if we're to take advantage of
> its efficiency over atomicModifyIORef).  Summary:
>
>  - make modifyIORef's type match modifyMVar
>  - add modifyIORef_
>  - add atomicModifyIORef and atomicModifyIORef_

One might reasonably worry about the proliferation of MVar manipulation
functions.  I think it's useful to realize that there are semantically only
four primitives in the proposed extended interface: `newEmptyMVar`,
`atomicModifyMVar`, `atomicTryModifyMVar`, and `addMVarFinalizer`.  All the
other functions can be built simply out of these primitives.  In fact, I
would recommend we include in the documentation for all the nonprimitive
functions their definitions in terms of the primitives.

 -- Dean

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



Re: The Death of Finalizers

2002-10-22 Thread Dean Herington
George Russell wrote:

> Simon Peyton-Jones wrote:
> >
> > | In the meantime, I'm glad we have got a new function
> > |atomicModifyIORef
> > | which I for one will use, when it gets into GHC's regular release.
> >
> > Just before this gets out of the door... any chance of calling it
> >
> > modifyIORef
> >
> > and documenting that it's atomic
>
> My vote goes for
>
> modifyIORef :: IORef a -> (a -> (a,b)) -> IO b
> modifyIORef_ :: IORef a -> (a -> a) -> IO a
>
> modifyIORef_ ioRef fn = modifyIORef ioRef (\ a0 -> let a1 = fn a0 in (a1,a1))
>
> The names are similar to those of GHC's modifyMVar and modifyMVar_.
> I think there's some sense in providing modifyIORef_ as well as
> modifyIORef, as I think for some implementations it will be even faster,
> since it's unnecessary to create thunks for (fst (fn a0)) and
> (snd (fn a0)).  But you lot know a lot more about writing Haskell
> compilers than I do . . .
>
> Thus you can implement a counter returning integers 1,2,3,...
> via
>
>newCounter :: IO (IO Integer)
>newCounter = do
>   ioRef <- newIORef 0
>   return (modifyIORef_ ioRef (+1))
>
> I don't think it's necessary for the name to include "atomic".
> We are unlikely ever to want a non-atomic version of atomicModifyIORef,
> especially as such a thing would be quite dangerous, and you can roll
> your own from readIORef and writeIORef.

I like the idea of consistency (in naming, signatures, and semantics) between the
sets of functions manipulating IORefs and MVars.  Here's the scheme I would
prefer for the "modify" subset of these functions.  Existing functions are
labeled "(e)", proposed functions "(p)".  "(*)" indicates an existing function
with a different interface.

(e)   modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b
(e)   modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()
(p)   atomicModifyMVar :: MVar a -> (a -> (a, b)) -> IO b
(p)   atomicModifyMVar_ :: MVar a -> (a -> a) -> IO ()

(*)   modifyIORef :: IORef a -> (a -> IO (a, b)) -> IO b
(p)   modifyIORef_ :: IORef a -> (a -> IO a) -> IO ()
(p)   atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b
(p)   atomicModifyIORef_ :: IORef a -> (a -> a) -> IO ()

Notes:

* I prefer having the "*modify*_" functions return IO (), despite the fact that
it means the newCounter example George gives becomes more complicated.

* I strongly agree with Alastair that an atomic function should be so labeled.

* The nonatomic functions are all simply convenient combinations of other
functions.  As such, they could be dispensed with.  Even if they were dispensed
with, however, I would recommend against using their (without-"atomic") names for
the atomic functions, because I think the natural interfaces for the nonatomic
names are the ones given above.

* In fact, only atomicModifyMVar and atomicModifyIORef are primitive.

* The existence of modifyIORef with the "wrong" interface is an unfortunate
problem with this scheme.

 -- Dean

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