Re: [Haskell-cafe] strange hangs with -threaded runtime (now with test case)

2012-07-18 Thread Joey Hess
Just following up to my problem, I was seeing lots of hangs in various
places in my program when it was built with the threaded runtime.

I eventually tracked every single hang back to calls to MissingH's
System.Cmd.Utils, including pipeFrom, pipeTo, pipeBoth, and pOpen.

I was at this point running my program in a loop 1000 times, and it'd
hang between 1 and 10 times on average, since these hangs seem to be
timing-related.

In all cases, when it hung, it had forked a child, and the child
was blocked in a futex() call. Each of these functions calls
forkProcess, and then does some very simple setup before it calls
executeFile -- but as far as I could see, the forked process never
ran a single thing before hanging.

The solution, for me, was to convert all my code to use System.Process
instead of System.Cmd.Utils. It seems that System.Process does all
its setup between fork and exec using C code, and so avoids this
problem.

I think it'd make sense to either add deprecation warnings to
System.Cmd.Utils, or to rewrite it to be a wrapper around
System.Process.

-- 
see shy jo


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


Re: [Haskell-cafe] strange hangs with -threaded runtime (now with test case)

2012-07-14 Thread Joey Hess
I've found a minimal test case that seems to demonstrate a bug in either
MissingH or ghc's threaded runtime. Or I'm doing something stupid in
fewer lines of code than usual. ;)

When built with the threaded runtime, after a short while it hangs in
hGetContents.

import System.Cmd
import System.IO
import System.Cmd.Utils
import System.Posix.Process
import Control.Monad

main :: IO ()
main = forever $ pipeRead [hello, world]

pipeRead :: [String] - IO ()
pipeRead params = do
-- removing this next line avoids the hang somehow
print $ pipeRead in  ++ show params
(p, h) - hPipeFrom echo params
print pipeRead getcontents
c - hGetContents h
print $ got:  ++ c
_ - getProcessStatus True False $ processID p
-- removing this last line avoids the hang somehow
print pipeRead out

joey@wren:~ghc --make -threaded test
[1 of 1] Compiling Main ( test.hs, test.o )
Linking test ...
joey@wren:~./test
pipeRead in [\hello\,\world\]
pipeRead getcontents
got: hello world\n
pipeRead out
pipeRead in [\hello\,\world\]
pipeRead getcontents
got: hello world\n
pipeRead out
snip 20 repeats
pipeRead in [\hello\,\world\]
pipeRead getcontents
hang

Ghc 7.4.2, Debian Linux

-- 
see shy jo

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


Re: [Haskell-cafe] strange hangs with -threaded runtime (now with test case)

2012-07-14 Thread Antoine Latter
Well, hPipeFrom does indeed call forkProcess internally. I don't fully
understand when it is and is not safe to use 'forkProcess' with the
threaded runtime of GHC.

Which version of GHC are you using?

Antoine

On Sat, Jul 14, 2012 at 1:24 PM, Joey Hess j...@kitenet.net wrote:
 I've found a minimal test case that seems to demonstrate a bug in either
 MissingH or ghc's threaded runtime. Or I'm doing something stupid in
 fewer lines of code than usual. ;)

 When built with the threaded runtime, after a short while it hangs in
 hGetContents.

 import System.Cmd
 import System.IO
 import System.Cmd.Utils
 import System.Posix.Process
 import Control.Monad

 main :: IO ()
 main = forever $ pipeRead [hello, world]

 pipeRead :: [String] - IO ()
 pipeRead params = do
 -- removing this next line avoids the hang somehow
 print $ pipeRead in  ++ show params
 (p, h) - hPipeFrom echo params
 print pipeRead getcontents
 c - hGetContents h
 print $ got:  ++ c
 _ - getProcessStatus True False $ processID p
 -- removing this last line avoids the hang somehow
 print pipeRead out

 joey@wren:~ghc --make -threaded test
 [1 of 1] Compiling Main ( test.hs, test.o )
 Linking test ...
 joey@wren:~./test
 pipeRead in [\hello\,\world\]
 pipeRead getcontents
 got: hello world\n
 pipeRead out
 pipeRead in [\hello\,\world\]
 pipeRead getcontents
 got: hello world\n
 pipeRead out
 snip 20 repeats
 pipeRead in [\hello\,\world\]
 pipeRead getcontents
 hang

 Ghc 7.4.2, Debian Linux

 --
 see shy jo

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

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


Re: [Haskell-cafe] strange hangs with -threaded runtime (now with test case)

2012-07-14 Thread Joey Hess
Antoine Latter wrote:
 Well, hPipeFrom does indeed call forkProcess internally. I don't fully
 understand when it is and is not safe to use 'forkProcess' with the
 threaded runtime of GHC.
 
 Which version of GHC are you using?

I've reproduced the problem with 7.4.2, and 7.4.1.

Just tried 6.12.1, which is interesting.. after around the same number of 
iterations
at which it hangs with the newer ghcs, it instead does this:

pipeRead in [\hello\,\world\]
pipeRead getcontents
test: internal error: MUT_ARR_PTRS_FROZEN object entered!
(GHC version 6.12.1 for i386_unknown_linux)
Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
got: 
pipeRead out

-- 
see shy jo

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


Re: [Haskell-cafe] strange hangs with -threaded runtime (now with test case)

2012-07-14 Thread Joey Hess
I've isolated the hang further to hPipeFrom's use of System.Log.Logger.
Commenting out calls to logging functions makes it reliably run ok. See
the LINE OF DEATH in the attached updated test case.

... And it turns out that System.Log.Logger uses a MVar to hold the
logger information. So I think this points to a MissingH bug, although I
don't yet understand it.

-- 
see shy jo
import System.Cmd
import System.IO
import System.Posix.Process
import Control.Monad
import System.Exit
import System.Cmd
import System.Log.Logger
import System.Posix.IO
import System.Posix.Process
import System.Posix.Signals
import System.Posix.Types
import System.IO
import System.IO.Error
import Control.Concurrent(forkIO)
import Control.Exception(finally)

main :: IO ()
main = forever $ 
	pipeRead [hello, world]

pipeRead :: [String] - IO ()
pipeRead params = do
	print $ pipeRead in  ++ show (params)
	(p, h) - hPipeFrom echo params
	print pipeRead getcontents
	c - hGetContents h
	print $ got:  ++ c
	_ - getProcessStatus True False $ processID p
	print pipeRead out

data PipeHandle =
PipeHandle { processID :: ProcessID,
 phCommand :: FilePath,
 phArgs :: [String],
 phCreator :: String -- ^ Function that created it
   }
deriving (Eq, Show)

logRunning :: String - FilePath - [String] - IO ()
logRunning func fp args = debugM (logbase ++ . ++ func) (showCmd fp args)

logbase :: String
logbase = System.Cmd.Utils

showCmd :: FilePath - [String] - String
showCmd fp args = fp ++   ++ show args

warnFail :: [Char] - FilePath - [String] - [Char] - IO t
warnFail funcname fp args msg =
let m = showCmd fp args ++ :  ++ msg
in do warningM (logbase ++ . ++ funcname) m
  fail m

hPipeFrom :: FilePath - [String] - IO (PipeHandle, Handle)
hPipeFrom fp args =
do pipepair - createPipe
   logRunning pipeFrom fp args --- LINE OF DEATH
   let childstuff = do dupTo (snd pipepair) stdOutput
   closeFd (fst pipepair)
   executeFile fp True args Nothing
   p - try (forkProcess childstuff)
   -- parent
   pid - case p of
  Right x - return x
  Left e - warnFail pipeFrom fp args $
Error in fork:  ++ show e
   closeFd (snd pipepair)
   h - fdToHandle (fst pipepair)
   return (PipeHandle pid fp args pipeFrom, h)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] strange hangs with -threaded runtime (now with test case)

2012-07-14 Thread Antoine Latter
If the MVar was set up prior to the fork, I can imagine things going crazy
trying to use it on the ther side of the fork - especially if their were
waiting readers or writers while the fork was executing.
On Jul 14, 2012 3:01 PM, Joey Hess j...@kitenet.net wrote:

 I've isolated the hang further to hPipeFrom's use of System.Log.Logger.
 Commenting out calls to logging functions makes it reliably run ok. See
 the LINE OF DEATH in the attached updated test case.

 ... And it turns out that System.Log.Logger uses a MVar to hold the
 logger information. So I think this points to a MissingH bug, although I
 don't yet understand it.

 --
 see shy jo

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