Maybe this is by design, but I just
thought I would point this behavior out and ask for comment.
test1 merely shows that runInteractiveCommand
reacts differently to perl warnings than perl errors. Okay, maybe the inconsistency
in that case is due to perl and not haskell.
test2 behaves the same on win and nix.
This is "pipe like" in that the ouptut of a command (which could
be the result of a shell call, but just as easily be the return of a haskell
function) gets fed into a shell command. In this case, if the shell command
is simply "tail" the behavior is consistent from win to nix.
test3 shows that the behavior stops
being consistent if ssh enters the picture. (piping to tail via ssh). again,
maybe this is due to ssh and not haskell.
however... note however that on windows
ghc -e 'mapM_ ( putStrLn . show ) [1..1000]
' | ssh `whoami`@localhost 'tail -n2'
works fine. so it's not *just*
ssh, but ssh in conjuction with runInteractiveCommand which seems to cause
problems
FWIW, using 10 lines instead of 1000
still hangs on windows.
Is there a way to code up shell pipelike
behavior in a more portable way?
curious what the cafe thinks...
thomas.
import Test.HUnit
import Misc ( (>>=^) )
import System.Process
import System.IO
import System.Exit
-- works on linux, error on windows
test1 = do
res1 <- test_shellrunStderrOk
runTestTT $ TestCase ( assertEqual
"test1" "made it" res1 )
where test_shellrunStderrOk
= do
runprocessStdErrAllowed' "" cmdPerlwarn
return "made it"
cmdPerldie
= " perl -e 'die \"error\"' "
cmdPerlwarn
= " perl -e 'warn \"blee\"' "
-- works on linux, windows
test2 = pipeTo "tail -n2"
-- works on linux, hangs on windows
test3 = pipeTo "ssh `whoami`@localhost
'tail -n2'"
pipeTo cmd = do
res2 <- test_shellrunPipeinLike
runTestTT $ TestCase ( assertEqual
( "pipe to, cmd: " ++ cmd) (show l) res2 )
where test_shellrunPipeinLike
= do
runprocessStdErrAllowed' (unlines $ map show [1..l]) ( cmd )
>>=^ filter (not . ( == '\n') )
l = 1000
runprocessStdErrAllowed' inp s = do
(ih,oh,eh,pid) <-
runInteractiveCommand s
so <- hGetContents
oh
se <- hGetContents
eh
hPutStrLn ih inp
hClose ih
ex <- waitForProcess
pid
case ex of
ExitFailure
e -> fail $ "shell command " ++ s ++ "\nFailed
with status: " ++ show e
_
| otherwise -> return so
---
This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.