{-# LANGUAGE OverloadedStrings #-}
-- Copyright 2020 United States Government as represented by the Administrator
-- of the National Aeronautics and Space Administration. All Rights Reserved.
--
-- Disclaimers
--
-- No Warranty: THE SUBJECT SOFTWARE IS PROVIDED "AS IS" WITHOUT ANY WARRANTY
-- OF ANY KIND, EITHER EXPRESSED, IMPLIED, OR STATUTORY, INCLUDING, BUT NOT
-- LIMITED TO, ANY WARRANTY THAT THE SUBJECT SOFTWARE WILL CONFORM TO
-- SPECIFICATIONS, ANY IMPLIED WARRANTIES OF MERCHANTABILITY, FITNESS FOR A
-- PARTICULAR PURPOSE, OR FREEDOM FROM INFRINGEMENT, ANY WARRANTY THAT THE
-- SUBJECT SOFTWARE WILL BE ERROR FREE, OR ANY WARRANTY THAT DOCUMENTATION, IF
-- PROVIDED, WILL CONFORM TO THE SUBJECT SOFTWARE. THIS AGREEMENT DOES NOT, IN
-- ANY MANNER, CONSTITUTE AN ENDORSEMENT BY GOVERNMENT AGENCY OR ANY PRIOR
-- RECIPIENT OF ANY RESULTS, RESULTING DESIGNS, HARDWARE, SOFTWARE PRODUCTS OR
-- ANY OTHER APPLICATIONS RESULTING FROM USE OF THE SUBJECT SOFTWARE. FURTHER,
-- GOVERNMENT AGENCY DISCLAIMS ALL WARRANTIES AND LIABILITIES REGARDING
-- THIRD-PARTY SOFTWARE, IF PRESENT IN THE ORIGINAL SOFTWARE, AND DISTRIBUTES
-- IT "AS IS."
--
-- Waiver and Indemnity: RECIPIENT AGREES TO WAIVE ANY AND ALL CLAIMS AGAINST
-- THE UNITED STATES GOVERNMENT, ITS CONTRACTORS AND SUBCONTRACTORS, AS WELL AS
-- ANY PRIOR RECIPIENT. IF RECIPIENT'S USE OF THE SUBJECT SOFTWARE RESULTS IN
-- ANY LIABILITIES, DEMANDS, DAMAGES, EXPENSES OR LOSSES ARISING FROM SUCH USE,
-- INCLUDING ANY DAMAGES FROM PRODUCTS BASED ON, OR RESULTING FROM, RECIPIENT'S
-- USE OF THE SUBJECT SOFTWARE, RECIPIENT SHALL INDEMNIFY AND HOLD HARMLESS THE
-- UNITED STATES GOVERNMENT, ITS CONTRACTORS AND SUBCONTRACTORS, AS WELL AS ANY
-- PRIOR RECIPIENT, TO THE EXTENT PERMITTED BY LAW. RECIPIENT'S SOLE REMEDY
-- FOR ANY SUCH MATTER SHALL BE THE IMMEDIATE, UNILATERAL TERMINATION OF THIS
-- AGREEMENT.
--
-- | Auxiliary functions for working with directories.
module System.Directory.Extra
    ( copyDirectoryRecursive
    , copyFile'
    , copyTemplate
    )
  where

-- External imports
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." #-}
-- | Copy all files from one directory to another.
copyDirectoryRecursive :: FilePath  -- ^ Source directory
                       -> FilePath  -- ^ Target directory
                       -> 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
    -- Obtain files in source directory
    [FilePath]
files <- FilePath -> IO [FilePath]
getDirectoryContentsRecursive FilePath
sourceDir

    -- Determine the actual source and destination path for a file.
    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

    -- Copy all the files, replacing the top directory.
    (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." #-}
-- | Copy file origin to dest, creating the target directory if it does not
-- exist.
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

-- | Handle the case in which the source directory cannot be copied or the
-- target directory cannot be created/written.
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)

-- * Generic template handling

-- | Copy a template directory into a target location, expanding variables
-- provided in a map in a JSON value, both in the file contents and in the
-- filepaths themselves.
copyTemplate :: FilePath -> Value -> FilePath -> IO ()
copyTemplate :: FilePath -> Value -> FilePath -> IO ()
copyTemplate FilePath
templateDir Value
subst FilePath
targetDir = do

  -- Get all files (not directories) in the template dir. To keep a directory,
  -- create an empty file in it (e.g., .keep).
  [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

  -- Copy files to new locations, expanding their name and contents as
  -- mustache templates.
  [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

    -- New file name in target directory, treating file
    -- name as mustache template.
    let fullPath :: FilePath
fullPath = FilePath
targetDir FilePath -> FilePath -> FilePath
</> FilePath
newFP
          where
            -- If file name has mustache markers, expand, otherwise use
            -- relative file path
            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

            -- Local file name within template dir
            relFP :: FilePath
relFP = FilePath -> FilePath -> FilePath
makeRelative FilePath
templateDir FilePath
fp

            -- Apply mustache substitutions to file name
            fpAsTemplateE :: Either ParseError Template
fpAsTemplateE = PName -> Text -> Either ParseError Template
compileMustacheText PName
"fp" (FilePath -> Text
pack FilePath
relFP)

    -- File contents, treated as a mustache template.
    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

    -- Create target directory if necessary
    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

    -- Write expanded contents to expanded file path
    FilePath -> ByteString -> IO ()
B.writeFile FilePath
fullPath ByteString
contents