[commit: packages/process] less-cpp, master: Remove (broken) support for non-GHC compilers (60dbdb9)

git at git.haskell.org git at git.haskell.org
Tue Dec 15 13:34:53 UTC 2015


Repository : ssh://git@git.haskell.org/process

On branches: less-cpp,master
Link       : http://ghc.haskell.org/trac/ghc/changeset/60dbdb959996e49b8a61b249c7e96971295f0cca/process

>---------------------------------------------------------------

commit 60dbdb959996e49b8a61b249c7e96971295f0cca
Author: Michael Snoyman <michael at fpcomplete.com>
Date:   Mon Nov 2 21:20:40 2015 +0000

    Remove (broken) support for non-GHC compilers


>---------------------------------------------------------------

60dbdb959996e49b8a61b249c7e96971295f0cca
 System/Process.hsc          | 15 ---------------
 System/Process/Internals.hs |  9 ---------
 System/Process/Posix.hs     |  4 ----
 process.cabal               | 24 ++++++++++--------------
 4 files changed, 10 insertions(+), 42 deletions(-)

diff --git a/System/Process.hsc b/System/Process.hsc
index 0673ca5..6b870fd 100644
--- a/System/Process.hsc
+++ b/System/Process.hsc
@@ -1,12 +1,10 @@
 {-# LANGUAGE CPP, ForeignFunctionInterface #-}
-#ifdef __GLASGOW_HASKELL__
 #if __GLASGOW_HASKELL__ >= 709
 {-# LANGUAGE Safe #-}
 #else
 {-# LANGUAGE Trustworthy #-}
 #endif
 {-# LANGUAGE InterruptibleFFI #-}
-#endif
 
 -----------------------------------------------------------------------------
 -- |
@@ -92,9 +90,7 @@ import System.IO.Error (mkIOError, ioeSetErrorString)
 import System.Posix.Types (CPid (..))
 #endif
 
-#ifdef __GLASGOW_HASKELL__
 import GHC.IO.Exception ( ioException, IOErrorType(..), IOException(..) )
-#endif
 
 -- ----------------------------------------------------------------------------
 -- createProcess
@@ -548,15 +544,11 @@ withForkWait async body = do
     restore (body wait) `C.onException` killThread tid
 
 ignoreSigPipe :: IO () -> IO ()
-#if defined(__GLASGOW_HASKELL__)
 ignoreSigPipe = C.handle $ \e -> case e of
                                    IOError { ioe_type  = ResourceVanished
                                            , ioe_errno = Just ioe }
                                      | Errno ioe == ePIPE -> return ()
                                    _ -> throwIO e
-#else
-ignoreSigPipe = id
-#endif
 
 -- ----------------------------------------------------------------------------
 -- showCommandForUser
@@ -860,13 +852,11 @@ will not work.
 On Unix systems, see 'waitForProcess' for the meaning of exit codes
 when the process died as the result of a signal.
 -}
-#ifdef __GLASGOW_HASKELL__
 system :: String -> IO ExitCode
 system "" = ioException (ioeSetErrorString (mkIOError InvalidArgument "system" Nothing Nothing) "null command")
 system str = do
   (_,_,_,p) <- createProcess_ "system" (shell str) { delegate_ctlc = True }
   waitForProcess p
-#endif  /* __GLASGOW_HASKELL__ */
 
 
 --TODO: in a later release {-# DEPRECATED rawSystem "Use 'callProcess' (or 'spawnProcess' and 'waitForProcess') instead" #-}
@@ -880,11 +870,6 @@ It will therefore behave more portably between operating systems than 'system'.
 The return codes and possible failures are the same as for 'system'.
 -}
 rawSystem :: String -> [String] -> IO ExitCode
-#ifdef __GLASGOW_HASKELL__
 rawSystem cmd args = do
   (_,_,_,p) <- createProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True }
   waitForProcess p
-#else
--- crude fallback implementation: could do much better than this under Unix
-rawSystem cmd args = system (showCommandForUser cmd args)
-#endif
diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs
index 69ecd2b..ef8ff8f 100644
--- a/System/Process/Internals.hs
+++ b/System/Process/Internals.hs
@@ -1,9 +1,7 @@
 {-# LANGUAGE CPP #-}
 {-# OPTIONS_HADDOCK not-home #-}
-#ifdef __GLASGOW_HASKELL__
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE InterruptibleFFI #-}
-#endif
 
 -----------------------------------------------------------------------------
 -- |
@@ -25,13 +23,11 @@ module System.Process.Internals (
     ProcessHandle(..), ProcessHandle__(..),
     PHANDLE, closePHANDLE, mkProcessHandle,
     modifyProcessHandle, withProcessHandle,
-#ifdef __GLASGOW_HASKELL__
     CreateProcess(..),
     CmdSpec(..), StdStream(..),
     createProcess_,
     runGenProcess_, --deprecated
     fdToHandle,
-#endif
     startDelegateControlC,
     endDelegateControlC,
     stopDelegateControlC,
@@ -48,9 +44,7 @@ module System.Process.Internals (
 import Foreign.C
 import System.IO
 
-#ifdef __GLASGOW_HASKELL__
 import GHC.IO.Handle.FD (fdToHandle)
-#endif
 
 import System.Process.Common
 
@@ -145,7 +139,6 @@ translate = translateInternal
 -- ----------------------------------------------------------------------------
 -- Deprecated / compat
 
-#ifdef __GLASGOW_HASKELL__
 {-# DEPRECATED runGenProcess_
       "Please do not use this anymore, use the ordinary 'System.Process.createProcess'. If you need the SIGINT handling, use delegate_ctlc = True (runGenProcess_ is now just an imperfectly emulated stub that probably duplicates or overrides your own signal handling)." #-}
 runGenProcess_
@@ -159,8 +152,6 @@ runGenProcess_ fun c (Just sig) (Just sig') | isDefaultSignal sig && sig == sig'
                          = createProcess_ fun c { delegate_ctlc = True }
 runGenProcess_ fun c _ _ = createProcess_ fun c
 
-#endif
-
 -- ---------------------------------------------------------------------------
 -- createPipe
 
diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs
index a68d942..6129197 100644
--- a/System/Process/Posix.hs
+++ b/System/Process/Posix.hs
@@ -93,8 +93,6 @@ withCEnvironment envir act =
   let env' = map (\(name, val) -> name ++ ('=':val)) envir
   in withMany withCString env' (\pEnv -> withArray0 nullPtr pEnv act)
 
-#ifdef __GLASGOW_HASKELL__
-
 -- -----------------------------------------------------------------------------
 -- POSIX runProcess with signal handling in the child
 
@@ -267,8 +265,6 @@ foreign import ccall unsafe "runInteractiveProcess"
         -> Ptr CString
         -> IO PHANDLE
 
-#endif /* __GLASGOW_HASKELL__ */
-
 ignoreSignal, defaultSignal :: CLong
 ignoreSignal  = CONST_SIG_IGN
 defaultSignal = CONST_SIG_DFL
diff --git a/process.cabal b/process.cabal
index ee79452..0b4ffd7 100644
--- a/process.cabal
+++ b/process.cabal
@@ -44,14 +44,16 @@ library
     exposed-modules:
         System.Cmd
         System.Process
-    if impl(ghc)
-        exposed-modules:
-            System.Process.Internals
-        other-modules: System.Process.Common
-        if os(windows)
-            other-modules: System.Process.Windows
-        else
-            other-modules: System.Process.Posix
+        System.Process.Internals
+    other-modules: System.Process.Common
+    if os(windows)
+        other-modules: System.Process.Windows
+        build-depends: Win32 >=2.2 && < 2.4
+        extra-libraries: kernel32
+        cpp-options: -DWINDOWS
+    else
+        other-modules: System.Process.Posix
+        build-depends: unix >= 2.5 && < 2.8
 
     c-sources:
         cbits/runProcess.c
@@ -68,12 +70,6 @@ library
                    directory >= 1.1 && < 1.3,
                    filepath  >= 1.2 && < 1.5,
                    deepseq   >= 1.1 && < 1.5
-    if os(windows)
-        build-depends: Win32 >=2.2 && < 2.4
-        extra-libraries: kernel32
-        cpp-options: -DWINDOWS
-    else
-        build-depends: unix >= 2.5 && < 2.8
 
 test-suite test
   default-language: Haskell2010



More information about the ghc-commits mailing list