6b018cce5a526e7e111d459d3bd3b68d3d21ed09
[opengl.git] / src / Language / Haskell / LSP / Test / Compat.hs
1 {-# LANGUAGE CPP #-}
2 -- For some reason ghc warns about not using
3 -- Control.Monad.IO.Class but it's needed for
4 -- MonadIO
5 {-# OPTIONS_GHC -Wunused-imports #-}
6 module Language.Haskell.LSP.Test.Compat where
7
8 import Control.Concurrent.Chan
9 import Control.Monad.IO.Class
10 import Data.Conduit
11 import Data.Maybe
12
13 #if MIN_VERSION_process(1,6,3)
14 import System.Process hiding (getPid)
15 import qualified System.Process (getPid)
16 #else
17 import System.Process
18 import System.Process.Internals
19 import Control.Concurrent.MVar
20 #endif
21
22 #ifdef mingw32_HOST_OS
23 import qualified System.Win32.Process
24 #else
25 import qualified System.Posix.Process
26 #endif
27
28
29 getCurrentProcessID :: IO Int
30 #ifdef mingw32_HOST_OS
31 getCurrentProcessID = fromIntegral <$> System.Win32.Process.getCurrentProcessId
32 #else
33 getCurrentProcessID = fromIntegral <$> System.Posix.Process.getProcessID
34 #endif
35
36 getProcessID :: ProcessHandle -> IO Int
37 getProcessID p = fromIntegral . fromJust <$> getProcessID' p
38   where
39 #if MIN_VERSION_process(1,6,3)
40   getProcessID' = System.Process.getPid
41 #else
42   getProcessID' (ProcessHandle mh _ _) = do
43     p_ <- readMVar mh
44     case p_ of
45 #ifdef mingw32_HOST_OS
46       OpenHandle h -> do
47         pid <- System.Win32.Process.getProcessId h
48         return $ Just pid
49 #else
50       OpenHandle pid -> return $ Just pid
51 #endif
52       _ -> return Nothing
53 #endif
54
55 #if MIN_VERSION_conduit(1,3,0)
56 chanSource :: MonadIO m => Chan o -> ConduitT i o m b
57 #else
58 chanSource :: MonadIO m => Chan o -> ConduitM i o m b
59 #endif
60 chanSource c = do
61   x <- liftIO $ readChan c
62   yield x
63   chanSource c