{-# LANGUAGE CPP #-}
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
data TmpFs = TmpFs
{ TmpFs -> IORef (Map String String)
tmp_dirs_to_clean :: IORef (Map FilePath FilePath)
, TmpFs -> IORef Int
tmp_next_suffix :: IORef Int
, TmpFs -> IORef FilesToClean
tmp_files_to_clean :: IORef FilesToClean
}
data FilesToClean = FilesToClean
{ FilesToClean -> Set String
ftcGhcSession :: !(Set FilePath)
, FilesToClean -> Set String
ftcCurrentModule :: !(Set FilePath)
}
data TempFileLifetime
= TFL_CurrentModule
| TFL_GhcSession
deriving (Int -> TempFileLifetime -> ShowS
[TempFileLifetime] -> ShowS
TempFileLifetime -> String
(Int -> TempFileLifetime -> ShowS)
-> (TempFileLifetime -> String)
-> ([TempFileLifetime] -> ShowS)
-> Show TempFileLifetime
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)
emptyFilesToClean :: FilesToClean
emptyFilesToClean :: FilesToClean
emptyFilesToClean = Set String -> Set String -> FilesToClean
FilesToClean Set String
forall a. Set a
Set.empty Set String
forall a. Set a
Set.empty
mergeFilesToClean :: FilesToClean -> FilesToClean -> FilesToClean
mergeFilesToClean :: FilesToClean -> FilesToClean -> FilesToClean
mergeFilesToClean FilesToClean
x FilesToClean
y = FilesToClean
{ ftcGhcSession :: Set String
ftcGhcSession = Set String -> Set String -> Set String
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 = Set String -> Set String -> Set String
forall a. Ord a => Set a -> Set a -> Set a
Set.union (FilesToClean -> Set String
ftcCurrentModule FilesToClean
x) (FilesToClean -> Set String
ftcCurrentModule FilesToClean
y)
}
initTmpFs :: IO TmpFs
initTmpFs :: IO TmpFs
initTmpFs = do
IORef FilesToClean
files <- FilesToClean -> IO (IORef FilesToClean)
forall a. a -> IO (IORef a)
newIORef FilesToClean
emptyFilesToClean
IORef (Map String String)
dirs <- Map String String -> IO (IORef (Map String String))
forall a. a -> IO (IORef a)
newIORef Map String String
forall k a. Map k a
Map.empty
IORef Int
next <- Int -> IO (IORef Int)
forall a. a -> IO (IORef a)
newIORef Int
0
TmpFs -> IO TmpFs
forall (m :: * -> *) a. Monad m => a -> m a
return (TmpFs -> IO TmpFs) -> TmpFs -> IO TmpFs
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
}
forkTmpFsFrom :: TmpFs -> IO TmpFs
forkTmpFsFrom :: TmpFs -> IO TmpFs
forkTmpFsFrom TmpFs
old = do
IORef FilesToClean
files <- FilesToClean -> IO (IORef FilesToClean)
forall a. a -> IO (IORef a)
newIORef FilesToClean
emptyFilesToClean
TmpFs -> IO TmpFs
forall (m :: * -> *) a. Monad m => a -> m a
return (TmpFs -> IO TmpFs) -> TmpFs -> IO TmpFs
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
}
mergeTmpFsInto :: TmpFs -> TmpFs -> IO ()
mergeTmpFsInto :: TmpFs -> TmpFs -> IO ()
mergeTmpFsInto TmpFs
src TmpFs
dst = do
FilesToClean
src_files <- IORef FilesToClean
-> (FilesToClean -> (FilesToClean, FilesToClean))
-> IO FilesToClean
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))
IORef FilesToClean -> (FilesToClean -> (FilesToClean, ())) -> IO ()
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
= Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepTmpFiles DynFlags
dflags)
(IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ()
forall a. IO a -> IO a
mask_
(IO () -> IO ()) -> IO () -> IO ()
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 <- IORef (Map String String)
-> (Map String String -> (Map String String, Map String String))
-> IO (Map String String)
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef (Map String String)
ref ((Map String String -> (Map String String, Map String String))
-> IO (Map String String))
-> (Map String String -> (Map String String, Map String String))
-> IO (Map String String)
forall a b. (a -> b) -> a -> b
$ \Map String String
ds -> (Map String String
forall k a. Map k a
Map.empty, Map String String
ds)
Logger -> DynFlags -> [String] -> IO ()
removeTmpDirs Logger
logger DynFlags
dflags (Map String String -> [String]
forall k a. Map k a -> [a]
Map.elems Map String String
ds)
cleanTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanTempFiles Logger
logger TmpFs
tmpfs DynFlags
dflags
= Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepTmpFiles DynFlags
dflags)
(IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ()
forall a. IO a -> IO a
mask_
(IO () -> IO ()) -> IO () -> IO ()
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 <- IORef FilesToClean
-> (FilesToClean -> (FilesToClean, [String])) -> IO [String]
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef FilesToClean
ref ((FilesToClean -> (FilesToClean, [String])) -> IO [String])
-> (FilesToClean -> (FilesToClean, [String])) -> IO [String]
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
, Set String -> [String]
forall a. Set a -> [a]
Set.toList Set String
cm_files [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ Set String -> [String]
forall a. Set a -> [a]
Set.toList Set String
gs_files)
Logger -> DynFlags -> [String] -> IO ()
removeTmpFiles Logger
logger DynFlags
dflags [String]
to_delete
cleanCurrentModuleTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanCurrentModuleTempFiles :: Logger -> TmpFs -> DynFlags -> IO ()
cleanCurrentModuleTempFiles Logger
logger TmpFs
tmpfs DynFlags
dflags
= Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_KeepTmpFiles DynFlags
dflags)
(IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ()
forall a. IO a -> IO a
mask_
(IO () -> IO ()) -> IO () -> IO ()
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 <- IORef FilesToClean
-> (FilesToClean -> (FilesToClean, [String])) -> IO [String]
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef FilesToClean
ref ((FilesToClean -> (FilesToClean, [String])) -> IO [String])
-> (FilesToClean -> (FilesToClean, [String])) -> IO [String]
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 = Set String
forall a. Set a
Set.empty}, Set String -> [String]
forall a. Set a -> [a]
Set.toList Set String
cm_files)
Logger -> DynFlags -> [String] -> IO ()
removeTmpFiles Logger
logger DynFlags
dflags [String]
to_delete
addFilesToClean :: TmpFs -> TempFileLifetime -> [FilePath] -> IO ()
addFilesToClean :: TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
lifetime [String]
new_files = IORef FilesToClean -> (FilesToClean -> FilesToClean) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' (TmpFs -> IORef FilesToClean
tmp_files_to_clean TmpFs
tmpfs) ((FilesToClean -> FilesToClean) -> IO ())
-> (FilesToClean -> FilesToClean) -> IO ()
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 Set String -> Set String -> Set String
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 Set String -> Set String -> Set String
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 Set String -> Set String -> Set String
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 Set String -> Set String -> Set String
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 = [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList [String]
new_files
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
} <- IORef FilesToClean -> IO FilesToClean
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 String -> Set String -> Bool
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
newTempSuffix :: TmpFs -> IO Int
newTempSuffix :: TmpFs -> IO Int
newTempSuffix TmpFs
tmpfs =
IORef Int -> (Int -> (Int, Int)) -> IO Int
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' (TmpFs -> IORef Int
tmp_next_suffix TmpFs
tmpfs) ((Int -> (Int, Int)) -> IO Int) -> (Int -> (Int, Int)) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Int
n -> (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,Int
n)
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_")
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 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
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
TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
lifetime [String
filename]
String -> IO String
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 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
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
String -> IO String
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
let libname :: String
libname = String
prefix String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
filename :: String
filename = String
dir String -> ShowS
</> String
"lib" String -> ShowS
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
TmpFs -> TempFileLifetime -> [String] -> IO ()
addFilesToClean TmpFs
tmpfs TempFileLifetime
lifetime [String
filename]
(String, String, String) -> IO (String, String, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String
filename, String
dir, String
libname)
getTempDir :: Logger -> TmpFs -> DynFlags -> IO FilePath
getTempDir :: Logger -> TmpFs -> DynFlags -> IO String
getTempDir Logger
logger TmpFs
tmpfs DynFlags
dflags = do
Map String String
mapping <- IORef (Map String String) -> IO (Map String String)
forall a. IORef a -> IO a
readIORef IORef (Map String String)
dir_ref
case String -> Map String String -> Maybe String
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" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
pid String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"_"
IO String -> IO String
forall a. IO a -> IO a
mask_ (IO String -> IO String) -> IO String -> IO String
forall a b. (a -> b) -> a -> b
$ String -> IO String
mkTempDir String
prefix
Just String
dir -> String -> IO String
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 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
String -> IO ()
createDirectory String
our_dir
Maybe String
their_dir <- IORef (Map String String)
-> (Map String String -> (Map String String, Maybe String))
-> IO (Maybe String)
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef (Map String String)
dir_ref ((Map String String -> (Map String String, Maybe String))
-> IO (Maybe String))
-> (Map String String -> (Map String String, Maybe String))
-> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ \Map String String
mapping ->
case String -> Map String String -> Maybe String
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, String -> Maybe String
forall a. a -> Maybe a
Just String
dir)
Maybe String
Nothing -> (String -> String -> Map String String -> Map String String
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, Maybe String
forall a. Maybe a
Nothing)
case Maybe String
their_dir of
Maybe String
Nothing -> do
Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
2 (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"Created temporary directory:" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
our_dir
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
our_dir
Just String
dir -> do
String -> IO ()
removeDirectory String
our_dir
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
dir
IO String -> (IOException -> IO String) -> IO String
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 IOException -> IO String
forall a. IOException -> IO a
ioError IOException
e
removeTmpDirs :: Logger -> DynFlags -> [FilePath] -> IO ()
removeTmpDirs :: Logger -> DynFlags -> [String] -> IO ()
removeTmpDirs Logger
logger DynFlags
dflags [String]
ds
= Logger -> DynFlags -> String -> String -> IO () -> IO ()
forall a. Logger -> DynFlags -> String -> String -> IO a -> IO a
traceCmd Logger
logger DynFlags
dflags String
"Deleting temp dirs"
(String
"Deleting: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
ds)
((String -> IO ()) -> [String] -> IO ()
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 (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Logger -> DynFlags -> String -> String -> IO () -> IO ()
forall a. Logger -> DynFlags -> String -> String -> IO a -> IO a
traceCmd Logger
logger DynFlags
dflags String
"Deleting temp files"
(String
"Deleting: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
deletees)
((String -> IO ()) -> [String] -> IO ()
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
warnNon :: IO () -> IO ()
warnNon IO ()
act
| [String] -> Bool
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 ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
text [String]
non_deletees))
IO ()
act
([String]
non_deletees, [String]
deletees) = (String -> Bool) -> [String] -> ([String], [String])
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 IO () -> (IOException -> IO ()) -> IO ()
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 (IOException -> String
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)
foreign import ccall unsafe "_getpid" getProcessID :: IO Int
#else
getProcessID :: IO Int
getProcessID :: IO Int
getProcessID = IO CPid
System.Posix.Internals.c_getpid IO CPid -> (CPid -> IO Int) -> IO Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> (CPid -> Int) -> CPid -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CPid -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
#endif
withSystemTempDirectory :: String
-> (FilePath -> IO a)
-> IO a
withSystemTempDirectory :: forall a. String -> (String -> IO a) -> IO a
withSystemTempDirectory String
template String -> IO a
action =
IO String
getTemporaryDirectory IO String -> (String -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
tmpDir -> String -> String -> (String -> IO a) -> IO a
forall a. String -> String -> (String -> IO a) -> IO a
withTempDirectory String
tmpDir String
template String -> IO a
action
withTempDirectory :: FilePath
-> String
-> (FilePath -> IO a)
-> IO a
withTempDirectory :: forall a. String -> String -> (String -> IO a) -> IO a
withTempDirectory String
targetDir String
template =
IO String -> (String -> IO ()) -> (String -> IO a) -> IO a
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 (IO () -> IO ()) -> (String -> IO ()) -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
removeDirectoryRecursive)
ignoringIOErrors :: IO () -> IO ()
ignoringIOErrors :: IO () -> IO ()
ignoringIOErrors IO ()
ioe = IO ()
ioe IO () -> (IOException -> IO ()) -> IO ()
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` IO () -> IOException -> IO ()
forall a b. a -> b -> a
const (() -> IO ()
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 String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
x
String -> IO ()
createDirectory String
path
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
path
IO String -> (IOException -> IO String) -> IO String
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` \IOException
e -> if IOException -> Bool
isAlreadyExistsError IOException
e
then Int -> IO String
findTempName (Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) else IOException -> IO String
forall a. IOException -> IO a
ioError IOException
e