[commit: packages/process] less-cpp, master: Builds on non-Windows (46f0f27)
git at git.haskell.org
git at git.haskell.org
Tue Dec 15 13:34:28 UTC 2015
Repository : ssh://git@git.haskell.org/process
On branches: less-cpp,master
Link : http://ghc.haskell.org/trac/ghc/changeset/46f0f2778fbc3e62e9d36cd2aabfda2ef612e0cb/process
>---------------------------------------------------------------
commit 46f0f2778fbc3e62e9d36cd2aabfda2ef612e0cb
Author: Michael Snoyman <michael at fpcomplete.com>
Date: Mon Nov 2 16:30:17 2015 +0000
Builds on non-Windows
>---------------------------------------------------------------
46f0f2778fbc3e62e9d36cd2aabfda2ef612e0cb
System/Process/Common.hs | 4 ++++
System/Process/Internals.hs | 14 +++-----------
System/Process/Posix.hs | 45 +++++++++++++++++++++------------------------
System/Process/Windows.hs | 2 --
4 files changed, 28 insertions(+), 37 deletions(-)
diff --git a/System/Process/Common.hs b/System/Process/Common.hs
index fd9f38b..e7ce4d9 100644
--- a/System/Process/Common.hs
+++ b/System/Process/Common.hs
@@ -40,6 +40,8 @@ import GHC.IO.IOMode
#ifdef WINDOWS
import Data.Word (Word32)
import System.Win32.DebugApi (PHANDLE)
+#else
+import System.Posix.Types
#endif
#ifdef WINDOWS
@@ -47,6 +49,8 @@ import System.Win32.DebugApi (PHANDLE)
newtype CGid = CGid Word32
type GroupID = CGid
type UserID = CGid
+#else
+type PHANDLE = CPid
#endif
data CreateProcess = CreateProcess{
diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs
index 04eb1d2..32052eb 100644
--- a/System/Process/Internals.hs
+++ b/System/Process/Internals.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, RecordWildCards, BangPatterns #-}
+{-# LANGUAGE CPP #-}
{-# OPTIONS_HADDOCK not-home #-}
#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE Trustworthy #-}
@@ -43,15 +43,8 @@ module System.Process.Internals (
translate,
) where
-import Control.Concurrent
-import Control.Exception
-import Data.Bits
import Foreign.C
-import Foreign.Marshal
-import Foreign.Ptr
-import Foreign.Storable
import System.IO
-import System.IO.Unsafe
#ifdef __GLASGOW_HASKELL__
import GHC.IO.Handle.FD (fdToHandle)
@@ -65,9 +58,6 @@ import System.Process.Windows
import System.Process.Posix
#endif
-#include "HsProcessConfig.h"
-#include "processFlags.h"
-
-- ----------------------------------------------------------------------------
-- | This function is almost identical to
@@ -88,6 +78,7 @@ createProcess_
-> CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess_ = createProcess_Internal
+{-# INLINE createProcess_ #-}
-- ------------------------------------------------------------------------
-- Escaping commands for shells
@@ -146,6 +137,7 @@ use lpCommandLine alone, which CreateProcess supports.
translate :: String -> String
translate = translateInternal
+{-# INLINE translate #-}
-- ----------------------------------------------------------------------------
diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs
index 4619fd8..ec95743 100644
--- a/System/Process/Posix.hs
+++ b/System/Process/Posix.hs
@@ -1,5 +1,19 @@
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE CPP #-}
module System.Process.Posix
- (
+ ( mkProcessHandle
+ , translateInternal
+ , createProcess_Internal
+ , withCEnvironment
+ , closePHANDLE
+ , startDelegateControlC
+ , endDelegateControlC
+ , stopDelegateControlC
+ , isDefaultSignal
+ , ignoreSignal
+ , defaultSignal
+ , c_execvpe
+ , pPrPr_disableITimers
) where
import Control.Concurrent
@@ -11,43 +25,21 @@ import Foreign.Ptr
import Foreign.Storable
import System.IO.Unsafe
-#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
import Control.Monad
import Data.Char
import System.IO
import System.Posix.Process.Internals ( pPrPr_disableITimers, c_execvpe )
import System.Posix.Types
-#endif
-#ifdef __GLASGOW_HASKELL__
import System.Posix.Internals
import GHC.IO.Exception
-import GHC.IO.Encoding
-import qualified GHC.IO.FD as FD
-import GHC.IO.Device
-import GHC.IO.Handle.FD
-import GHC.IO.Handle.Internals
-import GHC.IO.Handle.Types hiding (ClosedHandle)
-import System.IO.Error
-import Data.Typeable
-# ifndef WINDOWS
import System.Posix.Signals as Sig
-# endif
-#endif
import System.Process.Common
-#if WINDOWS
-import System.Process.Windows
-#else
-import System.Process.Posix
-#endif
-
#include "HsProcessConfig.h"
#include "processFlags.h"
-type PHANDLE = CPid
-
mkProcessHandle :: PHANDLE -> Bool -> IO ProcessHandle
mkProcessHandle p mb_delegate_ctlc = do
m <- newMVar (OpenHandle p)
@@ -102,7 +94,12 @@ withCEnvironment envir act =
-- -----------------------------------------------------------------------------
-- POSIX runProcess with signal handling in the child
-createProcess_ fun CreateProcess{ cmdspec = cmdsp,
+createProcess_Internal
+ :: String
+ -> CreateProcess
+ -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
+createProcess_Internal fun
+ CreateProcess{ cmdspec = cmdsp,
cwd = mb_cwd,
env = mb_env,
std_in = mb_stdin,
diff --git a/System/Process/Windows.hs b/System/Process/Windows.hs
index 3afeeb3..bae63c6 100644
--- a/System/Process/Windows.hs
+++ b/System/Process/Windows.hs
@@ -75,7 +75,6 @@ foreign import WINDOWS_CCONV unsafe "CloseHandle"
:: PHANDLE
-> IO ()
-{-# INLINE createProcess_Internal #-}
createProcess_Internal
:: String -- ^ function name (for error messages)
-> CreateProcess
@@ -222,7 +221,6 @@ findCommandInterpreter = do
"findCommandInterpreter" Nothing Nothing)
Just cmd -> return cmd
-{-# INLINE translateInternal #-}
translateInternal :: String -> String
translateInternal xs = '"' : snd (foldr escape (True,"\"") xs)
where escape '"' (_, str) = (True, '\\' : '"' : str)
More information about the ghc-commits
mailing list