{-# LINE 1 "libraries/unix/./System/Posix/Temp.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "libraries/unix/./System/Posix/Temp.hsc" #-}

{-# LINE 3 "libraries/unix/./System/Posix/Temp.hsc" #-}
{-# LANGUAGE Trustworthy #-}

{-# LINE 5 "libraries/unix/./System/Posix/Temp.hsc" #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.Temp
-- 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 (

    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.hsc" #-}

import System.IO
import System.Posix.IO
import System.Posix.Types
import Foreign.C


{-# LINE 39 "libraries/unix/./System/Posix/Temp.hsc" #-}
import System.Posix.Internals (withFilePath, peekFilePath)

{-# LINE 52 "libraries/unix/./System/Posix/Temp.hsc" #-}

-- |'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
-- the created file, which is padded with 6 random characters.
mkstemp :: String -> IO (FilePath, Handle)
mkstemp template = do

{-# LINE 60 "libraries/unix/./System/Posix/Temp.hsc" #-}
  withFilePath template $ \ ptr -> do
    fd <- throwErrnoIfMinus1 "mkstemp" (c_mkstemp ptr)
    name <- peekFilePath ptr
    h <- fdToHandle (Fd fd)
    return (name, h)

{-# LINE 82 "libraries/unix/./System/Posix/Temp.hsc" #-}

foreign import ccall unsafe "HsUnix.h __hscore_mkstemp"
  c_mkstemp :: CString -> IO CInt