Skip to content
Snippets Groups Projects
Unverified Commit b4ea8144 authored by Oleg Grenrus's avatar Oleg Grenrus Committed by Mikhail Glushenkov
Browse files

Merge pull request #5730 from haskell/remove-unix-constraiant

Remove unix constraint from cabal.project

(cherry picked from commit 6797a9e5)
parent 547066b2
No related branches found
No related tags found
No related merge requests found
......@@ -38,7 +38,12 @@ makeAbsolute p | Path.isAbsolute p = return p
#if !MIN_VERSION_directory(1,2,7)
doesPathExist :: FilePath -> IO Bool
doesPathExist path = (||) <$> doesDirectoryExist path <*> doesFileExist path
doesPathExist path = do
-- not using Applicative, as this way we can do less IO
e <- doesDirectoryExist path
if e
then return True
else doesFileExist path
#endif
import Test.Cabal.Prelude
import Data.Maybe
import System.Directory
import Distribution.Compat.Directory
import Control.Monad.IO.Class
main = cabalTest $ do
withPackageDb $ do
withSandbox $ do
......
......@@ -254,9 +254,15 @@ initServer s0 = do
#else
pid <- withProcessHandle (serverProcessHandle s0) $ \ph ->
case ph of
#if MIN_VERSION_process(1,2,0)
OpenHandle x -> return (show x)
-- TODO: handle OpenExtHandle?
_ -> return (serverProcessId s0)
#else
OpenHandle x -> return (ph, show x)
-- TODO: handle OpenExtHandle?
_ -> return (ph, serverProcessId s0)
#endif
#endif
let s = s0 { serverProcessId = pid }
-- We will read/write a line at a time, including for
......
{-# LANGUAGE CPP #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ScopedTypeVariables #-}
......@@ -20,13 +21,25 @@ import Control.Monad
import qualified Control.Exception as E
import GHC.Conc (numCapabilities)
import Data.List
import Data.Monoid (mempty, (<>))
import Text.Printf
import qualified System.Clock as Clock
import System.IO
import System.FilePath
import System.Exit
import System.Process (callProcess, showCommandForUser)
import System.Process (
#if MIN_VERSION_process(1,2,0)
callProcess,
#else
proc, createProcess, waitForProcess, terminateProcess,
#endif
showCommandForUser)
#if !MIN_VERSION_base(4,12,0)
import Data.Monoid ((<>))
#endif
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (mempty)
#endif
-- | Record for arguments that can be passed to @cabal-tests@ executable.
data MainArgs = MainArgs {
......@@ -298,3 +311,20 @@ getTime = do
t <- Clock.getTime Clock.Monotonic
let ns = realToFrac $ Clock.toNanoSecs t
return $ ns / 10 ^ (9 :: Int)
-------------------------------------------------------------------------------
-- compat
-------------------------------------------------------------------------------
#if !MIN_VERSION_process(1,2,0)
callProcess :: FilePath -> [String] -> IO ()
callProcess cmd args = do
exit_code <- bracket (createProcess (proc cmd args)) cleanupProcess
$ \(_, _, _, ph) -> waitForProcess ph
case exit_code of
ExitSuccess -> return ()
ExitFailure r -> fail $ "processFailedException " ++ show (cmd, args, r)
where
cleanupProcess (_, _, _, ph) = terminateProcess ph
#endif
packages: Cabal/ cabal-testsuite/ cabal-install/ solver-benchmarks/ pretty-show-1.6.16/
constraints: unix >= 2.7.1.0
-- Uncomment to allow picking up extra local unpacked deps:
--optional-packages: */
......
......@@ -16,5 +16,17 @@ allow-newer: hackage-repo-tool:time
package Cabal
ghc-options: -Werror -fno-warn-orphans
constraints:
binary installed,
bytestring installed,
containers installed,
deepseq installed,
directory installed,
filepath installed,
pretty installed,
process installed,
time installed,
unix installed
package cabal-install
ghc-options: -Werror
packages: Cabal/ cabal-testsuite/ cabal-install/
packages: Cabal/ cabal-testsuite/
package Cabal
ghc-options: -Werror -fno-ignore-asserts
package cabal-testsuite
ghc-options: -Werror -fno-ignore-asserts
package cabal-install
ghc-options: -Werror -fno-ignore-asserts
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment