{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
module Hakyll.Core.Util.File
( makeDirectories
, getRecursiveContents
, removeDirectory
) where
import Control.Concurrent (threadDelay)
import Control.Exception (SomeException, catch)
import Control.Monad (filterM, forM, when)
import System.Directory (createDirectoryIfMissing,
doesDirectoryExist, getDirectoryContents,
removeDirectoryRecursive, removePathForcibly)
import System.FilePath (takeDirectory, (</>))
makeDirectories :: FilePath -> IO ()
makeDirectories :: FilePath -> IO ()
makeDirectories = Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True (FilePath -> IO ()) -> (FilePath -> FilePath) -> FilePath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDirectory
getRecursiveContents :: (FilePath -> IO Bool)
-> FilePath
-> IO [FilePath]
getRecursiveContents :: (FilePath -> IO Bool) -> FilePath -> IO [FilePath]
getRecursiveContents FilePath -> IO Bool
ignore FilePath
top = FilePath -> IO [FilePath]
go FilePath
""
where
isProper :: FilePath -> IO Bool
isProper FilePath
x
| FilePath
x FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath
".", FilePath
".."] = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
| Bool
otherwise = Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO Bool
ignore FilePath
x
go :: FilePath -> IO [FilePath]
go FilePath
dir = do
Bool
dirExists <- FilePath -> IO Bool
doesDirectoryExist (FilePath
top FilePath -> FilePath -> FilePath
</> FilePath
dir)
if Bool -> Bool
not Bool
dirExists
then [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return []
else do
[FilePath]
names <- (FilePath -> IO Bool) -> [FilePath] -> IO [FilePath]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM FilePath -> IO Bool
isProper ([FilePath] -> IO [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< FilePath -> IO [FilePath]
getDirectoryContents (FilePath
top FilePath -> FilePath -> FilePath
</> FilePath
dir)
[[FilePath]]
paths <- [FilePath] -> (FilePath -> IO [FilePath]) -> IO [[FilePath]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [FilePath]
names ((FilePath -> IO [FilePath]) -> IO [[FilePath]])
-> (FilePath -> IO [FilePath]) -> IO [[FilePath]]
forall a b. (a -> b) -> a -> b
$ \FilePath
name -> do
let rel :: FilePath
rel = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
name
Bool
isDirectory <- FilePath -> IO Bool
doesDirectoryExist (FilePath
top FilePath -> FilePath -> FilePath
</> FilePath
rel)
if Bool
isDirectory
then FilePath -> IO [FilePath]
go FilePath
rel
else [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath
rel]
[FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[FilePath]]
paths
removeDirectory :: FilePath -> IO ()
#ifndef mingw32_HOST_OS
removeDirectory :: FilePath -> IO ()
removeDirectory FilePath
fp = do
Bool
e <- FilePath -> IO Bool
doesDirectoryExist FilePath
fp
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
e (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
removeDirectoryRecursive FilePath
fp
#else
removeDirectory = retryWithDelay 10 . removePathForcibly
#endif
retryWithDelay :: Int -> IO a -> IO a
retryWithDelay :: Int -> IO a -> IO a
retryWithDelay Int
i IO a
x
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = FilePath -> IO a
forall a. HasCallStack => FilePath -> a
error FilePath
"Hakyll.Core.Util.File.retry: retry count must be 1 or more"
| Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = IO a
x
| Bool
otherwise = IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch IO a
x ((SomeException -> IO a) -> IO a)
-> (SomeException -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \(SomeException
_::SomeException) -> Int -> IO ()
threadDelay Int
100 IO () -> IO a -> IO a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> IO a -> IO a
forall a. Int -> IO a -> IO a
retryWithDelay (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) IO a
x