Skip to content
Snippets Groups Projects
Commit 4b867e26 authored by dterei's avatar dterei
Browse files

Code cleaning for recent changes

parent bf46721d
Branches
Tags
No related merge requests found
...@@ -23,14 +23,16 @@ module System.Posix.Temp ( ...@@ -23,14 +23,16 @@ module System.Posix.Temp (
#include "HsUnix.h" #include "HsUnix.h"
#if !HAVE_MKSTEMPS
import Control.Exception (throwIO) import Control.Exception (throwIO)
#endif
import Foreign.C
import System.IO import System.IO
import System.Posix.IO #if !HAVE_MKDTEMP
import System.Posix.Types
#if !defined(__GLASGOW_HASKELL__) && !defined(__HUGS__)
import System.Posix.Directory (createDirectory) import System.Posix.Directory (createDirectory)
#endif #endif
import Foreign.C import System.Posix.IO
import System.Posix.Types
#if __GLASGOW_HASKELL__ > 700 #if __GLASGOW_HASKELL__ > 700
import System.Posix.Internals (withFilePath, peekFilePath) import System.Posix.Internals (withFilePath, peekFilePath)
...@@ -49,6 +51,11 @@ peekFilePath :: CString -> IO FilePath ...@@ -49,6 +51,11 @@ peekFilePath :: CString -> IO FilePath
peekFilePath = peekCString peekFilePath = peekCString
#endif #endif
#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
foreign import ccall unsafe "HsUnix.h __hscore_mkstemp"
c_mkstemp :: CString -> IO CInt
#endif
-- | Make a unique filename and open it for reading\/writing. The returned -- | Make a unique filename and open it for reading\/writing. The returned
-- 'FilePath' is the (possibly relative) path of the created file, which is -- 'FilePath' is the (possibly relative) path of the created file, which is
-- padded with 6 random characters. The argument is the desired prefix of the -- padded with 6 random characters. The argument is the desired prefix of the
...@@ -71,22 +78,25 @@ mkstemp template' = do ...@@ -71,22 +78,25 @@ mkstemp template' = do
return (name, h) return (name, h)
#endif #endif
#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__) #if HAVE_MKSTEMPS
foreign import ccall unsafe "HsUnix.h __hscore_mkstemp" foreign import ccall unsafe "HsUnix.h __hscore_mkstemps"
c_mkstemp :: CString -> IO CInt c_mkstemps :: CString -> CInt -> IO CInt
#endif #endif
-- |'mkstemps' - make a unique filename with a given prefix and suffix -- | Make a unique filename with a given prefix and suffix and open it for
-- and open it for reading\/writing (only safe on GHC & Hugs). -- reading\/writing. The returned 'FilePath' is the (possibly relative) path of
-- The returned 'FilePath' is the (possibly relative) path of -- the created file, which contains 6 random characters in between the prefix
-- the created file, which contains 6 random characters in between -- and suffix. The first argument is the desired prefix of the filepath of the
-- the prefix and suffix. -- temporary file to be created. The second argument is the suffix of the
-- temporary file to be created.
--
-- If you are using as system that doesn't support the mkstemps glibc function
-- (supported in glibc > 2.11) then this function simply throws an error.
mkstemps :: String -> String -> IO (FilePath, Handle) mkstemps :: String -> String -> IO (FilePath, Handle)
mkstemps prefix suffix = do mkstemps prefix suffix = do
#if HAVE_MKSTEMPS #if HAVE_MKSTEMPS
let template = prefix ++ "XXXXXX" ++ suffix let template = prefix ++ "XXXXXX" ++ suffix
lenOfsuf :: CInt lenOfsuf = (fromIntegral $ length suffix) :: CInt
lenOfsuf = fromIntegral $ length suffix
withFilePath template $ \ ptr -> do withFilePath template $ \ ptr -> do
fd <- throwErrnoIfMinus1 "mkstemps" (c_mkstemps ptr lenOfsuf) fd <- throwErrnoIfMinus1 "mkstemps" (c_mkstemps ptr lenOfsuf)
name <- peekFilePath ptr name <- peekFilePath ptr
...@@ -96,17 +106,18 @@ mkstemps prefix suffix = do ...@@ -96,17 +106,18 @@ mkstemps prefix suffix = do
throwIO . userError $ "mkstemps: System does not have a mkstemp C function." throwIO . userError $ "mkstemps: System does not have a mkstemp C function."
#endif #endif
#if HAVE_MKSTEMPS #if HAVE_MKDTEMP
foreign import ccall unsafe "HsUnix.h __hscore_mkstemps" foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
c_mkstemps :: CString -> CInt -> IO CInt c_mkdtemp :: CString -> IO CString
#endif #endif
-- | Make a unique directory. The returned 'FilePath' is the path of the -- | Make a unique directory. The returned 'FilePath' is the path of the
-- created directory, which is padded with 6 random characters. The argument is -- created directory, which is padded with 6 random characters. The argument is
-- the desired prefix of the filepath of the temporary directory to be created. -- the desired prefix of the filepath of the temporary directory to be created.
-- --
-- If you aren't using GHC or Hugs then this function simply wraps mktemp and -- If you are using as system that doesn't support the mkdtemp glibc function
-- so shouldn't be considered safe. -- (supported in glibc > 2.1.91) then this function uses mktemp and so
-- shouldn't be considered safe.
mkdtemp :: String -> IO FilePath mkdtemp :: String -> IO FilePath
mkdtemp template' = do mkdtemp template' = do
let template = template' ++ "XXXXXX" let template = template' ++ "XXXXXX"
...@@ -121,12 +132,11 @@ mkdtemp template' = do ...@@ -121,12 +132,11 @@ mkdtemp template' = do
return name return name
#endif #endif
#if HAVE_MKDTEMP
foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
c_mkdtemp :: CString -> IO CString
#endif
#if (!defined(__GLASGOW_HASKELL__) && !defined(__HUGS__)) || !HAVE_MKDTEMP #if (!defined(__GLASGOW_HASKELL__) && !defined(__HUGS__)) || !HAVE_MKDTEMP
foreign import ccall unsafe "mktemp"
c_mktemp :: CString -> IO CString
-- | Make a unique file name It is required that the template have six trailing -- | Make a unique file name It is required that the template have six trailing
-- \'X\'s. This function should be considered deprecated. -- \'X\'s. This function should be considered deprecated.
{-# WARNING mktemp "This function is unsafe; use mkstemp instead" #-} {-# WARNING mktemp "This function is unsafe; use mkstemp instead" #-}
...@@ -135,8 +145,5 @@ mktemp template = do ...@@ -135,8 +145,5 @@ mktemp template = do
withFilePath template $ \ ptr -> do withFilePath template $ \ ptr -> do
ptr <- throwErrnoIfNull "mktemp" (c_mktemp ptr) ptr <- throwErrnoIfNull "mktemp" (c_mktemp ptr)
peekFilePath ptr peekFilePath ptr
foreign import ccall unsafe "mktemp"
c_mktemp :: CString -> IO CString
#endif #endif
...@@ -23,23 +23,27 @@ module System.Posix.Temp.ByteString ( ...@@ -23,23 +23,27 @@ module System.Posix.Temp.ByteString (
#include "HsUnix.h" #include "HsUnix.h"
#if !HAVE_MKSTEMPS
import Control.Exception (throwIO) import Control.Exception (throwIO)
import System.IO
import System.Posix.IO
import System.Posix.Types
#if !defined(__GLASGOW_HASKELL__) && !defined(__HUGS__)
import System.Posix.Directory (createDirectory)
#endif #endif
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Foreign.C import Foreign.C
import System.IO
import System.Posix.ByteString.FilePath import System.Posix.ByteString.FilePath
#if !HAVE_MKDTEMP
import System.Posix.Directory (createDirectory)
#endif
import System.Posix.IO
import System.Posix.Types
import Data.ByteString (ByteString) #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
import qualified Data.ByteString as B foreign import ccall unsafe "HsUnix.h __hscore_mkstemp"
import qualified Data.ByteString.Char8 as BC c_mkstemp :: CString -> IO CInt
#endif
-- | Make a unique filename and open it for reading\/writing. The returned -- | Make a unique filename and open it for reading\/writing. The returned
-- 'RawFilePath' is the (possibly relative) path of the created file, which is -- 'RawFilePath' is the (possibly relative) path of the created file, which is
...@@ -63,9 +67,9 @@ mkstemp template' = do ...@@ -63,9 +67,9 @@ mkstemp template' = do
return (name, h) return (name, h)
#endif #endif
#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__) #if HAVE_MKSTEMPS
foreign import ccall unsafe "HsUnix.h __hscore_mkstemp" foreign import ccall unsafe "HsUnix.h __hscore_mkstemps"
c_mkstemp :: CString -> IO CInt c_mkstemps :: CString -> CInt -> IO CInt
#endif #endif
-- |'mkstemps' - make a unique filename with a given prefix and suffix -- |'mkstemps' - make a unique filename with a given prefix and suffix
...@@ -77,8 +81,7 @@ mkstemps :: ByteString -> ByteString -> IO (RawFilePath, Handle) ...@@ -77,8 +81,7 @@ mkstemps :: ByteString -> ByteString -> IO (RawFilePath, Handle)
mkstemps prefix suffix = do mkstemps prefix suffix = do
#if HAVE_MKSTEMPS #if HAVE_MKSTEMPS
let template = prefix `B.append` (BC.pack "XXXXXX") `B.append` suffix let template = prefix `B.append` (BC.pack "XXXXXX") `B.append` suffix
lenOfsuf :: CInt lenOfsuf = (fromIntegral $ B.length suffix) :: CInt
lenOfsuf = fromIntegral $ B.length suffix
withFilePath template $ \ ptr -> do withFilePath template $ \ ptr -> do
fd <- throwErrnoIfMinus1 "mkstemps" (c_mkstemps ptr lenOfsuf) fd <- throwErrnoIfMinus1 "mkstemps" (c_mkstemps ptr lenOfsuf)
name <- peekFilePath ptr name <- peekFilePath ptr
...@@ -88,9 +91,9 @@ mkstemps prefix suffix = do ...@@ -88,9 +91,9 @@ mkstemps prefix suffix = do
throwIO . userError $ "mkstemps: System does not have a mkstemp C function." throwIO . userError $ "mkstemps: System does not have a mkstemp C function."
#endif #endif
#if HAVE_MKSTEMPS #if HAVE_MKDTEMP
foreign import ccall unsafe "HsUnix.h __hscore_mkstemps" foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
c_mkstemps :: CString -> CInt -> IO CInt c_mkdtemp :: CString -> IO CString
#endif #endif
-- | Make a unique directory. The returned 'RawFilePath' is the path of the -- | Make a unique directory. The returned 'RawFilePath' is the path of the
...@@ -113,12 +116,11 @@ mkdtemp template' = do ...@@ -113,12 +116,11 @@ mkdtemp template' = do
return name return name
#endif #endif
#if HAVE_MKDTEMP
foreign import ccall unsafe "HsUnix.h __hscore_mkdtemp"
c_mkdtemp :: CString -> IO CString
#endif
#if (!defined(__GLASGOW_HASKELL__) && !defined(__HUGS__)) || !HAVE_MKDTEMP #if (!defined(__GLASGOW_HASKELL__) && !defined(__HUGS__)) || !HAVE_MKDTEMP
foreign import ccall unsafe "mktemp"
c_mktemp :: CString -> IO CString
-- | Make a unique file name It is required that the template have six trailing -- | Make a unique file name It is required that the template have six trailing
-- \'X\'s. This function should be considered deprecated. -- \'X\'s. This function should be considered deprecated.
{-# WARNING mktemp "This function is unsafe; use mkstemp instead" #-} {-# WARNING mktemp "This function is unsafe; use mkstemp instead" #-}
...@@ -127,8 +129,5 @@ mktemp template = do ...@@ -127,8 +129,5 @@ mktemp template = do
withFilePath template $ \ ptr -> do withFilePath template $ \ ptr -> do
ptr <- throwErrnoIfNull "mktemp" (c_mktemp ptr) ptr <- throwErrnoIfNull "mktemp" (c_mktemp ptr)
peekFilePath ptr peekFilePath ptr
foreign import ccall unsafe "mktemp"
c_mktemp :: CString -> IO CString
#endif #endif
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment