summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Propellor/Bootstrap.hs34
-rw-r--r--src/Propellor/Property/SiteSpecific/JoeySites.hs44
-rw-r--r--src/Propellor/Types/Dns.hs2
-rw-r--r--src/Propellor/Wrapper.hs1
-rw-r--r--src/System/Console/Concurrent.hs10
-rw-r--r--src/System/Console/Concurrent/Internal.hs187
-rw-r--r--src/System/Process/Concurrent.hs16
-rw-r--r--src/Utility/Process/Shim.hs3
8 files changed, 133 insertions, 164 deletions
diff --git a/src/Propellor/Bootstrap.hs b/src/Propellor/Bootstrap.hs
index d772d7c7..6aa5720c 100644
--- a/src/Propellor/Bootstrap.hs
+++ b/src/Propellor/Bootstrap.hs
@@ -81,13 +81,21 @@ buildCommand bs = intercalate " && " (go (getBuilder bs))
go Cabal =
[ "cabal configure"
, "cabal build -j1 propellor-config"
- , "ln -sf dist/build/propellor-config/propellor-config propellor"
+ , "ln -sf" `commandCabalBuildTo` "propellor"
]
go Stack =
[ "stack build :propellor-config"
, "ln -sf $(stack path --dist-dir)/build/propellor-config/propellor-config propellor"
]
+commandCabalBuildTo :: ShellCommand -> FilePath -> ShellCommand
+commandCabalBuildTo cmd dest = intercalate "; "
+ [ "if [ -d dist-newstyle ]"
+ , "then " ++ cmd ++ " $(cabal exec -- sh -c 'command -v propellor-config') " ++ shellEscape dest
+ , "else " ++ cmd ++ " dist/build/propellor-config/propellor-config " ++ shellEscape dest
+ , "fi"
+ ]
+
-- Check if all dependencies are installed; if not, run the depsCommand.
checkDepsCommand :: Bootstrapper -> Maybe System -> ShellCommand
checkDepsCommand bs sys = go (getBuilder bs)
@@ -257,32 +265,28 @@ buildPropellor mh = unlessM (actionMessage "Propellor build" build) $
-- dependencies and retries.
cabalBuild :: Maybe System -> IO Bool
cabalBuild msys = do
- make "dist/setup-config" ["propellor.cabal"] cabal_configure
+ make "configured" ["propellor.cabal"] cabal_configure
unlessM cabal_build $
unlessM (cabal_configure <&&> cabal_build) $
error "cabal build failed"
- -- For safety against eg power loss in the middle of the build,
- -- make a copy of the binary, and move it into place atomically.
- -- This ensures that the propellor symlink only ever points at
- -- a binary that is fully built. Also, avoid ever removing
- -- or breaking the symlink.
- --
- -- Need cp -pfRL to make build timestamp checking work.
- unlessM (boolSystem "cp" [Param "-pfRL", Param cabalbuiltbin, Param (tmpfor safetycopy)]) $
+ -- Make a copy of the binary, and move it into place atomically.
+ let safetycopy = "propellor.built"
+ let cpcmd = "cp -pfL" `commandCabalBuildTo` safetycopy
+ unlessM (boolSystem "sh" [Param "-c", Param cpcmd]) $
error "cp of binary failed"
- rename (tmpfor safetycopy) safetycopy
- symlinkPropellorBin safetycopy
+ rename safetycopy "propellor"
return True
where
- cabalbuiltbin = "dist/build/propellor-config/propellor-config"
- safetycopy = cabalbuiltbin ++ ".built"
cabal_configure = ifM (cabal ["configure"])
- ( return True
+ ( do
+ writeFile "configured" ""
+ return True
, case msys of
Nothing -> return False
Just sys ->
boolSystem "sh" [Param "-c", Param (depsCommand (Robustly Cabal) (Just sys))]
<&&> cabal ["configure"]
+ <&&> (writeFile "configured" "" >> return True)
)
-- The -j1 is to only run one job at a time -- in some situations,
-- eg in qemu, ghc does not run reliably in parallel.
diff --git a/src/Propellor/Property/SiteSpecific/JoeySites.hs b/src/Propellor/Property/SiteSpecific/JoeySites.hs
index 9b8a7e70..64bee99d 100644
--- a/src/Propellor/Property/SiteSpecific/JoeySites.hs
+++ b/src/Propellor/Property/SiteSpecific/JoeySites.hs
@@ -1238,33 +1238,46 @@ homeNAS = propertyList "home NAS" $ props
[ "# let users power control startech hub with uhubctl"
, "ATTR{idVendor}==\"" ++ hubvendor ++ "\", ATTR{idProduct}==\"005a\", MODE=\"0666\""
]
- & autoMountDrivePort "archive-10" (USBHubPort hubvendor hubloc 1)
+ & autoMountDrivePort "archive-10"
+ (USBHubPort hubvendor 1)
+ (USBDriveId wd "1230")
(Just "archive-oldest")
- & autoMountDrivePort "archive-11" (USBHubPort hubvendor hubloc 2)
+ & autoMountDrivePort "archive-11"
+ (USBHubPort hubvendor 2)
+ (USBDriveId wd "25ee")
(Just "archive-older")
- & autoMountDrivePort "archive-12" (USBHubPort hubvendor hubloc 3)
+ & autoMountDrivePort "archive-12"
+ (USBHubPort hubvendor 3)
+ (USBDriveId seagate "3322")
(Just "archive-old")
- & autoMountDrivePort "archive-13" (USBHubPort hubvendor hubloc 4)
+ & autoMountDrivePort "archive-13"
+ (USBHubPort hubvendor 4)
+ (USBDriveId wd "25a3")
(Just "archive")
& autoMountDrive "passport" Nothing
& Apt.installed ["git-annex", "borgbackup"]
where
hubvendor = "0409"
- hubloc = "4-1.6"
+ wd = "1058"
+ seagate = "0bc2"
data USBHubPort = USBHubPort
{ hubVendor :: String
- , hubLocation :: String
, hubPort :: Int
}
+data USBDriveId = USBDriveId
+ { driveVendorId :: String
+ , driveProductId :: String
+ }
+
-- Makes a USB drive with the given label automount, and unmount after idle
-- for a while.
--
-- The hub port is turned on and off automatically as needed, using
-- uhubctl.
-autoMountDrivePort :: Mount.Label -> USBHubPort -> Maybe FilePath -> Property DebianLike
-autoMountDrivePort label hp malias = propertyList desc $ props
+autoMountDrivePort :: Mount.Label -> USBHubPort -> USBDriveId -> Maybe FilePath -> Property DebianLike
+autoMountDrivePort label hp drive malias = propertyList desc $ props
& File.hasContent ("/etc/systemd/system/" ++ hub)
[ "[Unit]"
, "Description=Startech usb hub port " ++ show (hubPort hp)
@@ -1272,7 +1285,7 @@ autoMountDrivePort label hp malias = propertyList desc $ props
, "[Service]"
, "Type=oneshot"
, "RemainAfterExit=true"
- , "ExecStart=/usr/sbin/uhubctl -a on " ++ selecthubport
+ , "ExecStart=/bin/sh -c 'uhubctl -a on " ++ selecthubport ++ "'"
, "ExecStop=/bin/sh -c 'uhubctl -a off " ++ selecthubport
-- Powering off the port does not remove device
-- files, so ask udev to remove the devfile; it will
@@ -1300,7 +1313,18 @@ autoMountDrivePort label hp malias = propertyList desc $ props
selecthubport = unwords
[ "-p", show (hubPort hp)
, "-n", hubVendor hp
- , "-l", hubLocation hp
+ , "-l", concat
+ -- The hub's location id, eg "1-1.4", does not seem
+ -- as stable as uhubctl claims it will be,
+ -- and the vendor is not sufficient since I have 2
+ -- hubs from the same vendor. So search for the
+ -- drive lsusb to find that. This works even if the
+ -- port is powered off, as long as it's been on at
+ -- some point before.
+ [ "$(lsusb -tvv | perl -lne \"if (\\\\$h && m!/sys/bus/usb/devices/(.*?) !) {\\\\$v=\\\\$1}; if (m/Hub/) { \\\\$h=1 } else { \\\\$h=0 }; if (/"
+ , driveVendorId drive ++ ":" ++ driveProductId drive
+ ++ "/) { print \\\\$v; last}\")"
+ ]
]
-- Makes a USB drive with the given label automount, and unmount after idle
diff --git a/src/Propellor/Types/Dns.hs b/src/Propellor/Types/Dns.hs
index 30302a7d..e9902513 100644
--- a/src/Propellor/Types/Dns.hs
+++ b/src/Propellor/Types/Dns.hs
@@ -181,7 +181,7 @@ newtype NamedConfMap = NamedConfMap (M.Map Domain NamedConf)
instance IsInfo NamedConfMap where
propagateInfo _ = PropagateInfo False
--- | Adding a Master NamedConf stanza for a particulr domain always
+-- | Adding a Master NamedConf stanza for a particular domain always
-- overrides an existing Secondary stanza for that domain, while a
-- Secondary stanza is only added when there is no existing Master stanza.
instance Sem.Semigroup NamedConfMap where
diff --git a/src/Propellor/Wrapper.hs b/src/Propellor/Wrapper.hs
index f399b2cf..1bef651c 100644
--- a/src/Propellor/Wrapper.hs
+++ b/src/Propellor/Wrapper.hs
@@ -2,7 +2,6 @@
-- distribution.
--
-- Distributions should install this program into PATH.
--- (Cabal builds it as dist/build/propellor/propellor).
--
-- This is not the propellor main program (that's config.hs).
-- This bootstraps ~/.propellor/config.hs, builds it if
diff --git a/src/System/Console/Concurrent.hs b/src/System/Console/Concurrent.hs
index 12447637..8ab73c3d 100644
--- a/src/System/Console/Concurrent.hs
+++ b/src/System/Console/Concurrent.hs
@@ -7,29 +7,25 @@
-- > import Control.Concurrent.Async
-- > import System.Console.Concurrent
-- >
--- > main = withConcurrentOutput $
+-- > main = withConcurrentOutput $ do
-- > outputConcurrent "washed the car\n"
-- > `concurrently`
-- > outputConcurrent "walked the dog\n"
-- > `concurrently`
-- > createProcessConcurrent (proc "ls" [])
-{-# LANGUAGE CPP #-}
-
module System.Console.Concurrent (
-- * Concurrent output
withConcurrentOutput,
Outputable(..),
outputConcurrent,
errorConcurrent,
- ConcurrentProcessHandle,
-#ifndef mingw32_HOST_OS
createProcessConcurrent,
-#endif
- waitForProcessConcurrent,
createProcessForeground,
flushConcurrentOutput,
lockOutput,
+ ConcurrentProcessHandle,
+ waitForProcessConcurrent,
-- * Low level access to the output buffer
OutputBuffer,
StdHandle(..),
diff --git a/src/System/Console/Concurrent/Internal.hs b/src/System/Console/Concurrent/Internal.hs
index ffe6a9e8..de4cffaf 100644
--- a/src/System/Console/Concurrent/Internal.hs
+++ b/src/System/Console/Concurrent/Internal.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances, TupleSections #-}
-{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -O2 #-}
{- Building this module with -O0 causes streams not to fuse and too much
- memory to be used. -}
@@ -15,9 +14,6 @@
module System.Console.Concurrent.Internal where
import System.IO
-#ifndef mingw32_HOST_OS
-import System.Posix.IO
-#endif
import System.Directory
import System.Exit
import Control.Monad
@@ -32,6 +28,7 @@ import Data.Monoid
import qualified System.Process as P
import qualified Data.Text as T
import qualified Data.Text.IO as T
+import qualified Data.Text.Lazy as L
import Control.Applicative
import Prelude
@@ -43,8 +40,6 @@ data OutputHandle = OutputHandle
, outputBuffer :: TMVar OutputBuffer
, errorBuffer :: TMVar OutputBuffer
, outputThreads :: TMVar Integer
- , processWaiters :: TMVar [Async ()]
- , waitForProcessLock :: TMVar ()
}
data Lock = Locked
@@ -57,8 +52,6 @@ globalOutputHandle = unsafePerformIO $ OutputHandle
<*> newTMVarIO (OutputBuffer [])
<*> newTMVarIO (OutputBuffer [])
<*> newTMVarIO 0
- <*> newTMVarIO []
- <*> newEmptyTMVarIO
-- | Holds a lock while performing an action. This allows the action to
-- perform its own output to the console, without using functions from this
@@ -109,7 +102,8 @@ dropOutputLock :: IO ()
dropOutputLock = withLock $ void . takeTMVar
-- | Use this around any actions that use `outputConcurrent`
--- or `createProcessConcurrent`
+-- or `createProcessConcurrent`, unless
+-- `System.Console.Regions.displayConsoleRegions` is being used.
--
-- This is necessary to ensure that buffered concurrent output actually
-- gets displayed before the program exits.
@@ -140,20 +134,30 @@ class Outputable v where
instance Outputable T.Text where
toOutput = id
+-- | Note that using a lazy Text as an Outputable value
+-- will buffer it all in memory.
+instance Outputable L.Text where
+ toOutput = toOutput . L.toStrict
+
instance Outputable String where
toOutput = toOutput . T.pack
-- | Displays a value to stdout.
--
--- No newline is appended to the value, so if you want a newline, be sure
--- to include it yourself.
---
-- Uses locking to ensure that the whole output occurs atomically
-- even when other threads are concurrently generating output.
--
+-- No newline is appended to the value, so if you want a newline, be sure
+-- to include it yourself.
+--
-- When something else is writing to the console at the same time, this does
-- not block. It buffers the value, so it will be displayed once the other
-- writer is done.
+--
+-- When outputConcurrent is used within a call to
+-- `System.Console.Regions.displayConsoleRegions`, the output is displayed
+-- above the currently open console regions. Only lines ending in a newline
+-- are displayed in this case (it uses `waitCompleteLines`).
outputConcurrent :: Outputable v => v -> IO ()
outputConcurrent = outputConcurrent' StdOut
@@ -179,69 +183,13 @@ outputConcurrent' stdh v = bracket setup cleanup go
h = toHandle stdh
bv = bufferFor stdh
-newtype ConcurrentProcessHandle = ConcurrentProcessHandle P.ProcessHandle
-
-toConcurrentProcessHandle :: (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle) -> (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
-toConcurrentProcessHandle (i, o, e, h) = (i, o, e, ConcurrentProcessHandle h)
+-- | This alias is provided to avoid breaking backwards compatibility.
+type ConcurrentProcessHandle = P.ProcessHandle
--- | Use this to wait for processes started with
--- `createProcessConcurrent` and `createProcessForeground`, and get their
--- exit status.
---
--- Note that such processes are actually automatically waited for
--- internally, so not calling this explicitly will not result
--- in zombie processes. This behavior differs from `P.waitForProcess`
+-- | Same as `P.waitForProcess`; provided to avoid breaking backwards
+-- compatibility.
waitForProcessConcurrent :: ConcurrentProcessHandle -> IO ExitCode
-waitForProcessConcurrent (ConcurrentProcessHandle h) =
- bracket lock unlock checkexit
- where
- lck = waitForProcessLock globalOutputHandle
- lock = atomically $ tryPutTMVar lck ()
- unlock True = atomically $ takeTMVar lck
- unlock False = return ()
- checkexit locked = maybe (waitsome locked) return
- =<< P.getProcessExitCode h
- waitsome True = do
- let v = processWaiters globalOutputHandle
- l <- atomically $ readTMVar v
- if null l
- -- Avoid waitAny [] which blocks forever
- then P.waitForProcess h
- else do
- -- Wait for any of the running
- -- processes to exit. It may or may not
- -- be the one corresponding to the
- -- ProcessHandle. If it is,
- -- getProcessExitCode will succeed.
- void $ tryIO $ waitAny l
- checkexit True
- waitsome False = do
- -- Another thread took the lck first. Wait for that thread to
- -- wait for one of the running processes to exit.
- atomically $ do
- putTMVar lck ()
- takeTMVar lck
- checkexit False
-
--- Registers an action that waits for a process to exit,
--- adding it to the processWaiters list, and removing it once the action
--- completes.
-asyncProcessWaiter :: IO () -> IO ()
-asyncProcessWaiter waitaction = do
- regdone <- newEmptyTMVarIO
- waiter <- async $ do
- self <- atomically (takeTMVar regdone)
- waitaction `finally` unregister self
- register waiter regdone
- where
- v = processWaiters globalOutputHandle
- register waiter regdone = atomically $ do
- l <- takeTMVar v
- putTMVar v (waiter:l)
- putTMVar regdone waiter
- unregister waiter = atomically $ do
- l <- takeTMVar v
- putTMVar v (filter (/= waiter) l)
+waitForProcessConcurrent = P.waitForProcess
-- | Wrapper around `System.Process.createProcess` that prevents
-- multiple processes that are running concurrently from writing
@@ -260,9 +208,10 @@ asyncProcessWaiter waitaction = do
-- redirected to a buffer. The buffered output will be displayed as soon
-- as the output lock becomes free.
--
--- Currently only available on Unix systems, not Windows.
-#ifndef mingw32_HOST_OS
-createProcessConcurrent :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
+-- Note that the the process is waited for by a background thread,
+-- so unlike createProcess, neglecting to call waitForProcess will not
+-- result in zombie processess.
+createProcessConcurrent :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle)
createProcessConcurrent p
| willOutput (P.std_out p) || willOutput (P.std_err p) =
ifM tryTakeOutputLock
@@ -271,56 +220,65 @@ createProcessConcurrent p
)
| otherwise = do
r@(_, _, _, h) <- P.createProcess p
- asyncProcessWaiter $
- void $ tryIO $ P.waitForProcess h
- return (toConcurrentProcessHandle r)
-#endif
+ _ <- async $ void $ tryIO $ P.waitForProcess h
+ return r
-- | Wrapper around `System.Process.createProcess` that makes sure a process
-- is run in the foreground, with direct access to stdout and stderr.
-- Useful when eg, running an interactive process.
-createProcessForeground :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
+--
+-- Note that the the process is waited for by a background thread,
+-- so unlike createProcess, neglecting to call waitForProcess will not
+-- result in zombie processess.
+createProcessForeground :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle)
createProcessForeground p = do
takeOutputLock
fgProcess p
-fgProcess :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
+fgProcess :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle)
fgProcess p = do
r@(_, _, _, h) <- P.createProcess p
`onException` dropOutputLock
registerOutputThread
-- Wait for the process to exit and drop the lock.
- asyncProcessWaiter $ do
+ _ <- async $ do
void $ tryIO $ P.waitForProcess h
unregisterOutputThread
dropOutputLock
- return (toConcurrentProcessHandle r)
+ return r
-#ifndef mingw32_HOST_OS
-bgProcess :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ConcurrentProcessHandle)
+bgProcess :: P.CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle)
bgProcess p = do
- (toouth, fromouth) <- pipe
- (toerrh, fromerrh) <- pipe
let p' = p
- { P.std_out = rediroutput (P.std_out p) toouth
- , P.std_err = rediroutput (P.std_err p) toerrh
+ { P.std_out = rediroutput (P.std_out p)
+ , P.std_err = rediroutput (P.std_err p)
}
registerOutputThread
- r@(_, _, _, h) <- P.createProcess p'
+ (stdin_h, stdout_h, stderr_h, h) <- P.createProcess p'
`onException` unregisterOutputThread
- asyncProcessWaiter $ void $ tryIO $ P.waitForProcess h
- outbuf <- setupOutputBuffer StdOut toouth (P.std_out p) fromouth
- errbuf <- setupOutputBuffer StdErr toerrh (P.std_err p) fromerrh
+ let r =
+ ( stdin_h
+ , mungeret (P.std_out p) stdout_h
+ , mungeret (P.std_err p) stderr_h
+ , h
+ )
+ -- Wait for the process for symmetry with fgProcess,
+ -- which does the same.
+ _ <- async $ void $ tryIO $ P.waitForProcess h
+ outbuf <- setupOutputBuffer StdOut (mungebuf (P.std_out p) stdout_h)
+ errbuf <- setupOutputBuffer StdErr (mungebuf (P.std_err p) stderr_h)
void $ async $ bufferWriter [outbuf, errbuf]
- return (toConcurrentProcessHandle r)
+ return r
where
- pipe = do
- (from, to) <- createPipe
- (,) <$> fdToHandle to <*> fdToHandle from
- rediroutput ss h
- | willOutput ss = P.UseHandle h
+ rediroutput ss
+ | willOutput ss = P.CreatePipe
| otherwise = ss
-#endif
+ mungebuf ss mh
+ | willOutput ss = mh
+ | otherwise = Nothing
+ mungeret ss mh
+ | willOutput ss = Nothing
+ | otherwise = mh
willOutput :: P.StdStream -> Bool
willOutput P.Inherit = True
@@ -353,32 +311,31 @@ data AtEnd = AtEnd
data BufSig = BufSig
-setupOutputBuffer :: StdHandle -> Handle -> P.StdStream -> Handle -> IO (StdHandle, MVar OutputBuffer, TMVar BufSig, TMVar AtEnd)
-setupOutputBuffer h toh ss fromh = do
- hClose toh
+setupOutputBuffer :: StdHandle -> Maybe Handle -> IO (StdHandle, MVar OutputBuffer, TMVar BufSig, TMVar AtEnd)
+setupOutputBuffer h fromh = do
buf <- newMVar (OutputBuffer [])
bufsig <- atomically newEmptyTMVar
bufend <- atomically newEmptyTMVar
- void $ async $ outputDrainer ss fromh buf bufsig bufend
+ void $ async $ outputDrainer fromh buf bufsig bufend
return (h, buf, bufsig, bufend)
-- Drain output from the handle, and buffer it.
-outputDrainer :: P.StdStream -> Handle -> MVar OutputBuffer -> TMVar BufSig -> TMVar AtEnd -> IO ()
-outputDrainer ss fromh buf bufsig bufend
- | willOutput ss = go
- | otherwise = atend
+outputDrainer :: Maybe Handle -> MVar OutputBuffer -> TMVar BufSig -> TMVar AtEnd -> IO ()
+outputDrainer mfromh buf bufsig bufend = case mfromh of
+ Nothing -> atend
+ Just fromh -> go fromh
where
- go = do
+ go fromh = do
t <- T.hGetChunk fromh
if T.null t
- then atend
+ then do
+ atend
+ hClose fromh
else do
modifyMVar_ buf $ addOutputBuffer (Output t)
changed
- go
- atend = do
- atomically $ putTMVar bufend AtEnd
- hClose fromh
+ go fromh
+ atend = atomically $ putTMVar bufend AtEnd
changed = atomically $ do
void $ tryTakeTMVar bufsig
putTMVar bufsig BufSig
diff --git a/src/System/Process/Concurrent.hs b/src/System/Process/Concurrent.hs
index 0e00e4fd..346ce2e0 100644
--- a/src/System/Process/Concurrent.hs
+++ b/src/System/Process/Concurrent.hs
@@ -9,26 +9,14 @@
module System.Process.Concurrent where
import System.Console.Concurrent
-import System.Console.Concurrent.Internal (ConcurrentProcessHandle(..))
import System.Process hiding (createProcess, waitForProcess)
import System.IO
import System.Exit
-- | Calls `createProcessConcurrent`
---
--- You should use the waitForProcess in this module on the resulting
--- ProcessHandle. Using System.Process.waitForProcess instead can have
--- mildly unexpected results.
createProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-createProcess p = do
- (i, o, e, ConcurrentProcessHandle h) <- createProcessConcurrent p
- return (i, o, e, h)
+createProcess = createProcessConcurrent
-- | Calls `waitForProcessConcurrent`
---
--- You should only use this on a ProcessHandle obtained by calling
--- createProcess from this module. Using this with a ProcessHandle
--- obtained from System.Process.createProcess etc will have extremely
--- unexpected results; it can wait a very long time before returning.
waitForProcess :: ProcessHandle -> IO ExitCode
-waitForProcess = waitForProcessConcurrent . ConcurrentProcessHandle
+waitForProcess = waitForProcessConcurrent
diff --git a/src/Utility/Process/Shim.hs b/src/Utility/Process/Shim.hs
index 09312c7f..3efc6450 100644
--- a/src/Utility/Process/Shim.hs
+++ b/src/Utility/Process/Shim.hs
@@ -1,3 +1,4 @@
module Utility.Process.Shim (module X) where
-import System.Process as X
+import System.Process as X hiding (createProcess, waitForProcess)
+import System.Process.Concurrent as X