diff --git a/System/Posix/Directory.hsc b/System/Posix/Directory.hsc
index cb357df5d854083e2918a42deb008fd04d537998..7f64e167ad7e8df94d8a6d5bd871184fe40ce807 100644
--- a/System/Posix/Directory.hsc
+++ b/System/Posix/Directory.hsc
@@ -39,14 +39,28 @@ import System.Posix.Error
 import System.Posix.Types
 import Foreign
 import Foreign.C
+#if __GLASGOW_HASKELL__ > 700
+import System.Posix.Internals (withFilePath, peekFilePath)
+#elif __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals (withFilePath)
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+#else
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+#endif
 
 -- | @createDirectory dir mode@ calls @mkdir@ to 
 --   create a new directory, @dir@, with permissions based on
 --  @mode@.
 createDirectory :: FilePath -> FileMode -> IO ()
 createDirectory name mode =
-  withCString name $ \s ->
-    throwErrnoPathIfMinus1Retry_ "createDirectory" name (c_mkdir s mode)
+  withFilePath name $ \s -> 
+    throwErrnoPathIfMinus1Retry_ "createDirectory" name (c_mkdir s mode)  
     -- POSIX doesn't allow mkdir() to return EINTR, but it does on
     -- OS X (#5184), so we need the Retry variant here.
 
@@ -59,7 +73,7 @@ newtype DirStream = DirStream (Ptr CDir)
 --   directory stream for @dir@.
 openDirStream :: FilePath -> IO DirStream
 openDirStream name =
-  withCString name $ \s -> do
+  withFilePath name $ \s -> do
     dirp <- throwErrnoPathIfNullRetry "openDirStream" name $ c_opendir s
     return (DirStream dirp)
 
@@ -82,7 +96,7 @@ readDirStream (DirStream dirp) =
 		 if (dEnt == nullPtr)
 		    then return []
 		    else do
-	 	     entry <- (d_name dEnt >>= peekCString)
+	 	     entry <- (d_name dEnt >>= peekFilePath)
 		     c_freeDirEnt dEnt
 		     return entry
 	 else do errno <- getErrno
@@ -154,7 +168,7 @@ getWorkingDirectory = do
   where go p bytes = do
     	  p' <- c_getcwd p (fromIntegral bytes)
 	  if p' /= nullPtr 
-	     then do s <- peekCString p'
+	     then do s <- peekFilePath p'
 		     free p'
 		     return s
 	     else do errno <- getErrno
@@ -175,7 +189,7 @@ foreign import ccall unsafe "__hsunix_long_path_size"
 changeWorkingDirectory :: FilePath -> IO ()
 changeWorkingDirectory path =
   modifyIOError (`ioeSetFileName` path) $
-    withCString path $ \s -> 
+    withFilePath path $ \s -> 
        throwErrnoIfMinus1Retry_ "changeWorkingDirectory" (c_chdir s)
 
 foreign import ccall unsafe "chdir"
@@ -184,7 +198,7 @@ foreign import ccall unsafe "chdir"
 removeDirectory :: FilePath -> IO ()
 removeDirectory path =
   modifyIOError (`ioeSetFileName` path) $
-    withCString path $ \s ->
+    withFilePath path $ \s ->
        throwErrnoIfMinus1Retry_ "removeDirectory" (c_rmdir s)
 
 foreign import ccall unsafe "rmdir"
diff --git a/System/Posix/DynamicLinker.hsc b/System/Posix/DynamicLinker.hsc
index 1aa897bceb3a10cc1f1f41839d4f5788970877d7..418ce39124e5f240d04fe00022795a5a4c8eb86c 100644
--- a/System/Posix/DynamicLinker.hsc
+++ b/System/Posix/DynamicLinker.hsc
@@ -51,11 +51,17 @@ import System.Posix.DynamicLinker.Prim
 import Control.Exception	( bracket )
 import Control.Monad	( liftM )
 import Foreign.Ptr	( Ptr, nullPtr, FunPtr, nullFunPtr )
-import Foreign.C.String	( withCString, peekCString )
-
-dlopen :: String -> [RTLDFlags] -> IO DL
+import Foreign.C.String
+#if __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals ( withFilePath )
+#else
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+#endif
+
+dlopen :: FilePath -> [RTLDFlags] -> IO DL
 dlopen path flags = do
-  withCString path $ \ p -> do
+  withFilePath path $ \ p -> do
     liftM DLHandle $ throwDLErrorIf "dlopen" (== nullPtr) $ c_dlopen p (packRTLDFlags flags)
 
 dlclose :: DL -> IO ()
@@ -70,7 +76,7 @@ dlerror = c_dlerror >>= peekCString
 
 dlsym :: DL -> String -> IO (FunPtr a)
 dlsym source symbol = do
-  withCString symbol $ \ s -> do
+  withCAString symbol $ \ s -> do
     throwDLErrorIf "dlsym" (== nullFunPtr) $ c_dlsym (packDL source) s
 
 withDL :: String -> [RTLDFlags] -> (DL -> IO a) -> IO a
diff --git a/System/Posix/DynamicLinker/Module.hsc b/System/Posix/DynamicLinker/Module.hsc
index 080dad411cba720bbd4e2a7985de0bde4e946bf2..7ea8284c3ac9086b251e6b27ea469814e495406c 100644
--- a/System/Posix/DynamicLinker/Module.hsc
+++ b/System/Posix/DynamicLinker/Module.hsc
@@ -58,8 +58,15 @@ where
 
 import System.Posix.DynamicLinker
 import Foreign.Ptr	( Ptr, nullPtr, FunPtr )
+#if __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals ( withFilePath )
+#else
 import Foreign.C.String	( withCString )
 
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+#endif
+
 -- abstract handle for dynamically loaded module (EXPORTED)
 --
 newtype Module = Module (Ptr ())
@@ -72,7 +79,7 @@ unModule (Module adr)  = adr
 
 moduleOpen :: String -> [RTLDFlags] -> IO Module
 moduleOpen file flags = do
-  modPtr <- withCString file $ \ modAddr -> c_dlopen modAddr (packRTLDFlags flags)
+  modPtr <- withFilePath file $ \ modAddr -> c_dlopen modAddr (packRTLDFlags flags)
   if (modPtr == nullPtr)
       then moduleError >>= \ err -> ioError (userError ("dlopen: " ++ err))
       else return $ Module modPtr
diff --git a/System/Posix/Env.hsc b/System/Posix/Env.hsc
index 83bdc2c93894d83a9783d8746736c5ce2de09193..799fd6b1b31e4e0b372cea266230c3ad3c52465f 100644
--- a/System/Posix/Env.hsc
+++ b/System/Posix/Env.hsc
@@ -33,14 +33,28 @@ import Foreign.Ptr
 import Foreign.Storable
 import Control.Monad	( liftM )
 import Data.Maybe	( fromMaybe )
+#if __GLASGOW_HASKELL__ > 700
+import System.Posix.Internals (withFilePath, peekFilePath)
+#elif __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals (withFilePath)
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+#else
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+#endif
 
 -- |'getEnv' looks up a variable in the environment.
 
 getEnv :: String -> IO (Maybe String)
 getEnv name = do
-  litstring <- withCString name c_getenv
+  litstring <- withFilePath name c_getenv
   if litstring /= nullPtr
-     then liftM Just $ peekCString litstring
+     then liftM Just $ peekFilePath litstring
      else return Nothing
 
 -- |'getEnvDefault' is a wrapper around 'getEnv' where the
@@ -57,7 +71,7 @@ getEnvironmentPrim :: IO [String]
 getEnvironmentPrim = do
   c_environ <- getCEnviron
   arr <- peekArray0 nullPtr c_environ
-  mapM peekCString arr
+  mapM peekFilePath arr
 
 getCEnviron :: IO (Ptr CString)
 #if darwin_HOST_OS
@@ -91,7 +105,7 @@ getEnvironment = do
 unsetEnv :: String -> IO ()
 #ifdef HAVE_UNSETENV
 
-unsetEnv name = withCString name $ \ s ->
+unsetEnv name = withFilePath name $ \ s ->
   throwErrnoIfMinus1_ "unsetenv" (c_unsetenv s)
 
 foreign import ccall unsafe "__hsunix_unsetenv"
@@ -104,7 +118,7 @@ unsetEnv name = putEnv (name ++ "=")
 -- and is equivalent to @setEnv(key,value,True{-overwrite-})@.
 
 putEnv :: String -> IO ()
-putEnv keyvalue = withCString keyvalue $ \s ->
+putEnv keyvalue = withFilePath keyvalue $ \s ->
   throwErrnoIfMinus1_ "putenv" (c_putenv s)
 
 foreign import ccall unsafe "putenv"
@@ -120,8 +134,8 @@ foreign import ccall unsafe "putenv"
 setEnv :: String -> String -> Bool {-overwrite-} -> IO ()
 #ifdef HAVE_SETENV
 setEnv key value ovrwrt = do
-  withCString key $ \ keyP ->
-    withCString value $ \ valueP ->
+  withFilePath key $ \ keyP ->
+    withFilePath value $ \ valueP ->
       throwErrnoIfMinus1_ "setenv" $
 	c_setenv keyP valueP (fromIntegral (fromEnum ovrwrt))
 
diff --git a/System/Posix/Files.hsc b/System/Posix/Files.hsc
index 0242a076062c632c16e9f6fc024c51b0eaf32d3e..e8dbe43e27945bd48e21575a997c1638762c4318 100644
--- a/System/Posix/Files.hsc
+++ b/System/Posix/Files.hsc
@@ -93,6 +93,26 @@ import Data.Bits
 import System.Posix.Internals
 import Foreign hiding (unsafePerformIO)
 import Foreign.C
+#if __GLASGOW_HASKELL__ > 700
+import System.Posix.Internals (withFilePath, peekFilePath)
+#elif __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals (withFilePath)
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+
+peekFilePathLen :: CStringLen -> IO FilePath
+peekFilePathLen = peekCStringLen
+#else
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+
+peekFilePathLen :: CStringLen -> IO FilePath
+peekFilePathLen = peekCStringLen
+#endif
 
 -- -----------------------------------------------------------------------------
 -- POSIX file modes
@@ -212,7 +232,7 @@ socketMode = (#const S_IFSOCK)
 -- Note: calls @chmod@.
 setFileMode :: FilePath -> FileMode -> IO ()
 setFileMode name m =
-  withCString name $ \s -> do
+  withFilePath name $ \s -> do
     throwErrnoPathIfMinus1_ "setFileMode" name (c_chmod s m)
 
 -- | @setFdMode fd mode@ acts like 'setFileMode' but uses a file descriptor
@@ -255,7 +275,7 @@ fileAccess name readOK writeOK execOK = access name flags
 -- Note: calls @access@.
 fileExist :: FilePath -> IO Bool
 fileExist name = 
-  withCString name $ \s -> do
+  withFilePath name $ \s -> do
     r <- c_access s (#const F_OK)
     if (r == 0)
 	then return True
@@ -266,7 +286,7 @@ fileExist name =
 
 access :: FilePath -> CMode -> IO Bool
 access name flags = 
-  withCString name $ \s -> do
+  withFilePath name $ \s -> do
     r <- c_access s (fromIntegral flags)
     if (r == 0)
 	then return True
@@ -370,7 +390,7 @@ getFileStatus :: FilePath -> IO FileStatus
 getFileStatus path = do
   fp <- mallocForeignPtrBytes (#const sizeof(struct stat)) 
   withForeignPtr fp $ \p ->
-    withCString path $ \s -> 
+    withFilePath path $ \s -> 
       throwErrnoPathIfMinus1_ "getFileStatus" path (c_stat s p)
   return (FileStatus fp)
 
@@ -393,7 +413,7 @@ getSymbolicLinkStatus :: FilePath -> IO FileStatus
 getSymbolicLinkStatus path = do
   fp <- mallocForeignPtrBytes (#const sizeof(struct stat)) 
   withForeignPtr fp $ \p ->
-    withCString path $ \s -> 
+    withFilePath path $ \s -> 
       throwErrnoPathIfMinus1_ "getSymbolicLinkStatus" path (c_lstat s p)
   return (FileStatus fp)
 
@@ -409,7 +429,7 @@ foreign import ccall unsafe "__hsunix_lstat"
 -- Note: calls @mkfifo@.
 createNamedPipe :: FilePath -> FileMode -> IO ()
 createNamedPipe name mode = do
-  withCString name $ \s -> 
+  withFilePath name $ \s -> 
     throwErrnoPathIfMinus1_ "createNamedPipe" name (c_mkfifo s mode)
 
 -- | @createDevice path mode dev@ creates either a regular or a special file
@@ -422,7 +442,7 @@ createNamedPipe name mode = do
 -- Note: calls @mknod@.
 createDevice :: FilePath -> FileMode -> DeviceID -> IO ()
 createDevice path mode dev =
-  withCString path $ \s ->
+  withFilePath path $ \s ->
     throwErrnoPathIfMinus1_ "createDevice" path (c_mknod s mode dev)
 
 foreign import ccall unsafe "__hsunix_mknod" 
@@ -437,8 +457,8 @@ foreign import ccall unsafe "__hsunix_mknod"
 -- Note: calls @link@.
 createLink :: FilePath -> FilePath -> IO ()
 createLink name1 name2 =
-  withCString name1 $ \s1 ->
-  withCString name2 $ \s2 ->
+  withFilePath name1 $ \s1 ->
+  withFilePath name2 $ \s2 ->
   throwErrnoPathIfMinus1_ "createLink" name1 (c_link s1 s2)
 
 -- | @removeLink path@ removes the link named @path@.
@@ -446,7 +466,7 @@ createLink name1 name2 =
 -- Note: calls @unlink@.
 removeLink :: FilePath -> IO ()
 removeLink name =
-  withCString name $ \s ->
+  withFilePath name $ \s ->
   throwErrnoPathIfMinus1_ "removeLink" name (c_unlink s)
 
 -- -----------------------------------------------------------------------------
@@ -461,8 +481,8 @@ removeLink name =
 -- Note: calls @symlink@.
 createSymbolicLink :: FilePath -> FilePath -> IO ()
 createSymbolicLink file1 file2 =
-  withCString file1 $ \s1 ->
-  withCString file2 $ \s2 ->
+  withFilePath file1 $ \s1 ->
+  withFilePath file2 $ \s2 ->
   throwErrnoPathIfMinus1_ "createSymbolicLink" file1 (c_symlink s1 s2)
 
 foreign import ccall unsafe "symlink"
@@ -483,10 +503,10 @@ foreign import ccall unsafe "symlink"
 readSymbolicLink :: FilePath -> IO FilePath
 readSymbolicLink file =
   allocaArray0 (#const PATH_MAX) $ \buf -> do
-    withCString file $ \s -> do
+    withFilePath file $ \s -> do
       len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $ 
 	c_readlink s buf (#const PATH_MAX)
-      peekCStringLen (buf,fromIntegral len)
+      peekFilePathLen (buf,fromIntegral len)
 
 foreign import ccall unsafe "readlink"
   c_readlink :: CString -> CString -> CSize -> IO CInt
@@ -499,8 +519,8 @@ foreign import ccall unsafe "readlink"
 -- Note: calls @rename@.
 rename :: FilePath -> FilePath -> IO ()
 rename name1 name2 =
-  withCString name1 $ \s1 ->
-  withCString name2 $ \s2 ->
+  withFilePath name1 $ \s1 ->
+  withFilePath name2 $ \s2 ->
   throwErrnoPathIfMinus1_ "rename" name1 (c_rename s1 s2)
 
 foreign import ccall unsafe "rename"
@@ -517,7 +537,7 @@ foreign import ccall unsafe "rename"
 -- Note: calls @chown@.
 setOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()
 setOwnerAndGroup name uid gid = do
-  withCString name $ \s ->
+  withFilePath name $ \s ->
     throwErrnoPathIfMinus1_ "setOwnerAndGroup" name (c_chown s uid gid)
 
 foreign import ccall unsafe "chown"
@@ -541,7 +561,7 @@ foreign import ccall unsafe "fchown"
 -- Note: calls @lchown@.
 setSymbolicLinkOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()
 setSymbolicLinkOwnerAndGroup name uid gid = do
-  withCString name $ \s ->
+  withFilePath name $ \s ->
     throwErrnoPathIfMinus1_ "setSymbolicLinkOwnerAndGroup" name
 	(c_lchown s uid gid)
 
@@ -558,7 +578,7 @@ foreign import ccall unsafe "lchown"
 -- Note: calls @utime@.
 setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()
 setFileTimes name atime mtime = do
-  withCString name $ \s ->
+  withFilePath name $ \s ->
    allocaBytes (#const sizeof(struct utimbuf)) $ \p -> do
      (#poke struct utimbuf, actime)  p atime
      (#poke struct utimbuf, modtime) p mtime
@@ -570,7 +590,7 @@ setFileTimes name atime mtime = do
 -- Note: calls @utime@.
 touchFile :: FilePath -> IO ()
 touchFile name = do
-  withCString name $ \s ->
+  withFilePath name $ \s ->
    throwErrnoPathIfMinus1_ "touchFile" name (c_utime s nullPtr)
 
 -- -----------------------------------------------------------------------------
@@ -582,7 +602,7 @@ touchFile name = do
 -- Note: calls @truncate@.
 setFileSize :: FilePath -> FileOffset -> IO ()
 setFileSize file off = 
-  withCString file $ \s ->
+  withFilePath file $ \s ->
     throwErrnoPathIfMinus1_ "setFileSize" file (c_truncate s off)
 
 foreign import ccall unsafe "truncate"
@@ -672,7 +692,7 @@ pathVarConst v = case v of
 -- Note: calls @pathconf@.
 getPathVar :: FilePath -> PathVar -> IO Limit
 getPathVar name v = do
-  withCString name $ \ nameP -> 
+  withFilePath name $ \ nameP -> 
     throwErrnoPathIfMinus1 "getPathVar" name $ 
       c_pathconf nameP (pathVarConst v)
 
diff --git a/System/Posix/IO.hsc b/System/Posix/IO.hsc
index f58b49b178d99e75a0f3126ab421cdb03c4d145e..710299ba63ae74ac45e252e137f7551b9c599e65 100644
--- a/System/Posix/IO.hsc
+++ b/System/Posix/IO.hsc
@@ -94,6 +94,13 @@ import Hugs.Prelude (IOException(..), IOErrorType(..))
 import qualified Hugs.IO (handleToFd, openFd)
 #endif
 
+#if __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals ( withFilePath )
+#else
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+#endif
+
 #include "HsUnix.h"
 
 -- -----------------------------------------------------------------------------
@@ -178,7 +185,7 @@ openFd :: FilePath
        -> IO Fd
 openFd name how maybe_mode (OpenFileFlags appendFlag exclusiveFlag nocttyFlag
 				nonBlockFlag truncateFlag) = do
-   withCString name $ \s -> do
+   withFilePath name $ \s -> do
     fd <- throwErrnoPathIfMinus1Retry "openFd" name (c_open s all_flags mode_w)
     return (Fd fd)
   where
@@ -424,8 +431,8 @@ waitToSetLock (Fd fd) lock = do
 -- -----------------------------------------------------------------------------
 -- fd{Read,Write}
 
--- | Read data from an 'Fd' and convert it to a 'String'.  Throws an
--- exception if this is an invalid descriptor, or EOF has been
+-- | Read data from an 'Fd' and convert it to a 'String' using the locale encoding.
+-- Throws an exception if this is an invalid descriptor, or EOF has been
 -- reached.
 fdRead :: Fd
        -> ByteCount -- ^How many bytes to read
@@ -455,8 +462,7 @@ fdReadBuf fd buf nbytes =
 foreign import ccall safe "read"
    c_safe_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
 
--- | Write a 'String' to an 'Fd' (no character conversion is done,
--- the least-significant 8 bits of each character are written).
+-- | Write a 'String' to an 'Fd' using the locale encoding.
 fdWrite :: Fd -> String -> IO ByteCount
 fdWrite fd str = 
   withCStringLen str $ \ (buf,len) ->
diff --git a/System/Posix/Process.hsc b/System/Posix/Process.hsc
index 163c35628c1b5f63fba4d8b50f9cb061a240408d..248c2e2eab5b492a3478564b9e9a9b1b56d901ae 100644
--- a/System/Posix/Process.hsc
+++ b/System/Posix/Process.hsc
@@ -63,7 +63,7 @@ module System.Posix.Process (
 #include "HsUnix.h"
 
 import Foreign.C.Error
-import Foreign.C.String ( CString, withCString )
+import Foreign.C.String
 import Foreign.C.Types ( CInt, CClock )
 import Foreign.Marshal.Alloc ( alloca, allocaBytes )
 import Foreign.Marshal.Array ( withArray0 )
@@ -80,6 +80,13 @@ import Control.Monad
 import GHC.TopHandler	( runIO )
 #endif
 
+#if __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals ( withFilePath )
+#else
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+#endif
+
 #ifdef __HUGS__
 {-# CFILES cbits/HsUnix.c  #-}
 #endif
@@ -275,8 +282,8 @@ executeFile :: FilePath			    -- ^ Command
             -> Maybe [(String, String)]	    -- ^ Environment
             -> IO a
 executeFile path search args Nothing = do
-  withCString path $ \s ->
-    withMany withCString (path:args) $ \cstrs ->
+  withFilePath path $ \s ->
+    withMany withFilePath (path:args) $ \cstrs ->
       withArray0 nullPtr cstrs $ \arr -> do
 	pPrPr_disableITimers
 	if search 
@@ -285,11 +292,11 @@ executeFile path search args Nothing = do
         return undefined -- never reached
 
 executeFile path search args (Just env) = do
-  withCString path $ \s ->
-    withMany withCString (path:args) $ \cstrs ->
+  withFilePath path $ \s ->
+    withMany withFilePath (path:args) $ \cstrs ->
       withArray0 nullPtr cstrs $ \arg_arr ->
     let env' = map (\ (name, val) -> name ++ ('=' : val)) env in
-    withMany withCString env' $ \cenv ->
+    withMany withFilePath env' $ \cenv ->
       withArray0 nullPtr cenv $ \env_arr -> do
 	pPrPr_disableITimers
 	if search 
diff --git a/System/Posix/Temp.hsc b/System/Posix/Temp.hsc
index 26c6f6570a17d522a498209e669eaf599b702fd1..612580233e6cfb97c978fe8f177043699d7be495 100644
--- a/System/Posix/Temp.hsc
+++ b/System/Posix/Temp.hsc
@@ -32,6 +32,21 @@ import System.Posix.IO
 import System.Posix.Types
 import Foreign.C
 
+#if __GLASGOW_HASKELL__ > 700
+import System.Posix.Internals (withFilePath, peekFilePath)
+#elif __GLASGOW_HASKELL__ > 611
+import System.Posix.Internals (withFilePath)
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+#else
+withFilePath :: FilePath -> (CString -> IO a) -> IO a
+withFilePath = withCString
+
+peekFilePath :: CString -> IO FilePath
+peekFilePath = peekCString
+#endif
+
 -- |'mkstemp' - make a unique filename and open it for
 -- reading\/writing (only safe on GHC & Hugs).
 -- The returned 'FilePath' is the (possibly relative) path of
@@ -39,9 +54,9 @@ import Foreign.C
 mkstemp :: String -> IO (FilePath, Handle)
 mkstemp template = do
 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
-  withCString template $ \ ptr -> do
+  withFilePath template $ \ ptr -> do
     fd <- throwErrnoIfMinus1 "mkstemp" (c_mkstemp ptr)
-    name <- peekCString ptr
+    name <- peekFilePath ptr
     h <- fdToHandle (Fd fd)
     return (name, h)
 #else
@@ -54,9 +69,9 @@ mkstemp template = do
 
 mktemp :: String -> IO String
 mktemp template = do
-  withCString template $ \ ptr -> do
+  withFilePath template $ \ ptr -> do
     ptr <- throwErrnoIfNull "mktemp" (c_mktemp ptr)
-    peekCString ptr
+    peekFilePath ptr
 
 foreign import ccall unsafe "mktemp"
   c_mktemp :: CString -> IO CString
diff --git a/System/Posix/User.hsc b/System/Posix/User.hsc
index ce7a397cdc9f3755d5fd4d9d031aa1d12e14519c..4f31451f9d79042f738a159c5eefdaa22d8a4f58 100644
--- a/System/Posix/User.hsc
+++ b/System/Posix/User.hsc
@@ -131,7 +131,7 @@ getLoginName :: IO String
 getLoginName =  do
     -- ToDo: use getlogin_r
     str <- throwErrnoIfNull "getLoginName" c_getlogin
-    peekCString str
+    peekCAString str
 
 foreign import ccall unsafe "getlogin"
   c_getlogin :: IO CString
@@ -225,7 +225,7 @@ getGroupEntryForName :: String -> IO GroupEntry
 getGroupEntryForName name = do
   allocaBytes (#const sizeof(struct group)) $ \pgr ->
     alloca $ \ ppgr ->
-      withCString name $ \ pstr -> do
+      withCAString name $ \ pstr -> do
 	throwErrorIfNonZero_ "getGroupEntryForName" $
 	  doubleAllocWhile isERANGE grBufSize $ \s b ->
 	    c_getgrnam_r pstr pgr b (fromIntegral s) ppgr
@@ -287,11 +287,11 @@ grBufSize = 1024
 
 unpackGroupEntry :: Ptr CGroup -> IO GroupEntry
 unpackGroupEntry ptr = do
-   name    <- (#peek struct group, gr_name) ptr >>= peekCString
-   passwd  <- (#peek struct group, gr_passwd) ptr >>= peekCString
+   name    <- (#peek struct group, gr_name) ptr >>= peekCAString
+   passwd  <- (#peek struct group, gr_passwd) ptr >>= peekCAString
    gid     <- (#peek struct group, gr_gid) ptr
    mem     <- (#peek struct group, gr_mem) ptr
-   members <- peekArray0 nullPtr mem >>= mapM peekCString
+   members <- peekArray0 nullPtr mem >>= mapM peekCAString
    return (GroupEntry name passwd gid members)
 
 -- -----------------------------------------------------------------------------
@@ -359,7 +359,7 @@ getUserEntryForName :: String -> IO UserEntry
 getUserEntryForName name = do
   allocaBytes (#const sizeof(struct passwd)) $ \ppw ->
     alloca $ \ pppw ->
-      withCString name $ \ pstr -> do
+      withCAString name $ \ pstr -> do
 	throwErrorIfNonZero_ "getUserEntryForName" $
 	  doubleAllocWhile isERANGE pwBufSize $ \s b ->
 	    c_getpwnam_r pstr ppw b (fromIntegral s) pppw
@@ -377,7 +377,7 @@ foreign import ccall unsafe "__hsunix_getpwnam_r"
                -> CString -> CSize -> Ptr (Ptr CPasswd) -> IO CInt
 #elif HAVE_GETPWNAM
 getUserEntryForName name = do
-  withCString name $ \ pstr -> do
+  withCAString name $ \ pstr -> do
     withMVar lock $ \_ -> do
       ppw <- throwErrnoIfNull "getUserEntryForName" $ c_getpwnam pstr
       unpackUserEntry ppw
@@ -446,13 +446,13 @@ doubleAllocWhile p s m = do
 
 unpackUserEntry :: Ptr CPasswd -> IO UserEntry
 unpackUserEntry ptr = do
-   name   <- (#peek struct passwd, pw_name)   ptr >>= peekCString
-   passwd <- (#peek struct passwd, pw_passwd) ptr >>= peekCString
+   name   <- (#peek struct passwd, pw_name)   ptr >>= peekCAString
+   passwd <- (#peek struct passwd, pw_passwd) ptr >>= peekCAString
    uid    <- (#peek struct passwd, pw_uid)    ptr
    gid    <- (#peek struct passwd, pw_gid)    ptr
-   gecos  <- (#peek struct passwd, pw_gecos)  ptr >>= peekCString
-   dir    <- (#peek struct passwd, pw_dir)    ptr >>= peekCString
-   shell  <- (#peek struct passwd, pw_shell)  ptr >>= peekCString
+   gecos  <- (#peek struct passwd, pw_gecos)  ptr >>= peekCAString
+   dir    <- (#peek struct passwd, pw_dir)    ptr >>= peekCAString
+   shell  <- (#peek struct passwd, pw_shell)  ptr >>= peekCAString
    return (UserEntry name passwd uid gid gecos dir shell)
 
 -- Used when calling re-entrant system calls that signal their 'errno'