{-# LANGUAGE OverloadedStrings #-}
module System.Directory.Extra
( copyDirectoryRecursive
, copyFile'
, copyTemplate
)
where
import Control.Monad ( filterM, forM_ )
import qualified Control.Exception as E
import Data.Aeson ( Value (..) )
import qualified Data.ByteString.Lazy as B
import Data.Text.Lazy ( pack, unpack )
import Data.Text.Lazy.Encoding ( encodeUtf8 )
import Distribution.Simple.Utils ( getDirectoryContentsRecursive )
import System.Directory ( copyFile,
createDirectoryIfMissing,
doesFileExist )
import System.Exit ( ExitCode (ExitFailure), exitWith )
import System.FilePath ( makeRelative, splitFileName,
takeDirectory, (</>) )
import System.IO ( hPutStrLn, stderr )
import Text.Microstache ( compileMustacheFile,
compileMustacheText,
renderMustache )
{-# DEPRECATED copyDirectoryRecursive "This function is deprecated in ogma-extra-1.6.0." #-}
copyDirectoryRecursive :: FilePath
-> FilePath
-> IO ()
copyDirectoryRecursive :: FilePath -> FilePath -> IO ()
copyDirectoryRecursive FilePath
sourceDir FilePath
targetDir =
(SomeException -> IO ()) -> IO () -> IO ()
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
E.handle (FilePath -> FilePath -> SomeException -> IO ()
copyDirectoryRecursiveErrorHandler FilePath
sourceDir FilePath
targetDir) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
[FilePath]
files <- FilePath -> IO [FilePath]
getDirectoryContentsRecursive FilePath
sourceDir
let sourceAndDest :: FilePath -> (FilePath, FilePath)
sourceAndDest FilePath
file = (FilePath
src, FilePath
dest)
where
src :: FilePath
src = FilePath
sourceDir FilePath -> FilePath -> FilePath
</> FilePath
file
dest :: FilePath
dest = FilePath
targetDir FilePath -> FilePath -> FilePath
</> FilePath
file
(FilePath -> IO ()) -> [FilePath] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((FilePath, FilePath) -> IO ()
copyFile' ((FilePath, FilePath) -> IO ())
-> (FilePath -> (FilePath, FilePath)) -> FilePath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
sourceAndDest) [FilePath]
files
{-# DEPRECATED copyFile' "This function is deprecated in ogma-extra-1.6.0." #-}
copyFile' :: (FilePath, FilePath) -> IO ()
copyFile' :: (FilePath, FilePath) -> IO ()
copyFile' (FilePath
origin, FilePath
dest) = do
Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True (FilePath -> FilePath
takeDirectory FilePath
dest)
FilePath -> FilePath -> IO ()
copyFile FilePath
origin FilePath
dest
copyDirectoryRecursiveErrorHandler :: FilePath
-> FilePath
-> E.SomeException
-> IO ()
copyDirectoryRecursiveErrorHandler :: FilePath -> FilePath -> SomeException -> IO ()
copyDirectoryRecursiveErrorHandler FilePath
sourceDir FilePath
targetDir SomeException
_exception = do
Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
FilePath
"ogma: error: cannot copy " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
sourceDir FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" to " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
targetDir
ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
copyTemplate :: FilePath -> Value -> FilePath -> IO ()
copyTemplate :: FilePath -> Value -> FilePath -> IO ()
copyTemplate FilePath
templateDir Value
subst FilePath
targetDir = do
[FilePath]
tmplContents <- (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
templateDir FilePath -> FilePath -> FilePath
</>) ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FilePath
"..", FilePath
"."])
([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO [FilePath]
getDirectoryContentsRecursive FilePath
templateDir
[FilePath]
tmplFiles <- (FilePath -> IO Bool) -> [FilePath] -> IO [FilePath]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM FilePath -> IO Bool
doesFileExist [FilePath]
tmplContents
[FilePath] -> (FilePath -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [FilePath]
tmplFiles ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
fp -> do
let fullPath :: FilePath
fullPath = FilePath
targetDir FilePath -> FilePath -> FilePath
</> FilePath
newFP
where
newFP :: FilePath
newFP = (ParseError -> FilePath)
-> (Template -> FilePath) -> Either ParseError Template -> FilePath
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (FilePath -> ParseError -> FilePath
forall a b. a -> b -> a
const FilePath
relFP)
(Text -> FilePath
unpack (Text -> FilePath) -> (Template -> Text) -> Template -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Template -> Value -> Text
`renderMustache` Value
subst))
Either ParseError Template
fpAsTemplateE
relFP :: FilePath
relFP = FilePath -> FilePath -> FilePath
makeRelative FilePath
templateDir FilePath
fp
fpAsTemplateE :: Either ParseError Template
fpAsTemplateE = PName -> Text -> Either ParseError Template
compileMustacheText PName
"fp" (FilePath -> Text
pack FilePath
relFP)
ByteString
contents <- Text -> ByteString
encodeUtf8 (Text -> ByteString)
-> (Template -> Text) -> Template -> ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Template -> Value -> Text
`renderMustache` Value
subst)
(Template -> ByteString) -> IO Template -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO Template
compileMustacheFile FilePath
fp
let dirName :: FilePath
dirName = (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, FilePath) -> FilePath)
-> (FilePath, FilePath) -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> (FilePath, FilePath)
splitFileName FilePath
fullPath
Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True FilePath
dirName
FilePath -> ByteString -> IO ()
B.writeFile FilePath
fullPath ByteString
contents