[Haskell-cafe] Re: On improving libraries: wanted list

2006-12-14 Thread Wagner Ferenc
[EMAIL PROTECTED] (Donald Bruce Stewart) writes:

 Can't we do something like this, on top of System.Process?
 Do we need unix* stuff anymore?

Hi,

on my computer your code (with  return ()-s inserted) works with at
most 135168=132*1024 bytes of input:

import System.Exit
import System.IO
import System.Process
import Control.Concurrent   (forkIO, newEmptyMVar, putMVar, takeMVar)

import qualified Control.Exception

popen :: FilePath - [String] - Maybe String - IO (String,String,ExitCode)
popen file args minput =
Control.Exception.handle (\e - return ([],show e,error (show e))) $ do

(inp,out,err,pid) - runInteractiveProcess file args Nothing Nothing

case minput of
Just input - hPutStr inp input  hClose inp -- importante!
Nothing- return ()

output - hGetContents out
errput - hGetContents err

forkIO (Control.Exception.evaluate (length output)  return ())
forkIO (Control.Exception.evaluate (length errput)  return ())

e - Control.Exception.catch (waitForProcess pid) (\_ - return 
ExitSuccess)

return (output,errput,e)

main = do (out,err,code) - popen /bin/cat [] (Just $ take 135168 input)
  putStrLn $ exit status:  ++ show code
  putStrLn $ out:  ++ show (length out) ++  characters
  putStrLn $ err= ++ err
where input = concat [show n ++ , | n-[1..]]

One more byte, and cat blocks on writing to its pipe.  No wonder,
nobody reads the other end, as our hPutStr to cat also blocks, as a
direct consequence.  Moving the case beyond the forkIO-s resolves
this.  Btw, why don't you close the other handles?  Btw2 runCommand in
http://happs.org/HAppS/src/HAppS/Util/Common.hs takes a similar
approach with MVar-s; I wonder if they are really needed.
-- 
Feri.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: On improving libraries: wanted list

2006-12-13 Thread John Goerzen
On Wed, Dec 13, 2006 at 04:19:58PM +1100, Donald Bruce Stewart wrote:
  In particular, you seem to be wanting my pipeBoth function.
  
  Note that your proposed String - IO String function type is insufficient
  because it does not provide a way to evaluate the return value of the
  function.
 
 this kind of functionality seems to be expected by new users (its one of
 the more common questions on #haskell). 
 
 Is System.Cmd.Utils in a position to be moved into base alongside
 System.Cmd and System.Process? It seems quite fundamental for getting
 work done quickly for script-like haskell programs.

It could go under System.Posix perhaps.  It relies quite heavily on
functionality provided by the unix package and the System.Posix.* tree.

Take a look at the source at:

http://software.complete.org/missingh/browser/src/System/Cmd/Utils.hs

Only one function, safeSystem, is portable to Windows.  Also, because
Hugs doesn't support fork(), most aren't supported on Hugs, either.

I would be happy to contribute this to somewhere on the System.Posix
tree, or wherever it's most appropriate.

These functions take advantage of hslogger
(http://software.complete.org/hslogger), so you can use one line in your
main command to turn on command invocation debugging (see what commands
are started and what they return).  That will have to be stripped out
before it goes into base, which I'm willing to do.  (Or hslogger could
go into base, but I'm guessing there'd be objection to that.)

Comments?

Reminder for those just joining the thread, the API we're discussing is
http://software.complete.org/missingh/static/doc/System-Cmd-Utils.html

-- John
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: On improving libraries: wanted list

2006-12-13 Thread Donn Cave
On Wed, 13 Dec 2006, John Goerzen wrote:
 [... re System.Cmd.Utils]
 
 It could go under System.Posix perhaps.  It relies quite heavily on
 functionality provided by the unix package and the System.Posix.* tree.
 
 Take a look at the source at:
 
 http://software.complete.org/missingh/browser/src/System/Cmd/Utils.hs
...
 Comments?
 
 Reminder for those just joining the thread, the API we're discussing is
 http://software.complete.org/missingh/static/doc/System-Cmd-Utils.html

Use of executeFile means you inherit its ideas about the argument list.
Unless it has been fixed, you can't specify argv[0].  That's fine until
you want to specify argv[0] for some reason, then it's a gratuitous
compromise to the C interface.  If there isn't any special issue that
makes execve(2) awkward to use from Haskell, maybe you could use it
and avoid executeFile.  Otherwise, since argument list is not per
man 2 execve, the difference needs to be documented for functions that
take an argument list.

I find the name PipeHandle confusing, since it turns out there's no
open file pointer or any such Handle-like property.

pipeLinesFrom seems gratuitous, I mean, can't people use `lines'?

pOpen3Raw 3 4 4 ... is bad just because you'll close 4 twice?  It seems
like something people are bound to do anyway, and not a huge problem to
support.  For pOpen3, I think I would just say dup unit 0 from this fd,
etc., rather than send stdin to this fd which makes sense only if this
fd really is a pipe.  And of course I'd change redirecting things to
pipes to redirecting standard file descriptors, since it will work fine
whatever kind of device the fd may actually be.  It's clearer to use 0
as the name for UNIX standard input (and 1, 2 for output and error), and
explain separately if you think that won't be obvious to the audience.

From what I have seen of these pipe functions in other contexts, the
hairy stuff happens when people get a process with pipes on both ends,
and try to feed data in one end and milk it out on the other.  That
invariably causes some kind of deadlock.  If the API doesn't directly
support it, that would probably be just as well.

Well, you asked for comments!

Donn Cave, [EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: On improving libraries: wanted list

2006-12-13 Thread Donald Bruce Stewart
jgoerzen:
 On Wed, Dec 13, 2006 at 04:19:58PM +1100, Donald Bruce Stewart wrote:
   In particular, you seem to be wanting my pipeBoth function.
   
   Note that your proposed String - IO String function type is insufficient
   because it does not provide a way to evaluate the return value of the
   function.
  
  this kind of functionality seems to be expected by new users (its one of
  the more common questions on #haskell). 
  
  Is System.Cmd.Utils in a position to be moved into base alongside
  System.Cmd and System.Process? It seems quite fundamental for getting
  work done quickly for script-like haskell programs.
 
 It could go under System.Posix perhaps.  It relies quite heavily on
 functionality provided by the unix package and the System.Posix.* tree.

Can't we do something like this, on top of System.Process?
Do we need unix* stuff anymore?

(modulo getting rid of the non-portable stuff)

module Lib.Process (popen) where

import System.Exit
import System.IO
import System.Process
import Control.Concurrent   (forkIO, newEmptyMVar, putMVar, takeMVar)

import qualified Control.Exception

popen :: FilePath - [String] - Maybe String - IO (String,String,ExitCode)
popen file args minput =
Control.Exception.handle (\e - return ([],show e,error (show e))) $ do

(inp,out,err,pid) - runInteractiveProcess file args Nothing Nothing

case minput of
Just input - hPutStr inp input  hClose inp -- importante!
Nothing- return ()

output - hGetContents out
errput - hGetContents err

forkIO (Control.Exception.evaluate (length output))
forkIO (Control.Exception.evaluate (length errput))

e - Control.Exception.catch (waitForProcess pid) (\_ - return 
ExitSuccess)

return (output,errput,e)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: On improving libraries: wanted list

2006-12-12 Thread John Goerzen
On Mon, 11 Dec 2006 11:52:48 +1100, Donald Bruce Stewart wrote:

 With the upcoming hackathon[1], and its timely focus on real world
 libraries, infrastructure and tools support, I've started a list of
 truly missing libraries, for particular problem domains.
 
 If you have a problem, for which you think there *should* be a Haskell
 library, please add it to this page:
 
 http://haskell.org/haskellwiki/Wanted_libraries

I have misplaced my haskellwiki login right now, but...

Under section 2:

  MissingH already provides a whole slew of forking/popen code; see
  http://software.complete.org/missingh/static/doc/System-Cmd-Utils.html

In particular, you seem to be wanting my pipeBoth function.

Note that your proposed String - IO String function type is insufficient
because it does not provide a way to evaluate the return value of the
function.

-- John

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe