diff --git a/System/Posix/Process/ByteString.hsc b/System/Posix/Process/ByteString.hsc
index 4c6840a51d54021c7005815fcddd6547b00a055a..294970ec028c4ddf26582e1a63cc06935ae1d148 100644
--- a/System/Posix/Process/ByteString.hsc
+++ b/System/Posix/Process/ByteString.hsc
@@ -6,7 +6,7 @@
 -- Module      :  System.Posix.Process.ByteString
 -- Copyright   :  (c) The University of Glasgow 2002
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  provisional
 -- Portability :  non-portable (requires POSIX)
@@ -25,7 +25,7 @@ module System.Posix.Process.ByteString (
     forkProcessWithUnmask,
 #endif
     executeFile,
-    
+
     -- ** Exiting
     exitImmediately,
 
@@ -97,10 +97,10 @@ import System.Posix.ByteString.FilePath
 --   environment is provided to supersede the process's current
 --   environment.  The basename (leading directory names suppressed) of
 --   the command is passed to @execv*@ as @arg[0]@;
---   the argument list passed to 'executeFile' therefore 
+--   the argument list passed to 'executeFile' therefore
 --   begins with @arg[1]@.
 executeFile :: RawFilePath                          -- ^ Command
-            -> Bool			    -- ^ Search PATH?
+            -> Bool                         -- ^ Search PATH?
             -> [ByteString]                 -- ^ Arguments
             -> Maybe [(ByteString, ByteString)]     -- ^ Environment
             -> IO a
@@ -108,10 +108,10 @@ executeFile path search args Nothing = do
   withFilePath path $ \s ->
     withMany withFilePath (path:args) $ \cstrs ->
       withArray0 nullPtr cstrs $ \arr -> do
-	pPrPr_disableITimers
-	if search 
-	   then throwErrnoPathIfMinus1_ "executeFile" path (c_execvp s arr)
-	   else throwErrnoPathIfMinus1_ "executeFile" path (c_execv s arr)
+        pPrPr_disableITimers
+        if search
+           then throwErrnoPathIfMinus1_ "executeFile" path (c_execvp s arr)
+           else throwErrnoPathIfMinus1_ "executeFile" path (c_execv s arr)
         return undefined -- never reached
 
 executeFile path search args (Just env) = do
@@ -121,12 +121,12 @@ executeFile path search args (Just env) = do
     let env' = map (\ (name, val) -> name `BC.append` ('=' `BC.cons` val)) env in
     withMany withFilePath env' $ \cenv ->
       withArray0 nullPtr cenv $ \env_arr -> do
-	pPrPr_disableITimers
-	if search 
-	   then throwErrnoPathIfMinus1_ "executeFile" path
-		   (c_execvpe s arg_arr env_arr)
-	   else throwErrnoPathIfMinus1_ "executeFile" path
-		   (c_execve s arg_arr env_arr)
+        pPrPr_disableITimers
+        if search
+           then throwErrnoPathIfMinus1_ "executeFile" path
+                   (c_execvpe s arg_arr env_arr)
+           else throwErrnoPathIfMinus1_ "executeFile" path
+                   (c_execve s arg_arr env_arr)
         return undefined -- never reached
 
 foreign import ccall unsafe "execvp"
@@ -137,4 +137,3 @@ foreign import ccall unsafe "execv"
 
 foreign import ccall unsafe "execve"
   c_execve :: CString -> Ptr CString -> Ptr CString -> IO CInt
-
diff --git a/System/Posix/Process/Common.hsc b/System/Posix/Process/Common.hsc
index e8fd415b9a4dded828e0a0217080421c0352de6e..66e0d20dcb6d50ee52df5da2dc08755e54128d60 100644
--- a/System/Posix/Process/Common.hsc
+++ b/System/Posix/Process/Common.hsc
@@ -7,7 +7,7 @@
 -- Module      :  System.Posix.Process.Common
 -- Copyright   :  (c) The University of Glasgow 2002
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  provisional
 -- Portability :  non-portable (requires POSIX)
@@ -83,7 +83,7 @@ import Control.Monad
 
 #ifdef __GLASGOW_HASKELL__
 import Control.Exception.Base ( bracket, getMaskingState, MaskingState(..) ) -- used by forkProcess
-import GHC.TopHandler	( runIO )
+import GHC.TopHandler   ( runIO )
 import GHC.IO ( unsafeUnmask, uninterruptibleMask_ )
 #endif
 
@@ -188,11 +188,11 @@ foreign import ccall unsafe "setsid"
 
 data ProcessTimes
   = ProcessTimes { elapsedTime     :: ClockTick
-  		 , userTime        :: ClockTick
-		 , systemTime      :: ClockTick
-		 , childUserTime   :: ClockTick
-		 , childSystemTime :: ClockTick
-		 }
+                 , userTime        :: ClockTick
+                 , systemTime      :: ClockTick
+                 , childUserTime   :: ClockTick
+                 , childSystemTime :: ClockTick
+                 }
 
 -- | 'getProcessTimes' calls @times@ to obtain time-accounting
 --   information for the current process and its children.
@@ -205,11 +205,11 @@ getProcessTimes = do
      cut <- (#peek struct tms, tms_cutime) p_tms
      cst <- (#peek struct tms, tms_cstime) p_tms
      return (ProcessTimes{ elapsedTime     = elapsed,
-	 		   userTime        = ut,
-	 		   systemTime      = st,
-	 		   childUserTime   = cut,
-	 		   childSystemTime = cst
-			  })
+                           userTime        = ut,
+                           systemTime      = st,
+                           childUserTime   = cut,
+                           childSystemTime = cst
+                          })
 
 type CTms = ()
 
@@ -256,7 +256,7 @@ setProcessPriority      :: ProcessID      -> Int -> IO ()
 setProcessGroupPriority :: ProcessGroupID -> Int -> IO ()
 setUserPriority         :: UserID         -> Int -> IO ()
 
-setProcessPriority pid val = 
+setProcessPriority pid val =
   throwErrnoIfMinus1_ "setProcessPriority" $
     c_setpriority (#const PRIO_PROCESS) (fromIntegral pid) (fromIntegral val)
 
@@ -329,11 +329,11 @@ getProcessStatus :: Bool -> Bool -> ProcessID -> IO (Maybe ProcessStatus)
 getProcessStatus block stopped pid =
   alloca $ \wstatp -> do
     pid' <- throwErrnoIfMinus1Retry "getProcessStatus"
-		(c_waitpid pid wstatp (waitOptions block stopped))
+                (c_waitpid pid wstatp (waitOptions block stopped))
     case pid' of
       0  -> return Nothing
       _  -> do ps <- readWaitStatus wstatp
-	       return (Just ps)
+               return (Just ps)
 
 -- safe/interruptible, because this call might block
 foreign import ccall interruptible "waitpid"
@@ -356,11 +356,11 @@ getGroupProcessStatus :: Bool
 getGroupProcessStatus block stopped pgid =
   alloca $ \wstatp -> do
     pid <- throwErrnoIfMinus1Retry "getGroupProcessStatus"
-		(c_waitpid (-pgid) wstatp (waitOptions block stopped))
+                (c_waitpid (-pgid) wstatp (waitOptions block stopped))
     case pid of
       0  -> return Nothing
       _  -> do ps <- readWaitStatus wstatp
-	       return (Just (pid, ps))
+               return (Just (pid, ps))
 
 -- | @'getAnyProcessStatus' blk stopped@ calls @waitpid@, returning
 --   @'Just' (pid, tc)@, the 'ProcessID' and 'ProcessStatus' for any
diff --git a/System/Posix/Signals.hsc b/System/Posix/Signals.hsc
index 4b5321e7e70b5e076925d4852086482c030ef7f0..d4c6d517b9ee1fc7b0bb1b23aba184f2b5d4eaee 100644
--- a/System/Posix/Signals.hsc
+++ b/System/Posix/Signals.hsc
@@ -8,7 +8,7 @@
 -- Module      :  System.Posix.Signals
 -- Copyright   :  (c) The University of Glasgow 2002
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  provisional
 -- Portability :  non-portable (requires POSIX)
@@ -276,27 +276,27 @@ fileSizeLimitExceeded = sigXFSZ
 -- -----------------------------------------------------------------------------
 -- Signal-related functions
 
--- | @signalProcess int pid@ calls @kill@ to signal process @pid@ 
+-- | @signalProcess int pid@ calls @kill@ to signal process @pid@
 --   with interrupt signal @int@.
 signalProcess :: Signal -> ProcessID -> IO ()
-signalProcess sig pid 
+signalProcess sig pid
  = throwErrnoIfMinus1_ "signalProcess" (c_kill pid sig)
 
 foreign import ccall unsafe "kill"
   c_kill :: CPid -> CInt -> IO CInt
 
 
--- | @signalProcessGroup int pgid@ calls @kill@ to signal 
+-- | @signalProcessGroup int pgid@ calls @kill@ to signal
 --  all processes in group @pgid@ with interrupt signal @int@.
 signalProcessGroup :: Signal -> ProcessGroupID -> IO ()
-signalProcessGroup sig pgid 
+signalProcessGroup sig pgid
   = throwErrnoIfMinus1_ "signalProcessGroup" (c_killpg pgid sig)
 
 foreign import ccall unsafe "killpg"
   c_killpg :: CPid -> CInt -> IO CInt
 
 -- | @raiseSignal int@ calls @kill@ to signal the current process
---   with interrupt signal @int@. 
+--   with interrupt signal @int@.
 raiseSignal :: Signal -> IO ()
 raiseSignal sig = throwErrnoIfMinus1_ "raiseSignal" (c_raise sig)
 
@@ -315,7 +315,7 @@ type Signal = CInt
 -- | The actions to perform when a signal is received.
 data Handler = Default
              | Ignore
-	     -- not yet: | Hold 
+             -- not yet: | Hold
              | Catch (IO ())
              | CatchOnce (IO ())
              | CatchInfo (SignalInfo -> IO ())     -- ^ /Since: 2.7.0.0/
@@ -354,11 +354,11 @@ data SignalSpecificInfo
 --   signal handler for @int@ is returned
 installHandler :: Signal
                -> Handler
-               -> Maybe SignalSet	-- ^ other signals to block
-               -> IO Handler		-- ^ old handler
+               -> Maybe SignalSet       -- ^ other signals to block
+               -> IO Handler            -- ^ old handler
 
 #ifdef __PARALLEL_HASKELL__
-installHandler = 
+installHandler =
   error "installHandler: not available for Parallel Haskell"
 #else
 
@@ -392,7 +392,7 @@ installHandler sig handler _maybe_mask = do
             CatchInfo     action -> setHandler sig (Just (getinfo action,dyn))
             CatchInfoOnce action -> setHandler sig (Just (getinfo action,dyn))
             _                    -> error "installHandler"
-            
+
         let action = case handler of
                 Catch _         -> STG_SIG_HAN
                 CatchOnce _     -> STG_SIG_RST
@@ -417,10 +417,10 @@ installHandler sig handler _maybe_mask = do
 
 foreign import ccall unsafe
   stg_sig_install
-	:: CInt				-- sig no.
-	-> CInt				-- action code (STG_SIG_HAN etc.)
-	-> Ptr CSigset			-- (in, out) blocked
-	-> IO CInt			-- (ret) old action code
+        :: CInt                         -- sig no.
+        -> CInt                         -- action code (STG_SIG_HAN etc.)
+        -> Ptr CSigset                  -- (in, out) blocked
+        -> IO CInt                      -- (ret) old action code
 
 getinfo :: (SignalInfo -> IO ()) -> ForeignPtr Word8 -> IO ()
 getinfo handler fp_info = do
@@ -476,7 +476,7 @@ foreign import ccall "&nocldstop" nocldstop :: Ptr Int
 setStoppedChildFlag :: Bool -> IO Bool
 setStoppedChildFlag b = do
     rc <- peek nocldstop
-    poke nocldstop $ fromEnum (not b) 
+    poke nocldstop $ fromEnum (not b)
     return (rc == (0::Int))
 
 -- | Queries the current state of the stopped child flag.
@@ -543,7 +543,7 @@ getSignalMask = do
   withForeignPtr fp $ \p ->
     throwErrnoIfMinus1_ "getSignalMask" (c_sigprocmask 0 nullPtr p)
   return (SignalSet fp)
-   
+
 sigProcMask :: String -> CInt -> SignalSet -> IO ()
 sigProcMask fn how (SignalSet set) =
   withForeignPtr set $ \p_set ->
@@ -562,7 +562,7 @@ blockSignals set = sigProcMask "blockSignals" (CONST_SIG_BLOCK :: CInt) set
 
 -- | @unblockSignals mask@ calls @sigprocmask@ with
 --   @SIG_UNBLOCK@ to remove all interrupts in @mask@ from the
---   set of blocked interrupts. 
+--   set of blocked interrupts.
 unblockSignals :: SignalSet -> IO ()
 unblockSignals set = sigProcMask "unblockSignals" (CONST_SIG_UNBLOCK :: CInt) set
 
@@ -571,7 +571,7 @@ unblockSignals set = sigProcMask "unblockSignals" (CONST_SIG_UNBLOCK :: CInt) se
 getPendingSignals :: IO SignalSet
 getPendingSignals = do
   fp <- mallocForeignPtrBytes sizeof_sigset_t
-  withForeignPtr fp $ \p -> 
+  withForeignPtr fp $ \p ->
    throwErrnoIfMinus1_ "getPendingSignals" (c_sigpending p)
   return (SignalSet fp)
 
@@ -581,7 +581,7 @@ getPendingSignals = do
 -- If @iset@ is @Just s@, @awaitSignal@ calls @sigsuspend@, installing
 -- @s@ as the new signal mask before suspending execution; otherwise, it
 -- calls @sigsuspend@ with current signal mask. Note that RTS
--- scheduler signal (either 'virtualTimerExpired' or 'realTimeAlarm') 
+-- scheduler signal (either 'virtualTimerExpired' or 'realTimeAlarm')
 -- could cause premature termination of this call. It might be necessary to block that
 -- signal before invocation of @awaitSignal@ with 'blockSignals' 'reservedSignals'.
 --
@@ -593,8 +593,8 @@ getPendingSignals = do
 awaitSignal :: Maybe SignalSet -> IO ()
 awaitSignal maybe_sigset = do
   fp <- case maybe_sigset of
-    	  Nothing -> do SignalSet fp <- getSignalMask; return fp
-    	  Just (SignalSet fp) -> return fp
+          Nothing -> do SignalSet fp <- getSignalMask; return fp
+          Just (SignalSet fp) -> return fp
   withForeignPtr fp $ \p -> do
   _ <- c_sigsuspend p
   return ()
@@ -640,4 +640,3 @@ foreign import capi unsafe "signal.h sigismember"
 
 foreign import ccall unsafe "sigpending"
   c_sigpending :: Ptr CSigset -> IO CInt
-
diff --git a/System/Posix/Terminal.hsc b/System/Posix/Terminal.hsc
index a7ede2b8d877dcbd18a26b80544fd0fbd5cb04c7..be2d040b77005b655220070e3ea0911f5ed6f3b4 100644
--- a/System/Posix/Terminal.hsc
+++ b/System/Posix/Terminal.hsc
@@ -6,7 +6,7 @@
 -- Module      :  System.Posix.Terminal
 -- Copyright   :  (c) The University of Glasgow 2002
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  provisional
 -- Portability :  non-portable (requires POSIX)
@@ -88,7 +88,7 @@ import System.Posix.Internals (peekFilePath)
 getTerminalName :: Fd -> IO FilePath
 getTerminalName (Fd fd) = do
   s <- throwErrnoIfNull "getTerminalName" (c_ttyname fd)
-  peekFilePath s  
+  peekFilePath s
 
 foreign import ccall unsafe "ttyname"
   c_ttyname :: CInt -> IO CString