{-# LINE 1 "libraries/unix/./System/Posix/Temp/ByteString.hsc" #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LINE 2 "libraries/unix/./System/Posix/Temp/ByteString.hsc" #-} {-# LINE 3 "libraries/unix/./System/Posix/Temp/ByteString.hsc" #-} {-# LANGUAGE Trustworthy #-} {-# LINE 5 "libraries/unix/./System/Posix/Temp/ByteString.hsc" #-} ----------------------------------------------------------------------------- -- | -- Module : System.Posix.Temp.ByteString -- Copyright : (c) Volker Stolz <vs@foldr.org> -- License : BSD-style (see the file libraries/base/LICENSE) -- -- Maintainer : vs@foldr.org -- Stability : provisional -- Portability : non-portable (requires POSIX) -- -- POSIX environment support -- ----------------------------------------------------------------------------- module System.Posix.Temp.ByteString ( mkstemp {- Not ported (yet?): tmpfile: can we handle FILE*? tmpnam: ISO C, should go in base? tempname: dito -} ) where {-# LINE 32 "libraries/unix/./System/Posix/Temp/ByteString.hsc" #-} import System.IO (Handle) import System.Posix.IO import System.Posix.Types import Foreign.C hiding ( throwErrnoPath, throwErrnoPathIf, throwErrnoPathIf_, throwErrnoPathIfNull, throwErrnoPathIfMinus1, throwErrnoPathIfMinus1_ ) import System.Posix.ByteString.FilePath import Data.ByteString (ByteString) -- |'mkstemp' - make a unique filename and open it for -- reading\/writing (only safe on GHC & Hugs). -- The returned 'RawFilePath' is the (possibly relative) path of -- the created file, which is padded with 6 random characters. mkstemp :: ByteString -> IO (RawFilePath, Handle) mkstemp template = do {-# LINE 57 "libraries/unix/./System/Posix/Temp/ByteString.hsc" #-} withFilePath template $ \ ptr -> do fd <- throwErrnoIfMinus1 "mkstemp" (c_mkstemp ptr) name <- peekFilePath ptr h <- fdToHandle (Fd fd) return (name, h) {-# LINE 79 "libraries/unix/./System/Posix/Temp/ByteString.hsc" #-} foreign import ccall unsafe "HsUnix.h __hscore_mkstemp" c_mkstemp :: CString -> IO CInt