[Haskell] Win32 process spawning, POpen and Hugs, revisited

Ross Paterson ross at soi.city.ac.uk
Tue Mar 16 18:14:01 EST 2004


On Tue, Mar 16, 2004 at 05:26:14PM +0000, Graham Klyne wrote:
> Further to my previous messages:
>   http://www.haskell.org//pipermail/haskell/2004-February/013522.html
>   http://www.haskell.org//pipermail/haskell/2004-February/013679.html
> 
> I've come back to my stripped-down test case, and recreated the C test 
> program SpawnEchoShiftLetters.c [1] in Haskell SpawnEchoShiftLetters.hs 
> [2].  I've also added some diagnostic code.  To recap:  the C code 
> demonstrates that that the Win32 API used by spawnProc.c [4] is working as 
> expected, so the problem appears to be in the Haskell interface to it.
> 
> My problem seems to be occurring about here:
> [[
> spawn cmd =
>   withCString cmd $ \ p_cmd ->
>    withObject 0 $ \ p_wIn  ->
>     withObject 0 $ \ p_rOut ->
>      withObject 0 $ \ p_rErr -> do
>        rc  <- spawnProc p_cmd p_wIn p_rOut p_rErr
>        when (rc /= 0) (ioError (userError ("runProc: unable to spawn " ++ 
> show cmd)))
>        wIn <- peek p_wIn
> (-1-}  trace ("wIn "++show wIn) $ return ()
>        {- : -}
> (-2-}  hIn <- openFd (fromIntegral wIn) False WriteMode False
> (-3-}  trace ("hIn "++show hIn) $ return ()
> ]]
> -- http://www.ninebynine.org/Software/HaskellUtils/Win32/POpen.hs
> 
> Specifically:
> + the trace at {-1-} displays the expected value (i.e. the same as a 
> similar trace in the C version of the code [1], namely the value 3),
> + the trace at {-3-} is not displayed, indicating...
> + failure of the openFd call at {-2-}, also indicated by a Hugs error 
> message, thus:
> [[
> SpawnEchoShiftLetters> runTest
> wIn 3
> 
> Program error: openFd: does not exist (file does not exist)
> 
> SpawnEchoShiftLetters>
> ]]
> 
> 
> Thus, it would appear that I'm misunderstanding how to use the openFd 
> function that is part of the Hugs-supplied library code, declared as a 
> primitive:
> [[
> -- Creating a handle from a file descriptor/socket.
> --
> primitive openFd    :: Int    -- file descriptor
>                     -> Bool   -- True => it's a socket.
>                     -> IOMode -- what mode to open the handle in.
>                     -> Bool   -- binary?
>                     -> IO Handle
> ]]
> -- 
> http://cvs.haskell.org/cgi-bin/cvsweb.cgi/hugs98/libraries/Hugs/IO.hs?rev=1.9&content-type=text/x-cvsweb-markup
> 
> Can anyone help me out here?

It could well be Hugs.  In this situation it calls fdopen(fd, "w+"),
but I think it should be fdopen(fd, "w").


More information about the Cvs-hugs mailing list