Include ignoreSigPipe to avoid hangs
[lsp-test.git] / src / Language / Haskell / LSP / Test / Compat.hs
index 9467a322597cc75ed0d16c1f4010e9cb537b6cd0..87b7dc9ca9737cb5e2731722c110f6b0c8a76b41 100644 (file)
@@ -6,14 +6,30 @@
 module Language.Haskell.LSP.Test.Compat where
 
 import Data.Maybe
+import System.IO
 
 #if MIN_VERSION_process(1,6,3)
-import System.Process hiding (getPid)
+-- We have to hide cleanupProcess for process-1.6.3.0
+-- cause it is in the public api for 1.6.3.0 versions
+-- shipped with ghc >= 8.6 and < 8.6.4
+import System.Process hiding (getPid, cleanupProcess)
+# if MIN_VERSION_process(1,6,4)
+import qualified System.Process (getPid, cleanupProcess)
+# else
+import Foreign.C.Error
+import GHC.IO.Exception ( IOErrorType(..), IOException(..) )
+
 import qualified System.Process (getPid)
+import qualified Control.Exception as C
+# endif
 #else
+import Control.Concurrent.MVar
+import Foreign.C.Error
+import GHC.IO.Exception ( IOErrorType(..), IOException(..) )
 import System.Process
 import System.Process.Internals
-import Control.Concurrent.MVar
+
+import qualified Control.Exception as C
 #endif
 
 #ifdef mingw32_HOST_OS
@@ -52,3 +68,31 @@ getProcessID p = fromIntegral . fromJust <$> getProcessID' p
 #endif
       _ -> return Nothing
 #endif
+
+cleanupRunningProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO ()
+cleanupRunningProcess p@(_, _, _, ph) =
+  getProcessExitCode ph >>= maybe (cleanupProcess p) (const $ return ())
+
+cleanupProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO ()
+#if MIN_VERSION_process(1,6,4)
+cleanupProcess = System.Process.cleanupProcess
+#else
+cleanupProcess (mb_stdin, mb_stdout, mb_stderr, ph) = do
+
+    terminateProcess ph
+    -- Note, it's important that other threads that might be reading/writing
+    -- these handles also get killed off, since otherwise they might be holding
+    -- the handle lock and prevent us from closing, leading to deadlock.
+    maybe (return ()) (ignoreSigPipe . hClose) mb_stdin
+    maybe (return ()) hClose mb_stdout
+    maybe (return ()) hClose mb_stderr
+
+    return ()
+
+ignoreSigPipe :: IO () -> IO ()
+ignoreSigPipe = C.handle $ \e -> case e of
+                                   IOError { ioe_type  = ResourceVanished
+                                           , ioe_errno = Just ioe }
+                                     | Errno ioe == ePIPE -> return ()
+                                   _ -> C.throwIO e
+#endif