converted reads from stderr to use hGetLineUntilExitOrEOF
These are all unlikely to suffer from the inherited stderr fd problem, but who knows, it could happen.
This commit is contained in:
parent
613455e059
commit
ff0927bde9
3 changed files with 27 additions and 15 deletions
|
@ -225,16 +225,19 @@ youtubeDlFileNameHtmlOnly' url uo
|
||||||
liftIO $ withCreateProcess p waitproc
|
liftIO $ withCreateProcess p waitproc
|
||||||
|
|
||||||
waitproc Nothing (Just o) (Just e) pid = do
|
waitproc Nothing (Just o) (Just e) pid = do
|
||||||
output <- fmap fst $
|
errt <- async $ discardstderr pid e
|
||||||
hGetContentsStrict o
|
output <- hGetContentsStrict o
|
||||||
`concurrently`
|
|
||||||
hGetContentsStrict e
|
|
||||||
ok <- liftIO $ checkSuccessProcess pid
|
ok <- liftIO $ checkSuccessProcess pid
|
||||||
|
wait errt
|
||||||
return $ case (ok, lines output) of
|
return $ case (ok, lines output) of
|
||||||
(True, (f:_)) | not (null f) -> Right f
|
(True, (f:_)) | not (null f) -> Right f
|
||||||
_ -> nomedia
|
_ -> nomedia
|
||||||
waitproc _ _ _ _ = error "internal"
|
waitproc _ _ _ _ = error "internal"
|
||||||
|
|
||||||
|
discardstderr pid e = hGetLineUntilExitOrEOF pid e >>= \case
|
||||||
|
Nothing -> return ()
|
||||||
|
Just _ -> discardstderr pid e
|
||||||
|
|
||||||
nomedia = Left "no media in url"
|
nomedia = Left "no media in url"
|
||||||
|
|
||||||
youtubeDlOpts :: [CommandParam] -> Annex [CommandParam]
|
youtubeDlOpts :: [CommandParam] -> Annex [CommandParam]
|
||||||
|
|
14
Git/Fsck.hs
14
Git/Fsck.hs
|
@ -85,8 +85,8 @@ findBroken batchmode r = do
|
||||||
where
|
where
|
||||||
go _ (Just outh) (Just errh) pid = do
|
go _ (Just outh) (Just errh) pid = do
|
||||||
(o1, o2) <- concurrently
|
(o1, o2) <- concurrently
|
||||||
(parseFsckOutput maxobjs r outh)
|
(parseFsckOutput maxobjs r outh pid)
|
||||||
(parseFsckOutput maxobjs r errh)
|
(parseFsckOutput maxobjs r errh pid)
|
||||||
fsckok <- checkSuccessProcess pid
|
fsckok <- checkSuccessProcess pid
|
||||||
case mappend o1 o2 of
|
case mappend o1 o2 of
|
||||||
FsckOutput badobjs truncated
|
FsckOutput badobjs truncated
|
||||||
|
@ -121,9 +121,9 @@ knownMissing (FsckFoundMissing s _) = s
|
||||||
findMissing :: [Sha] -> Repo -> IO MissingObjects
|
findMissing :: [Sha] -> Repo -> IO MissingObjects
|
||||||
findMissing objs r = S.fromList <$> filterM (`isMissing` r) objs
|
findMissing objs r = S.fromList <$> filterM (`isMissing` r) objs
|
||||||
|
|
||||||
parseFsckOutput :: Int -> Repo -> Handle -> IO FsckOutput
|
parseFsckOutput :: Int -> Repo -> Handle -> ProcessHandle -> IO FsckOutput
|
||||||
parseFsckOutput maxobjs r h = do
|
parseFsckOutput maxobjs r h pid = do
|
||||||
ls <- lines <$> hGetContents h
|
ls <- getlines []
|
||||||
if null ls
|
if null ls
|
||||||
then return NoFsckOutput
|
then return NoFsckOutput
|
||||||
else if all ("duplicateEntries" `isInfixOf`) ls
|
else if all ("duplicateEntries" `isInfixOf`) ls
|
||||||
|
@ -133,6 +133,10 @@ parseFsckOutput maxobjs r h = do
|
||||||
let !truncated = length shas > maxobjs
|
let !truncated = length shas > maxobjs
|
||||||
missingobjs <- findMissing (take maxobjs shas) r
|
missingobjs <- findMissing (take maxobjs shas) r
|
||||||
return $ FsckOutput missingobjs truncated
|
return $ FsckOutput missingobjs truncated
|
||||||
|
where
|
||||||
|
getlines c = hGetLineUntilExitOrEOF pid h >>= \case
|
||||||
|
Nothing -> return (reverse c)
|
||||||
|
Just l -> getlines (l:c)
|
||||||
|
|
||||||
isMissing :: Sha -> Repo -> IO Bool
|
isMissing :: Sha -> Repo -> IO Bool
|
||||||
isMissing s r = either (const True) (const False) <$> tryIO dump
|
isMissing s r = either (const True) (const False) <$> tryIO dump
|
||||||
|
|
|
@ -113,23 +113,28 @@ sendFile f (CodeObserver observer) ps = do
|
||||||
-- Work around stupid stdout buffering behavior of python.
|
-- Work around stupid stdout buffering behavior of python.
|
||||||
-- See https://github.com/warner/magic-wormhole/issues/108
|
-- See https://github.com/warner/magic-wormhole/issues/108
|
||||||
environ <- addEntry "PYTHONUNBUFFERED" "1" <$> getEnvironment
|
environ <- addEntry "PYTHONUNBUFFERED" "1" <$> getEnvironment
|
||||||
runWormHoleProcess p { env = Just environ} $ \_hin hout herr -> do
|
runWormHoleProcess p { env = Just environ} $ \_hin hout herr ph -> do
|
||||||
(inout, inerr) <- findcode hout `concurrently` findcode herr
|
(inout, inerr) <- concurrently
|
||||||
|
(findcode ph hout)
|
||||||
|
(findcode ph herr)
|
||||||
return (inout || inerr)
|
return (inout || inerr)
|
||||||
where
|
where
|
||||||
p = wormHoleProcess (Param "send" : ps ++ [File f])
|
p = wormHoleProcess (Param "send" : ps ++ [File f])
|
||||||
findcode h = findcode' =<< words <$> hGetContents h
|
findcode ph h = findcode' =<< getwords ph h []
|
||||||
findcode' [] = return False
|
findcode' [] = return False
|
||||||
findcode' (w:ws) = case mkCode w of
|
findcode' (w:ws) = case mkCode w of
|
||||||
Just code -> do
|
Just code -> do
|
||||||
_ <- tryPutMVar observer code
|
_ <- tryPutMVar observer code
|
||||||
return True
|
return True
|
||||||
Nothing -> findcode' ws
|
Nothing -> findcode' ws
|
||||||
|
getwords ph h c = hGetLineUntilExitOrEOF ph h >>= \case
|
||||||
|
Nothing -> return $ concatMap words $ reverse c
|
||||||
|
Just l -> getwords ph h (l:c)
|
||||||
|
|
||||||
-- | Receives a file. Once the receive is under way, the Code will be
|
-- | Receives a file. Once the receive is under way, the Code will be
|
||||||
-- read from the CodeProducer, and fed to wormhole on stdin.
|
-- read from the CodeProducer, and fed to wormhole on stdin.
|
||||||
receiveFile :: FilePath -> CodeProducer -> WormHoleParams -> IO Bool
|
receiveFile :: FilePath -> CodeProducer -> WormHoleParams -> IO Bool
|
||||||
receiveFile f (CodeProducer producer) ps = runWormHoleProcess p $ \hin _hout _herr -> do
|
receiveFile f (CodeProducer producer) ps = runWormHoleProcess p $ \hin _hout _herr _ph -> do
|
||||||
Code c <- readMVar producer
|
Code c <- readMVar producer
|
||||||
hPutStrLn hin c
|
hPutStrLn hin c
|
||||||
hFlush hin
|
hFlush hin
|
||||||
|
@ -145,7 +150,7 @@ receiveFile f (CodeProducer producer) ps = runWormHoleProcess p $ \hin _hout _he
|
||||||
wormHoleProcess :: WormHoleParams -> CreateProcess
|
wormHoleProcess :: WormHoleParams -> CreateProcess
|
||||||
wormHoleProcess = proc "wormhole" . toCommand
|
wormHoleProcess = proc "wormhole" . toCommand
|
||||||
|
|
||||||
runWormHoleProcess :: CreateProcess -> (Handle -> Handle -> Handle -> IO Bool) -> IO Bool
|
runWormHoleProcess :: CreateProcess -> (Handle -> Handle -> Handle -> ProcessHandle -> IO Bool) -> IO Bool
|
||||||
runWormHoleProcess p consumer =
|
runWormHoleProcess p consumer =
|
||||||
withCreateProcess p' go `catchNonAsync` const (return False)
|
withCreateProcess p' go `catchNonAsync` const (return False)
|
||||||
where
|
where
|
||||||
|
@ -155,7 +160,7 @@ runWormHoleProcess p consumer =
|
||||||
, std_err = CreatePipe
|
, std_err = CreatePipe
|
||||||
}
|
}
|
||||||
go (Just hin) (Just hout) (Just herr) pid =
|
go (Just hin) (Just hout) (Just herr) pid =
|
||||||
consumer hin hout herr <&&> waitbool pid
|
consumer hin hout herr pid <&&> waitbool pid
|
||||||
go _ _ _ _ = error "internal"
|
go _ _ _ _ = error "internal"
|
||||||
waitbool pid = do
|
waitbool pid = do
|
||||||
r <- waitForProcess pid
|
r <- waitForProcess pid
|
||||||
|
|
Loading…
Reference in a new issue