{-# LINE 1 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE PackageImports #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.Temp.PosixString
-- Copyright   :  (c) Volker Stolz <vs@foldr.org>
--                    Deian Stefan <deian@cs.stanford.edu>
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org, vs@foldr.org, deian@cs.stanford.edu
-- Stability   :  provisional
-- Portability :  non-portable (requires POSIX)
--
-- POSIX temporary file and directory creation functions.
--
-----------------------------------------------------------------------------

module System.Posix.Temp.PosixString (
        mkstemp, mkstemps, mkdtemp
    ) where




{-# LINE 25 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
import qualified "os-string" System.OsString.Data.ByteString.Short as BC

{-# LINE 29 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
import Data.Word

import Foreign.C

import System.OsPath.Types
import System.IO
import System.Posix.PosixPath.FilePath
import System.OsString.Internal.Types (PosixString(..))

{-# LINE 40 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
import System.Posix.IO.PosixString
import System.Posix.Types


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


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

foreign import capi unsafe "HsUnix.h mkstemp"
  c_mkstemp :: CString -> IO CInt

-- | Make a unique filename and open it for reading\/writing. The returned
-- 'PosixPath' is the (possibly relative) path of the created file, which is
-- padded with 6 random characters. The argument is the desired prefix of the
-- filepath of the temporary file to be created.
--
-- If you aren't using GHC or Hugs then this function simply wraps mktemp and
-- so shouldn't be considered safe.
mkstemp :: PosixString -> IO (PosixPath, Handle)
mkstemp :: PosixString -> IO (PosixString, Handle)
mkstemp (PosixString ShortByteString
template') = do
  let template :: PosixString
template = ShortByteString -> PosixString
PosixString (ShortByteString -> PosixString) -> ShortByteString -> PosixString
forall a b. (a -> b) -> a -> b
$ ShortByteString
template' ShortByteString -> ShortByteString -> ShortByteString
`BC.append` ([Word8] -> ShortByteString
BC.pack [Word8
_X,Word8
_X,Word8
_X,Word8
_X,Word8
_X,Word8
_X])
  PosixString
-> (CString -> IO (PosixString, Handle))
-> IO (PosixString, Handle)
forall a. PosixString -> (CString -> IO a) -> IO a
withFilePath PosixString
template ((CString -> IO (PosixString, Handle)) -> IO (PosixString, Handle))
-> (CString -> IO (PosixString, Handle))
-> IO (PosixString, Handle)
forall a b. (a -> b) -> a -> b
$ \ CString
ptr -> do
    fd <- String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 String
"mkstemp" (CString -> IO CInt
c_mkstemp CString
ptr)
    name <- peekFilePath ptr
    h <- fdToHandle (Fd fd)
    return (name, h)


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


{-# LINE 78 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
foreign import capi unsafe "HsUnix.h mkstemps"
  c_mkstemps :: CString -> CInt -> IO CInt

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

-- |'mkstemps' - make a unique filename with a given prefix and suffix
-- and open it for reading\/writing (only safe on GHC & Hugs).
-- The returned 'PosixPath' is the (possibly relative) path of
-- the created file, which contains  6 random characters in between
-- the prefix and suffix.
mkstemps :: PosixString -> PosixString -> IO (PosixPath, Handle)

mkstemps :: PosixString -> PosixString -> IO (PosixString, Handle)
{-# LINE 89 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
mkstemps (PosixString prefix) (PosixString suffix) = do
  let template = PosixString $ prefix `BC.append` (BC.pack [_X,_X,_X,_X,_X,_X]) `BC.append` suffix
      lenOfsuf = (fromIntegral $ BC.length suffix) :: CInt
  withFilePath template $ \ ptr -> do
    fd <- throwErrnoIfMinus1 "mkstemps" (c_mkstemps ptr lenOfsuf)
    name <- peekFilePath ptr
    h <- fdToHandle (Fd fd)
    return (name, h)

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


{-# LINE 102 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
foreign import capi unsafe "HsUnix.h mkdtemp"
  c_mkdtemp :: CString -> IO CString

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

-- | Make a unique directory. The returned 'PosixPath' is the path of the
-- 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.
--
-- If you aren't using GHC or Hugs then this function simply wraps mktemp and
-- so shouldn't be considered safe.
mkdtemp :: PosixString -> IO PosixPath
mkdtemp :: PosixString -> IO PosixString
mkdtemp (PosixString ShortByteString
template') = do
  let template :: PosixString
template = ShortByteString -> PosixString
PosixString (ShortByteString -> PosixString) -> ShortByteString -> PosixString
forall a b. (a -> b) -> a -> b
$ ShortByteString
template' ShortByteString -> ShortByteString -> ShortByteString
`BC.append` ([Word8] -> ShortByteString
BC.pack [Word8
_X,Word8
_X,Word8
_X,Word8
_X,Word8
_X,Word8
_X])

{-# LINE 116 "libraries/unix/System/Posix/Temp/PosixString.hsc" #-}
  withFilePath template $ \ ptr -> do
    _ <- throwErrnoIfNull "mkdtemp" (c_mkdtemp ptr)
    name <- peekFilePath ptr
    return name

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


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

_X :: Word8
_X :: Word8
_X = Word8
0x58