Re: POpen, opening lots of processes

2004-01-12 Thread Ferenc Wagner
Tomasz Zielonka <[EMAIL PROTECTED]> writes:

> On Sun, Jan 11, 2004 at 10:22:09PM +0100, Ferenc Wagner wrote:
>
>>> It isn't suitable for exchanging bigger amounts of data
>>> between processes.
>> 
>> May I ask why?
>
> Well, if you were collecting big amounts of data (like
> dozens of megabytes) from the child process, you would
> probably rather want to either:
>   a) consume it incrementally 
>   b) store it in a more economic data structure
>
> Of course, both can be done in Haskell. I wonder if I
> could change my code to abstract it away...

I remember a discussion on the Haskell list about consuming
database requests.  The consensus was to use some pre-fold
like callbacks (proposed by Oleg?) as the most general
solution for such problems.  You may want to look into that.

Feri.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-11 Thread Ferenc Wagner
Tomasz Zielonka <[EMAIL PROTECTED]> writes:

> On Sat, Jan 10, 2004 at 04:50:28PM -0500, Mark Carroll wrote:
>
>>Your code looks great,
>
> Thanks :)
>
> It isn't suitable for exchanging bigger amounts of data between
> processes.

May I ask why?

Feri.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-10 Thread Tomasz Zielonka
On Sat, Jan 10, 2004 at 04:50:28PM -0500, Mark Carroll wrote:
> Tomasz,
> 
>Your code looks great,

Thanks :)

It was written in haste for a particular purpose and then tweaked a bit,
so I would be pleasantly surprised if it didn't contain any bugs
(besides the one mentioned in code).

It isn't suitable for exchanging bigger amounts of data between
processes.

> but where do you find the library documentation,
> like what the arguments for executeFile are all about? (I'd guessed the
> Maybe thing was an environment, but what's the Bool?)

That was about a month ago, so I don't remember exactly, but knowing me
I guess I must have looked into the source code. You can find some good,
but sometimes not haddockised, comments there.

Glynn Clements already cited some relevant code, but I think I was
rather looking at libraries/unix/System/Posix/Process.hsc which is the
one I used in my code, probably more recent.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-10 Thread Glynn Clements

Mark Carroll wrote:

>Your code looks great, but where do you find the library documentation,
> like what the arguments for executeFile are all about? (I'd guessed the
> Maybe thing was an environment, but what's the Bool?) I've been trying to
> do similar stuff, but have been stumbling in the dark rather.

Source code (hslibs/posix/PosixProcPrim.lhs):

executeFile :: FilePath -- Command
-> Bool -- Search PATH?
-> [String] -- Arguments
-> Maybe [(String, String)] -- Environment
-> IO ()
executeFile path search args Nothing = do
[snip]
if search 
   then throwErrnoIfMinus1_ "executeFile" (c_execvp s arr)
   else throwErrnoIfMinus1_ "executeFile" (c_execv s arr)

executeFile path search args (Just env) = do
[snip]
if search 
   then throwErrnoIfMinus1_ "executeFile" (c_execvpe s arg_arr env_arr)
   else throwErrnoIfMinus1_ "executeFile" (c_execve s arg_arr env_arr)

IOW:

search  env function

False   Nothing execv
TrueNothing execvp
False   Just _  execve
TrueJust _  execvpe [*]

[*] execvpe() isn't a standard library function; it is implemented in
hslibs/posix/cbits/execvpe.c using execve().

-- 
Glynn Clements <[EMAIL PROTECTED]>
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-10 Thread Mark Carroll
Tomasz,

   Your code looks great, but where do you find the library documentation,
like what the arguments for executeFile are all about? (I'd guessed the
Maybe thing was an environment, but what's the Bool?) I've been trying to
do similar stuff, but have been stumbling in the dark rather.

-- Mark
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: POpen, opening lots of processes

2004-01-09 Thread Simon Marlow
 
> > There is an outstanding proposal for a System.Process library:
> >
> > http://www.haskell.org/~simonmar/System.Process.html
> >
> > This is currently stalled because we need a non-blocking
> > implementation of getProcessStatus (which is in the
> > pipeline).  Something akin to Tomasz's launch could also
> > be included here.
> 
> How is it different from System.Posix.Process?  Supposed to
> be more portable?  Sounds good.

Yes, it is a portable process library.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-09 Thread Ferenc Wagner
"Simon Marlow" <[EMAIL PROTECTED]> writes:

>> Tomasz Zielonka <[EMAIL PROTECTED]> writes:
>> 
>>> I had a similar problem, and finally I created my own
>>> solution that doesn't leave zombies and doesn't block when
>>> the launched process writes too much to stderr.
>> 
>> Pretty neat, I've got an application idea for that code!
>> Couldn't it be include in the standard libraries?  Anyway,
>> thanks for posting it.
>
> There is an outstanding proposal for a System.Process library:
>
> http://www.haskell.org/~simonmar/System.Process.html
>
> This is currently stalled because we need a non-blocking
> implementation of getProcessStatus (which is in the
> pipeline).  Something akin to Tomasz's launch could also
> be included here.

How is it different from System.Posix.Process?  Supposed to
be more portable?  Sounds good.

Feri.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: POpen, opening lots of processes

2004-01-09 Thread Simon Marlow
 
> Tomasz Zielonka <[EMAIL PROTECTED]> writes:
> 
> > I had a similar problem, and finally I created my own
> > solution that doesn't leave zombies and doesn't block when
> > the launched process writes too much to stderr.
> 
> Pretty neat, I've got an application idea for that code!
> Couldn't it be include in the standard libraries?  Anyway,
> thanks for posting it.

There is an outstanding proposal for a System.Process library:

http://www.haskell.org/~simonmar/System.Process.html

This is currently stalled because we need a non-blocking implementation
of getProcessStatus (which is in the pipeline).  Something akin to
Tomasz's launch could also be included here.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-09 Thread Ferenc Wagner
Tomasz Zielonka <[EMAIL PROTECTED]> writes:

> I had a similar problem, and finally I created my own
> solution that doesn't leave zombies and doesn't block when
> the launched process writes too much to stderr.

Pretty neat, I've got an application idea for that code!
Couldn't it be include in the standard libraries?  Anyway,
thanks for posting it.

Feri.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-09 Thread Tomasz Zielonka
On Thu, Jan 08, 2004 at 09:33:29AM -0800, Hal Daume III wrote:
> Hi,
> 
> I'm using POpen to shell out to a command several hundreds or thousands of 
> times per call (none of them simultaneous, though, this is completely 
> serial).  After running my program for a while, I get:
> 
> Fail: resource exhausted
> Action: forkProcess
> Reason: Resource temporarily unavailable
> 
> which basically seems to be telling me that the program hasn't been 
> closing the old processes, even though they're definitely not in use 
> anymore.
> 
> Does anyone have any suggestions how to get around this?

I had a similar problem, and finally I created my own solution that
doesn't leave zombies and doesn't block when the launched process writes
too much to stderr.

I tested it in GHC 6.0. For 6.2 you'd have to change the use of
forkProcess.

Usage:

  launch :: String -> [String] -> String -> IO (ProcessStatus, String, String)

  (status, out, err) <- launch prog args progInput

Example:

*Shell> (status, out, err) <- launch "tr" ["a-z", "A-Z"] 
(unlines (replicate 1 "Haskell"))
*Shell> status
Exited ExitSuccess
*Shell> length out
8
*Shell> mapM_ putStrLn (take 10 (lines out))
HASKELL
HASKELL
HASKELL
HASKELL
HASKELL
HASKELL
HASKELL
HASKELL
HASKELL
HASKELL

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links

module Shell where

import System.Posix.Process
import System.Posix.IO
import Control.Concurrent
import IO

launch :: String -> [String] -> String -> IO (ProcessStatus, String, String)
launch prog args inputStr = do
(childIn, parentIn) <- createPipe
(parentOut, childOut) <- createPipe
(parentErr, childErr) <- createPipe

forkProcess >>= \pid -> case pid of
Nothing -> do -- child
closeFd parentIn
closeFd parentOut
closeFd parentErr
closeFd 0 -- FIXME: What if some of 0,1,2 are already closed?
closeFd 1
closeFd 2
childIn `dupTo` 0
childOut `dupTo` 1
childErr `dupTo` 2
closeFd childIn
closeFd childOut
closeFd childErr
executeFile prog True args Nothing
fail "launch: executeFile failed"

Just child -> do -- parent
closeFd childIn
closeFd childOut
closeFd childErr

input <- fdToHandle parentIn
output <- fdToHandle parentOut
err <- fdToHandle parentErr

outputCS <- hGetContents output
errCS <- hGetContents err

outputMV <- newEmptyMVar
errMV <- newEmptyMVar
inputMV <- newEmptyMVar

forkIO $ hPutStr input inputStr >> hClose input >> putMVar inputMV ()
forkIO $ foldr seq () outputCS `seq` hClose output >> putMVar outputMV ()
forkIO $ foldr seq () errCS `seq` hClose err >> putMVar errMV ()

takeMVar outputMV
takeMVar errMV
takeMVar inputMV

mStatus <- getProcessStatus True False child

case mStatus of
Nothing -> fail "launch: can't get child process status"
Just stat -> return (stat, outputCS, errCS)

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-08 Thread Glynn Clements

Hal Daume III wrote:

> > What does the output from "ps" indicate?
> 
> It lists all the processes as defunct:
> 
> 19981 pts/5Z  0:00 [suffixtree ]
> 19982 pts/5Z  0:00 [suffixtree ]
> 19983 pts/5Z  0:00 [suffixtree ]
> 19984 pts/5Z  0:00 [suffixtree ]
> 19985 pts/5Z  0:00 [suffixtree ]
> ...
> 
> > If you have any "live" processes (S or R state), it's probably because
> > the process' output hasn't been consumed, so the program hasn't
> > exit()ed yet. OTOH, if you have zombies (Z state), the program has
> > terminated but the parent (your program) hasn't called wait/waitpid
> > (the Haskell interface is getProcessStatus, getProcessGroupStatus or
> > getAnyProcessStatus).
> 
> I don't mind evaluating the contents returned strictly, but I can't figure 
> out how to force the process into a dead state...I don't see how any of 
> these three functions accomplishes that...what am I missing?

A "zombie" process (such as the above) is a process which has
terminated but which can't actually be removed from the system's
process table until the parent has retrieved its exit status.

That's where getProcessStatus etc (wait/waitpid at the C level) come
in; these functions block until a suitable[1] process has terminated,
and return its exit status. After which, the process can finally be
deleted (this is termed "reaping").

[1] getProcessStatus waits for a specific process,
getProcessGroupStatus waits for any process in a specific process
group, and getAnyProcessStatus waits for any child process.

So, you probably want something like:

do
(stdout, stderr, pid) <- popen cmd args (Just input)
-- consume stdout + stderr, e.g.:
writeFile "/dev/null" stdout
writeFile "/dev/null" stderr
getProcessStatus True False pid

You need to ensure that the output is consumed before calling
getProcessStatus, otherwise getProcessStatus will block indefinitely
(i.e. deadlock).

IMNSHO, this is one area where lazy I/O sucks even more than usual. 
It's bad enough having it tie up descriptors, let alone processes.

It probably works fine for "simple, stupid programs", which spawn a
handful of child processes (which they don't bother to reap) and then
terminate shortly thereafter (a process whose parent has terminated is
"adopted" by the init process, which can be relied upon to reap it
when it terminates).

-- 
Glynn Clements <[EMAIL PROTECTED]>
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-08 Thread Ferenc Wagner
Hal Daume III <[EMAIL PROTECTED]> writes:

> On Thu, 8 Jan 2004, Glynn Clements wrote:
>
>> What does the output from "ps" indicate?
>
> It lists all the processes as defunct:
>
> 19981 pts/5Z  0:00 [suffixtree ]
> 19982 pts/5Z  0:00 [suffixtree ]
> 19983 pts/5Z  0:00 [suffixtree ]
> 19984 pts/5Z  0:00 [suffixtree ]
> 19985 pts/5Z  0:00 [suffixtree ]
> ...
>
>> if you have zombies (Z state), the program has terminated
>> but the parent (your program) hasn't called wait/waitpid
>> (the Haskell interface is getProcessStatus,
>> getProcessGroupStatus or getAnyProcessStatus).
>
> I don't mind evaluating the contents returned strictly,
> but I can't figure out how to force the process into a
> dead state...

They are dead, just not acknowledged by their parent, so the
OS keeps their exit statuses around.

> I don't see how any of these three functions accomplishes
> that... what am I missing?

These functions read the exit status, and the OS will clean
up.  If you start them sequentially, then simply insert a
call to the appropriate function at a point where the
previous child is already finished.  Or spawn a thread which
sequence_s nonblocking getAnyProcessStatuses... :)  Never
tried myself.  man waitpid

Feri.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-08 Thread Hal Daume III
On Thu, 8 Jan 2004, Glynn Clements wrote:

> What does the output from "ps" indicate?

It lists all the processes as defunct:

19981 pts/5Z  0:00 [suffixtree ]
19982 pts/5Z  0:00 [suffixtree ]
19983 pts/5Z  0:00 [suffixtree ]
19984 pts/5Z  0:00 [suffixtree ]
19985 pts/5Z  0:00 [suffixtree ]
...

> If you have any "live" processes (S or R state), it's probably because
> the process' output hasn't been consumed, so the program hasn't
> exit()ed yet. OTOH, if you have zombies (Z state), the program has
> terminated but the parent (your program) hasn't called wait/waitpid
> (the Haskell interface is getProcessStatus, getProcessGroupStatus or
> getAnyProcessStatus).

I don't mind evaluating the contents returned strictly, but I can't figure 
out how to force the process into a dead state...I don't see how any of 
these three functions accomplishes that...what am I missing?

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: POpen, opening lots of processes

2004-01-08 Thread Glynn Clements

Hal Daume III wrote:

> I'm using POpen to shell out to a command several hundreds or thousands of 
> times per call (none of them simultaneous, though, this is completely 
> serial).  After running my program for a while, I get:
> 
> Fail: resource exhausted
> Action: forkProcess
> Reason: Resource temporarily unavailable
> 
> which basically seems to be telling me that the program hasn't been 
> closing the old processes, even though they're definitely not in use 
> anymore.
> 
> Does anyone have any suggestions how to get around this?

I note two facts regarding POpen.popen:

1. There is no corresponding pclose function.
2. It uses lazy I/O (hGetContents).

Also, I can't see wait/waitpid getting called anywhere (although there
might be other mechanims involved, e.g. SIGCHLD handlers; I haven't
looked that closely).

What does the output from "ps" indicate?

If you have any "live" processes (S or R state), it's probably because
the process' output hasn't been consumed, so the program hasn't
exit()ed yet. OTOH, if you have zombies (Z state), the program has
terminated but the parent (your program) hasn't called wait/waitpid
(the Haskell interface is getProcessStatus, getProcessGroupStatus or
getAnyProcessStatus).

-- 
Glynn Clements <[EMAIL PROTECTED]>
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users