{-# LANGUAGE CPP #-}

-- | Temporary file-system management
module GHC.Utils.TmpFs
    ( TmpFs
    , initTmpFs
    , forkTmpFsFrom
    , mergeTmpFsInto
    , FilesToClean(..)
    , emptyFilesToClean
    , TempFileLifetime(..)
    , cleanTempDirs
    , cleanTempFiles
    , cleanCurrentModuleTempFiles
    , addFilesToClean
    , changeTempFilesLifetime
    , newTempName
    , newTempLibName
    , newTempDir
    , withSystemTempDirectory
    , withTempDirectory
    )
where

import GHC.Prelude

import GHC.Driver.Session
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Logger
import GHC.Utils.Misc
import GHC.Utils.Exception as Exception
import GHC.Driver.Phases

import Control.Monad
import Data.List (partition)
import qualified Data.Set as Set
import Data.Set (Set)
import qualified Data.Map as Map
import Data.Map (Map)
import Data.IORef
import System.Directory
import System.FilePath
import System.IO.Error

#if !defined(mingw32_HOST_OS)
import qualified System.Posix.Internals
#endif

-- | Temporary file-system
data TmpFs = TmpFs
  { TmpFs -> IORef (Map String String)
tmp_dirs_to_clean :: IORef (Map FilePath FilePath)
      -- ^ Maps system temporary directory (passed via settings or DynFlags) to
      -- an actual temporary directory for this process.
      --
      -- It's a Map probably to support changing the system temporary directory
      -- over time.
      --
      -- Shared with forked TmpFs.

  , TmpFs -> IORef Int
tmp_next_suffix :: IORef Int
      -- ^ The next available suffix to uniquely name a temp file, updated
      -- atomically.
      --
      -- Shared with forked TmpFs.

  , TmpFs -> IORef FilesToClean
tmp_files_to_clean :: IORef FilesToClean
      -- ^ Files to clean (per session or per module)
      --
      -- Not shared with forked TmpFs.
  }

-- | A collection of files that must be deleted before ghc exits.
data FilesToClean = FilesToClean
    { FilesToClean -> Set String
ftcGhcSession :: !(Set FilePath)
        -- ^ Files that will be deleted at the end of runGhc(T)

    , FilesToClean -> Set String
ftcCurrentModule :: !(Set FilePath)
        -- ^ Files that will be deleted the next time
        -- 'cleanCurrentModuleTempFiles' is called, or otherwise at the end of
        -- the session.
    }

-- | Used when a temp file is created. This determines which component Set of
-- FilesToClean will get the temp file
data TempFileLifetime
  = TFL_CurrentModule
  -- ^ A file with lifetime TFL_CurrentModule will be cleaned up at the
  -- end of upweep_mod
  | TFL_GhcSession
  -- ^ A file with lifetime TFL_GhcSession will be cleaned up at the end of
  -- runGhc(T)
  deriving (Int -> TempFileLifetime -> ShowS
[TempFileLifetime] -> ShowS
TempFileLifetime -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TempFileLifetime] -> ShowS
$cshowList :: [TempFileLifetime] -> ShowS
show :: TempFileLifetime -> String
$cshow :: TempFileLifetime -> String
showsPrec :: Int -> TempFileLifetime -> ShowS
$cshowsPrec :: Int -> TempFileLifetime -> ShowS
Show)


-- | An empty FilesToClean
emptyFilesToClean :: FilesToClean
emptyFilesToClean :: FilesToClean
emptyFilesToClean = Set String -> Set String -> FilesToClean
FilesToClean forall a. Set a
Set.empty forall a. Set a
Set.empty

-- | Merge two FilesToClean
mergeFilesToClean :: FilesToClean -> FilesToClean -> FilesToClean
mergeFilesToClean :: FilesToClean -> FilesToClean -> FilesToClean
mergeFilesToClean FilesToClean
x FilesToClean
y = FilesToClean
    { ftcGhcSession :: Set String
ftcGhcSession    = forall a. Ord a => Set a -> Set a -> Set a
Set.union (FilesToClean -> Set String
ftcGhcSession FilesToClean
x) (FilesToClean -> Set String
ftcGhcSession FilesToClean
y)
    , ftcCurrentModule :: Set String
ftcCurrentModule = forall a. Ord a => Set a -> Set a -> Set a
Set.union (FilesToClean -> Set String
ftcCurrentModule FilesToClean
x) (FilesToClean -> Set String
ftcCurrentModule FilesToClean
y)
    }

-- | Initialise an empty TmpFs
initTmpFs :: IO TmpFs
initTmpFs :: IO TmpFs
initTmpFs = do
    IORef FilesToClean
files <- forall a. a -> IO (IORef a)
newIORef FilesToClean
emptyFilesToClean
    IORef (Map String String)
dirs  <- forall a. a -> IO (IORef a)
newIORef forall k a. Map k a
Map.empty
    IORef Int
next  <- forall a. a -> IO (IORef a)
newIORef Int
0
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TmpFs
        { tmp_files_to_clean :: IORef FilesToClean
tmp_files_to_clean = IORef FilesToClean
files
        , tmp_dirs_to_clean :: IORef (Map String String)
tmp_dirs_to_clean  = IORef (Map String String)
dirs
        , tmp_next_suffix :: IORef Int
tmp_next_suffix    = IORef Int
next
        }

-- | Initialise an empty TmpFs sharing unique numbers and per-process temporary
-- directories with the given TmpFs
forkTmpFsFrom :: TmpFs -> IO TmpFs
forkTmpFsFrom :: TmpFs -> IO TmpFs
forkTmpFsFrom TmpFs
old = do
    IORef FilesToClean
files <- forall a. a -> IO (IORef a)
newIORef FilesToClean
emptyFilesToClean
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TmpFs
        { tmp_files_to_clean :: IORef FilesToClean
tmp_files_to_clean = IORef FilesToClean
files
        , tmp_dirs_to_clean :: IORef (Map String String)
tmp_dirs_to_clean  = TmpFs -> IORef (Map String String)
tmp_dirs_to_clean TmpFs
old
        , tmp_next_suffix :: IORef Int
tmp_next_suffix    = TmpFs -> IORef Int
tmp_next_suffix TmpFs
old
        }

-- | Merge the first TmpFs into the second.
--
-- The first TmpFs is returned emptied.
mergeTmpFsInto :: TmpFs -> TmpFs -> IO ()
mergeTmpFsInto :: TmpFs -> TmpFs -> IO ()
mergeTmpFsInto TmpFs
src TmpFs
dst = do
    FilesToClean
src_files <- forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' (TmpFs -> IORef FilesToClean
tmp_files_to_clean TmpFs
src) (\FilesToClean
s -> (FilesToClean
emptyFilesToClean, FilesToClean
s))
    forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' (TmpFs -> IORef FilesToClean
tmp_files_to_clean TmpFs
dst) (\FilesToClean
s -> (FilesToClean -> FilesToClean -> FilesToClean
mergeFilesToClean FilesToClean
src_files FilesToClean
s, ()))

cleanTempDirs :: Logger -> TmpFs -> DynFlags -> IO ()
cleanTempDirs :: Logger -> TmpFs -> DynFlags -> IO ()
cleanTempDirs Logger
logger TmpFs
tmpfs DynFlags
dflags
   = forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepTmpFiles DynFlags
dflags)
   forall a b. (a -> b) -> a -> b
$ forall a. IO a -> IO a
mask_
   forall a b. (a -> b) -> a -> b
$ do let ref :: IORef (Map String String)
ref = TmpFs -> IORef (Map String String)
tmp_dirs_to_clean TmpFs
tmpfs
        Map String String
ds <- forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef (Map String String)
ref forall a b. (a -> b) -> a -> b
$ \Map String String
ds -> (forall k a. Map k a
Map.empty, Map String String
ds)
        Logger -> DynFlags -> [String] -> IO ()
removeTmpDirs Logger
logger DynFlags
dflags (forall k a. Map k a -> [a]
Map.elems Map String String
ds)

-- | Delete all files in @tmp_files_to_clean@.
cleanTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanTempFiles Logger
logger TmpFs
tmpfs DynFlags
dflags
   = forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepTmpFiles DynFlags
dflags)
   forall a b. (a -> b) -> a -> b
$ forall a. IO a -> IO a
mask_
   forall a b. (a -> b) -> a -> b
$ do let ref :: IORef FilesToClean
ref = TmpFs -> IORef FilesToClean
tmp_files_to_clean TmpFs
tmpfs
        [String]
to_delete <- forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef FilesToClean
ref forall a b. (a -> b) -> a -> b
$
            \FilesToClean
                { ftcCurrentModule :: FilesToClean -> Set String
ftcCurrentModule = Set String
cm_files
                , ftcGhcSession :: FilesToClean -> Set String
ftcGhcSession = Set String
gs_files
                } -> ( FilesToClean
emptyFilesToClean
                     , forall a. Set a -> [a]
Set.toList Set String
cm_files forall a. [a] -> [a] -> [a]
++ forall a. Set a -> [a]
Set.toList Set String
gs_files)
        Logger -> DynFlags -> [String] -> IO ()
removeTmpFiles Logger
logger DynFlags
dflags [String]
to_delete

-- | Delete all files in @tmp_files_to_clean@. That have lifetime
-- TFL_CurrentModule.
-- If a file must be cleaned eventually, but must survive a
-- cleanCurrentModuleTempFiles, ensure it has lifetime TFL_GhcSession.
cleanCurrentModuleTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanCurrentModuleTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanCurrentModuleTempFiles Logger
logger TmpFs
tmpfs DynFlags
dflags
   = forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepTmpFiles DynFlags
dflags)
   forall a b. (a -> b) -> a -> b
$ forall a. IO a -> IO a
mask_
   forall a b. (a -> b) -> a -> b
$ do let ref :: IORef FilesToClean
ref = TmpFs -> IORef FilesToClean
tmp_files_to_clean TmpFs
tmpfs
        [String]
to_delete <- forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef FilesToClean
ref forall a b. (a -> b) -> a -> b
$
            \ftc :: FilesToClean
ftc@FilesToClean{ftcCurrentModule :: FilesToClean -> Set String
ftcCurrentModule = Set String
cm_files} ->
                (FilesToClean
ftc {ftcCurrentModule :: Set String
ftcCurrentModule = forall a. Set a
Set.empty}, forall a. Set a -> [a]
Set.toList Set String
cm_files)
        Logger -> DynFlags -> [String] -> IO ()
removeTmpFiles Logger
logger DynFlags
dflags [String]
to_delete

-- | Ensure that new_files are cleaned on the next call of
-- 'cleanTempFiles' or 'cleanCurrentModuleTempFiles', depending on lifetime.
-- If any of new_files are already tracked, they will have their lifetime
-- updated.
addFilesToClean :: TmpFs -> TempFileLifetime -> [FilePath] -> IO ()
addFilesToClean :: TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
lifetime [String]
new_files = forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (TmpFs -> IORef FilesToClean
tmp_files_to_clean TmpFs
tmpfs) forall a b. (a -> b) -> a -> b
$
  \FilesToClean
    { ftcCurrentModule :: FilesToClean -> Set String
ftcCurrentModule = Set String
cm_files
    , ftcGhcSession :: FilesToClean -> Set String
ftcGhcSession = Set String
gs_files
    } -> case TempFileLifetime
lifetime of
      TempFileLifetime
TFL_CurrentModule -> FilesToClean
        { ftcCurrentModule :: Set String
ftcCurrentModule = Set String
cm_files forall a. Ord a => Set a -> Set a -> Set a
`Set.union` Set String
new_files_set
        , ftcGhcSession :: Set String
ftcGhcSession = Set String
gs_files forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` Set String
new_files_set
        }
      TempFileLifetime
TFL_GhcSession -> FilesToClean
        { ftcCurrentModule :: Set String
ftcCurrentModule = Set String
cm_files forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` Set String
new_files_set
        , ftcGhcSession :: Set String
ftcGhcSession = Set String
gs_files forall a. Ord a => Set a -> Set a -> Set a
`Set.union` Set String
new_files_set
        }
  where
    new_files_set :: Set String
new_files_set = forall a. Ord a => [a] -> Set a
Set.fromList [String]
new_files

-- | Update the lifetime of files already being tracked. If any files are
-- not being tracked they will be discarded.
changeTempFilesLifetime :: TmpFs -> TempFileLifetime -> [FilePath] -> IO ()
changeTempFilesLifetime :: TmpFs -> TempFileLifetime -> [String] -> IO ()
changeTempFilesLifetime TmpFs
tmpfs TempFileLifetime
lifetime [String]
files = do
  FilesToClean
    { ftcCurrentModule :: FilesToClean -> Set String
ftcCurrentModule = Set String
cm_files
    , ftcGhcSession :: FilesToClean -> Set String
ftcGhcSession = Set String
gs_files
    } <- forall a. IORef a -> IO a
readIORef (TmpFs -> IORef FilesToClean
tmp_files_to_clean TmpFs
tmpfs)
  let old_set :: Set String
old_set = case TempFileLifetime
lifetime of
        TempFileLifetime
TFL_CurrentModule -> Set String
gs_files
        TempFileLifetime
TFL_GhcSession -> Set String
cm_files
      existing_files :: [String]
existing_files = [String
f | String
f <- [String]
files, String
f forall a. Ord a => a -> Set a -> Bool
`Set.member` Set String
old_set]
  TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
lifetime [String]
existing_files

-- Return a unique numeric temp file suffix
newTempSuffix :: TmpFs -> IO Int
newTempSuffix :: TmpFs -> IO Int
newTempSuffix TmpFs
tmpfs =
  forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' (TmpFs -> IORef Int
tmp_next_suffix TmpFs
tmpfs) forall a b. (a -> b) -> a -> b
$ \Int
n -> (Int
nforall a. Num a => a -> a -> a
+Int
1,Int
n)

-- Find a temporary name that doesn't already exist.
newTempName :: Logger -> TmpFs -> DynFlags -> TempFileLifetime -> Suffix -> IO FilePath
newTempName :: Logger
-> TmpFs -> DynFlags -> TempFileLifetime -> String -> IO String
newTempName Logger
logger TmpFs
tmpfs DynFlags
dflags TempFileLifetime
lifetime String
extn
  = do String
d <- Logger -> TmpFs -> DynFlags -> IO String
getTempDir Logger
logger TmpFs
tmpfs DynFlags
dflags
       String -> IO String
findTempName (String
d String -> ShowS
</> String
"ghc_") -- See Note [Deterministic base name]
  where
    findTempName :: FilePath -> IO FilePath
    findTempName :: String -> IO String
findTempName String
prefix
      = do Int
n <- TmpFs -> IO Int
newTempSuffix TmpFs
tmpfs
           let filename :: String
filename = String
prefix forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n String -> ShowS
<.> String
extn
           Bool
b <- String -> IO Bool
doesFileExist String
filename
           if Bool
b then String -> IO String
findTempName String
prefix
                else do -- clean it up later
                        TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
lifetime [String
filename]
                        forall (m :: * -> *) a. Monad m => a -> m a
return String
filename

newTempDir :: Logger -> TmpFs -> DynFlags -> IO FilePath
newTempDir :: Logger -> TmpFs -> DynFlags -> IO String
newTempDir Logger
logger TmpFs
tmpfs DynFlags
dflags
  = do String
d <- Logger -> TmpFs -> DynFlags -> IO String
getTempDir Logger
logger TmpFs
tmpfs DynFlags
dflags
       String -> IO String
findTempDir (String
d String -> ShowS
</> String
"ghc_")
  where
    findTempDir :: FilePath -> IO FilePath
    findTempDir :: String -> IO String
findTempDir String
prefix
      = do Int
n <- TmpFs -> IO Int
newTempSuffix TmpFs
tmpfs
           let filename :: String
filename = String
prefix forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
           Bool
b <- String -> IO Bool
doesDirectoryExist String
filename
           if Bool
b then String -> IO String
findTempDir String
prefix
                else do String -> IO ()
createDirectory String
filename
                        -- see mkTempDir below; this is wrong: -> consIORef (tmp_dirs_to_clean tmpfs) filename
                        forall (m :: * -> *) a. Monad m => a -> m a
return String
filename

newTempLibName :: Logger -> TmpFs -> DynFlags -> TempFileLifetime -> Suffix
  -> IO (FilePath, FilePath, String)
newTempLibName :: Logger
-> TmpFs
-> DynFlags
-> TempFileLifetime
-> String
-> IO (String, String, String)
newTempLibName Logger
logger TmpFs
tmpfs DynFlags
dflags TempFileLifetime
lifetime String
extn
  = do String
d <- Logger -> TmpFs -> DynFlags -> IO String
getTempDir Logger
logger TmpFs
tmpfs DynFlags
dflags
       String -> String -> IO (String, String, String)
findTempName String
d (String
"ghc_")
  where
    findTempName :: FilePath -> String -> IO (FilePath, FilePath, String)
    findTempName :: String -> String -> IO (String, String, String)
findTempName String
dir String
prefix
      = do Int
n <- TmpFs -> IO Int
newTempSuffix TmpFs
tmpfs -- See Note [Deterministic base name]
           let libname :: String
libname = String
prefix forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
               filename :: String
filename = String
dir String -> ShowS
</> String
"lib" forall a. [a] -> [a] -> [a]
++ String
libname String -> ShowS
<.> String
extn
           Bool
b <- String -> IO Bool
doesFileExist String
filename
           if Bool
b then String -> String -> IO (String, String, String)
findTempName String
dir String
prefix
                else do -- clean it up later
                        TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
lifetime [String
filename]
                        forall (m :: * -> *) a. Monad m => a -> m a
return (String
filename, String
dir, String
libname)


-- Return our temporary directory within tmp_dir, creating one if we
-- don't have one yet.
getTempDir :: Logger -> TmpFs -> DynFlags -> IO FilePath
getTempDir :: Logger -> TmpFs -> DynFlags -> IO String
getTempDir Logger
logger TmpFs
tmpfs DynFlags
dflags = do
    Map String String
mapping <- forall a. IORef a -> IO a
readIORef IORef (Map String String)
dir_ref
    case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup String
tmp_dir Map String String
mapping of
        Maybe String
Nothing -> do
            Int
pid <- IO Int
getProcessID
            let prefix :: String
prefix = String
tmp_dir String -> ShowS
</> String
"ghc" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
pid forall a. [a] -> [a] -> [a]
++ String
"_"
            forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ String -> IO String
mkTempDir String
prefix
        Just String
dir -> forall (m :: * -> *) a. Monad m => a -> m a
return String
dir
  where
    tmp_dir :: String
tmp_dir = DynFlags -> String
tmpDir DynFlags
dflags
    dir_ref :: IORef (Map String String)
dir_ref = TmpFs -> IORef (Map String String)
tmp_dirs_to_clean TmpFs
tmpfs

    mkTempDir :: FilePath -> IO FilePath
    mkTempDir :: String -> IO String
mkTempDir String
prefix = do
        Int
n <- TmpFs -> IO Int
newTempSuffix TmpFs
tmpfs
        let our_dir :: String
our_dir = String
prefix forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n

        -- 1. Speculatively create our new directory.
        String -> IO ()
createDirectory String
our_dir

        -- 2. Update the tmp_dirs_to_clean mapping unless an entry already exists
        -- (i.e. unless another thread beat us to it).
        Maybe String
their_dir <- forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef (Map String String)
dir_ref forall a b. (a -> b) -> a -> b
$ \Map String String
mapping ->
            case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup String
tmp_dir Map String String
mapping of
                Just String
dir -> (Map String String
mapping, forall a. a -> Maybe a
Just String
dir)
                Maybe String
Nothing  -> (forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert String
tmp_dir String
our_dir Map String String
mapping, forall a. Maybe a
Nothing)

        -- 3. If there was an existing entry, return it and delete the
        -- directory we created.  Otherwise return the directory we created.
        case Maybe String
their_dir of
            Maybe String
Nothing  -> do
                Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
2 forall a b. (a -> b) -> a -> b
$
                    String -> SDoc
text String
"Created temporary directory:" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
our_dir
                forall (m :: * -> *) a. Monad m => a -> m a
return String
our_dir
            Just String
dir -> do
                String -> IO ()
removeDirectory String
our_dir
                forall (m :: * -> *) a. Monad m => a -> m a
return String
dir
      forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` \IOException
e -> if IOException -> Bool
isAlreadyExistsError IOException
e
                      then String -> IO String
mkTempDir String
prefix else forall a. IOException -> IO a
ioError IOException
e

{- Note [Deterministic base name]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

The filename of temporary files, especially the basename of C files, can end
up in the output in some form, e.g. as part of linker debug information. In the
interest of bit-wise exactly reproducible compilation (#4012), the basename of
the temporary file no longer contains random information (it used to contain
the process id).

This is ok, as the temporary directory used contains the pid (see getTempDir).
-}
removeTmpDirs :: Logger -> DynFlags -> [FilePath] -> IO ()
removeTmpDirs :: Logger -> DynFlags -> [String] -> IO ()
removeTmpDirs Logger
logger DynFlags
dflags [String]
ds
  = forall a. Logger -> DynFlags -> String -> String -> IO a -> IO a
traceCmd Logger
logger DynFlags
dflags String
"Deleting temp dirs"
             (String
"Deleting: " forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
ds)
             (forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Logger -> DynFlags -> (String -> IO ()) -> String -> IO ()
removeWith Logger
logger DynFlags
dflags String -> IO ()
removeDirectory) [String]
ds)

removeTmpFiles :: Logger -> DynFlags -> [FilePath] -> IO ()
removeTmpFiles :: Logger -> DynFlags -> [String] -> IO ()
removeTmpFiles Logger
logger DynFlags
dflags [String]
fs
  = IO () -> IO ()
warnNon forall a b. (a -> b) -> a -> b
$
    forall a. Logger -> DynFlags -> String -> String -> IO a -> IO a
traceCmd Logger
logger DynFlags
dflags String
"Deleting temp files"
             (String
"Deleting: " forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
deletees)
             (forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Logger -> DynFlags -> (String -> IO ()) -> String -> IO ()
removeWith Logger
logger DynFlags
dflags String -> IO ()
removeFile) [String]
deletees)
  where
     -- Flat out refuse to delete files that are likely to be source input
     -- files (is there a worse bug than having a compiler delete your source
     -- files?)
     --
     -- Deleting source files is a sign of a bug elsewhere, so prominently flag
     -- the condition.
    warnNon :: IO () -> IO ()
warnNon IO ()
act
     | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
non_deletees = IO ()
act
     | Bool
otherwise         = do
        Logger -> DynFlags -> SDoc -> IO ()
putMsg Logger
logger DynFlags
dflags (String -> SDoc
text String
"WARNING - NOT deleting source files:"
                       SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
hsep (forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
text [String]
non_deletees))
        IO ()
act

    ([String]
non_deletees, [String]
deletees) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition String -> Bool
isHaskellUserSrcFilename [String]
fs

removeWith :: Logger -> DynFlags -> (FilePath -> IO ()) -> FilePath -> IO ()
removeWith :: Logger -> DynFlags -> (String -> IO ()) -> String -> IO ()
removeWith Logger
logger DynFlags
dflags String -> IO ()
remover String
f = String -> IO ()
remover String
f forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO`
  (\IOException
e ->
   let msg :: SDoc
msg = if IOException -> Bool
isDoesNotExistError IOException
e
             then String -> SDoc
text String
"Warning: deleting non-existent" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
f
             else String -> SDoc
text String
"Warning: exception raised when deleting"
                                            SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
f SDoc -> SDoc -> SDoc
<> SDoc
colon
               SDoc -> SDoc -> SDoc
$$ String -> SDoc
text (forall a. Show a => a -> String
show IOException
e)
   in Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
2 SDoc
msg
  )

#if defined(mingw32_HOST_OS)
-- relies on Int == Int32 on Windows
foreign import ccall unsafe "_getpid" getProcessID :: IO Int
#else
getProcessID :: IO Int
getProcessID :: IO Int
getProcessID = IO CPid
System.Posix.Internals.c_getpid forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
#endif

-- The following three functions are from the `temporary` package.

-- | Create and use a temporary directory in the system standard temporary
-- directory.
--
-- Behaves exactly the same as 'withTempDirectory', except that the parent
-- temporary directory will be that returned by 'getTemporaryDirectory'.
withSystemTempDirectory :: String   -- ^ Directory name template. See 'openTempFile'.
                        -> (FilePath -> IO a) -- ^ Callback that can use the directory
                        -> IO a
withSystemTempDirectory :: forall a. String -> (String -> IO a) -> IO a
withSystemTempDirectory String
template String -> IO a
action =
  IO String
getTemporaryDirectory forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
tmpDir -> forall a. String -> String -> (String -> IO a) -> IO a
withTempDirectory String
tmpDir String
template String -> IO a
action


-- | Create and use a temporary directory.
--
-- Creates a new temporary directory inside the given directory, making use
-- of the template. The temp directory is deleted after use. For example:
--
-- > withTempDirectory "src" "sdist." $ \tmpDir -> do ...
--
-- The @tmpDir@ will be a new subdirectory of the given directory, e.g.
-- @src/sdist.342@.
withTempDirectory :: FilePath -- ^ Temp directory to create the directory in
                  -> String   -- ^ Directory name template. See 'openTempFile'.
                  -> (FilePath -> IO a) -- ^ Callback that can use the directory
                  -> IO a
withTempDirectory :: forall a. String -> String -> (String -> IO a) -> IO a
withTempDirectory String
targetDir String
template =
  forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exception.bracket
    (String -> String -> IO String
createTempDirectory String
targetDir String
template)
    (IO () -> IO ()
ignoringIOErrors forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
removeDirectoryRecursive)

ignoringIOErrors :: IO () -> IO ()
ignoringIOErrors :: IO () -> IO ()
ignoringIOErrors IO ()
ioe = IO ()
ioe forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return ())


createTempDirectory :: FilePath -> String -> IO FilePath
createTempDirectory :: String -> String -> IO String
createTempDirectory String
dir String
template = do
  Int
pid <- IO Int
getProcessID
  Int -> IO String
findTempName Int
pid
  where findTempName :: Int -> IO String
findTempName Int
x = do
            let path :: String
path = String
dir String -> ShowS
</> String
template forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
x
            String -> IO ()
createDirectory String
path
            forall (m :: * -> *) a. Monad m => a -> m a
return String
path
          forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` \IOException
e -> if IOException -> Bool
isAlreadyExistsError IOException
e
                          then Int -> IO String
findTempName (Int
xforall a. Num a => a -> a -> a
+Int
1) else forall a. IOException -> IO a
ioError IOException
e