Fix conditionals for process-1.6.3.0
[lsp-test.git] / src / Language / Haskell / LSP / Test / Compat.hs
index 6b018cce5a526e7e111d459d3bd3b68d3d21ed09..a68f74158bb95baa85d5965556eecaf5689c1044 100644 (file)
@@ -5,14 +5,17 @@
 {-# OPTIONS_GHC -Wunused-imports #-}
 module Language.Haskell.LSP.Test.Compat where
 
-import Control.Concurrent.Chan
-import Control.Monad.IO.Class
-import Data.Conduit
 import Data.Maybe
+import System.IO
 
 #if MIN_VERSION_process(1,6,3)
+# if MIN_VERSION_process(1,6,4)
+import System.Process hiding (getPid, cleanupProcess)
+import qualified System.Process (getPid, cleanupProcess)
+# else
 import System.Process hiding (getPid)
 import qualified System.Process (getPid)
+# endif
 #else
 import System.Process
 import System.Process.Internals
@@ -39,7 +42,11 @@ getProcessID p = fromIntegral . fromJust <$> getProcessID' p
 #if MIN_VERSION_process(1,6,3)
   getProcessID' = System.Process.getPid
 #else
+#if MIN_VERSION_process(1,6,0)
   getProcessID' (ProcessHandle mh _ _) = do
+#else
+  getProcessID' (ProcessHandle mh _) = do
+#endif
     p_ <- readMVar mh
     case p_ of
 #ifdef mingw32_HOST_OS
@@ -52,12 +59,23 @@ getProcessID p = fromIntegral . fromJust <$> getProcessID' p
       _ -> return Nothing
 #endif
 
-#if MIN_VERSION_conduit(1,3,0)
-chanSource :: MonadIO m => Chan o -> ConduitT i o m b
+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
-chanSource :: MonadIO m => Chan o -> ConduitM i o m b
+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 ()) hClose mb_stdin
+    maybe (return ()) hClose mb_stdout
+    maybe (return ()) hClose mb_stderr
+
+    return ()
 #endif
-chanSource c = do
-  x <- liftIO $ readChan c
-  yield x
-  chanSource c