Add runSessionWithHandles
[lsp-test.git] / src / Language / Haskell / LSP / Test / Compat.hs
index a6151949a07d7486db2069662cba52c112038dd9..12031c34dff77d8f44f4245feeecbf23063844bd 100644 (file)
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE CPP, OverloadedStrings #-}
 -- For some reason ghc warns about not using
 -- Control.Monad.IO.Class but it's needed for
 -- MonadIO
@@ -7,6 +7,7 @@ module Language.Haskell.LSP.Test.Compat where
 
 import Data.Maybe
 import System.IO
+import Language.Haskell.LSP.Types
 
 #if MIN_VERSION_process(1,6,3)
 -- We have to hide cleanupProcess for process-1.6.3.0
@@ -69,10 +70,6 @@ getProcessID p = fromIntegral . fromJust <$> getProcessID' p
       _ -> 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 ()
 
@@ -102,7 +99,7 @@ cleanupProcess (mb_stdin, mb_stdout, mb_stderr, ph) = do
 
     return ()
   where ignoreSigPipe = ignoreIOError ResourceVanished ePIPE
-        ignorePermDenied = ignoreIOError PermissionDenied ePERM
+        ignorePermDenied = ignoreIOError PermissionDenied eACCES
     
 ignoreIOError :: IOErrorType -> Errno -> IO () -> IO ()
 ignoreIOError ioErrorType errno =
@@ -117,3 +114,7 @@ withCreateProcess c action =
             (\(m_in, m_out, m_err, ph) -> action m_in m_out m_err ph)
 
 #endif
+
+
+lspTestClientInfo :: ClientInfo
+lspTestClientInfo = ClientInfo "lsp-test" (Just CURRENT_PACKAGE_VERSION)