--------------------------------------------------------------------------------
-- | Exports simple compilers to just copy files
{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.File
    ( CopyFile (..)
    , copyFileCompiler
    , TmpFile (..)
    , newTmpFile
    ) where


--------------------------------------------------------------------------------
import           Data.Binary                   (Binary (..))
import           Data.Typeable                 (Typeable)
#if MIN_VERSION_directory(1,2,6)
import           System.Directory              (copyFileWithMetadata)
#else
import           System.Directory              (copyFile)
#endif
import           System.Directory              (doesFileExist,
                                                renameFile)
import           System.FilePath               ((</>))
import           System.Random                 (randomIO)


--------------------------------------------------------------------------------
import           Hakyll.Core.Compiler
import           Hakyll.Core.Compiler.Internal
import           Hakyll.Core.Configuration
import           Hakyll.Core.Item
import           Hakyll.Core.Provider
import qualified Hakyll.Core.Store             as Store
import           Hakyll.Core.Util.File
import           Hakyll.Core.Writable


--------------------------------------------------------------------------------
-- | This will copy any file directly by using a system call
newtype CopyFile = CopyFile FilePath
    deriving (Get CopyFile
[CopyFile] -> Put
CopyFile -> Put
(CopyFile -> Put)
-> Get CopyFile -> ([CopyFile] -> Put) -> Binary CopyFile
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [CopyFile] -> Put
$cputList :: [CopyFile] -> Put
get :: Get CopyFile
$cget :: Get CopyFile
put :: CopyFile -> Put
$cput :: CopyFile -> Put
Binary, CopyFile -> CopyFile -> Bool
(CopyFile -> CopyFile -> Bool)
-> (CopyFile -> CopyFile -> Bool) -> Eq CopyFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyFile -> CopyFile -> Bool
$c/= :: CopyFile -> CopyFile -> Bool
== :: CopyFile -> CopyFile -> Bool
$c== :: CopyFile -> CopyFile -> Bool
Eq, Eq CopyFile
Eq CopyFile
-> (CopyFile -> CopyFile -> Ordering)
-> (CopyFile -> CopyFile -> Bool)
-> (CopyFile -> CopyFile -> Bool)
-> (CopyFile -> CopyFile -> Bool)
-> (CopyFile -> CopyFile -> Bool)
-> (CopyFile -> CopyFile -> CopyFile)
-> (CopyFile -> CopyFile -> CopyFile)
-> Ord CopyFile
CopyFile -> CopyFile -> Bool
CopyFile -> CopyFile -> Ordering
CopyFile -> CopyFile -> CopyFile
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CopyFile -> CopyFile -> CopyFile
$cmin :: CopyFile -> CopyFile -> CopyFile
max :: CopyFile -> CopyFile -> CopyFile
$cmax :: CopyFile -> CopyFile -> CopyFile
>= :: CopyFile -> CopyFile -> Bool
$c>= :: CopyFile -> CopyFile -> Bool
> :: CopyFile -> CopyFile -> Bool
$c> :: CopyFile -> CopyFile -> Bool
<= :: CopyFile -> CopyFile -> Bool
$c<= :: CopyFile -> CopyFile -> Bool
< :: CopyFile -> CopyFile -> Bool
$c< :: CopyFile -> CopyFile -> Bool
compare :: CopyFile -> CopyFile -> Ordering
$ccompare :: CopyFile -> CopyFile -> Ordering
$cp1Ord :: Eq CopyFile
Ord, Int -> CopyFile -> ShowS
[CopyFile] -> ShowS
CopyFile -> String
(Int -> CopyFile -> ShowS)
-> (CopyFile -> String) -> ([CopyFile] -> ShowS) -> Show CopyFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyFile] -> ShowS
$cshowList :: [CopyFile] -> ShowS
show :: CopyFile -> String
$cshow :: CopyFile -> String
showsPrec :: Int -> CopyFile -> ShowS
$cshowsPrec :: Int -> CopyFile -> ShowS
Show, Typeable)


--------------------------------------------------------------------------------
instance Writable CopyFile where
#if MIN_VERSION_directory(1,2,6)
    write :: String -> Item CopyFile -> IO ()
write String
dst (Item Identifier
_ (CopyFile String
src)) = String -> String -> IO ()
copyFileWithMetadata String
src String
dst
#else
    write dst (Item _ (CopyFile src)) = copyFile src dst
#endif
--------------------------------------------------------------------------------
copyFileCompiler :: Compiler (Item CopyFile)
copyFileCompiler :: Compiler (Item CopyFile)
copyFileCompiler = do
    Identifier
identifier <- Compiler Identifier
getUnderlying
    Provider
provider   <- CompilerRead -> Provider
compilerProvider (CompilerRead -> Provider)
-> Compiler CompilerRead -> Compiler Provider
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler CompilerRead
compilerAsk
    CopyFile -> Compiler (Item CopyFile)
forall a. a -> Compiler (Item a)
makeItem (CopyFile -> Compiler (Item CopyFile))
-> CopyFile -> Compiler (Item CopyFile)
forall a b. (a -> b) -> a -> b
$ String -> CopyFile
CopyFile (String -> CopyFile) -> String -> CopyFile
forall a b. (a -> b) -> a -> b
$ Provider -> Identifier -> String
resourceFilePath Provider
provider Identifier
identifier


--------------------------------------------------------------------------------
newtype TmpFile = TmpFile FilePath
    deriving (Typeable)


--------------------------------------------------------------------------------
instance Binary TmpFile where
    put :: TmpFile -> Put
put TmpFile
_ = () -> Put
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    get :: Get TmpFile
get   = String -> Get TmpFile
forall a. HasCallStack => String -> a
error (String -> Get TmpFile) -> String -> Get TmpFile
forall a b. (a -> b) -> a -> b
$
        String
"Hakyll.Core.File.TmpFile: You tried to load a TmpFile, however, " String -> ShowS
forall a. [a] -> [a] -> [a]
++
        String
"this is not possible since these are deleted as soon as possible."


--------------------------------------------------------------------------------
instance Writable TmpFile where
    write :: String -> Item TmpFile -> IO ()
write String
dst (Item Identifier
_ (TmpFile String
fp)) = String -> String -> IO ()
renameFile String
fp String
dst


--------------------------------------------------------------------------------
-- | Create a tmp file
newTmpFile :: String            -- ^ Suffix and extension
           -> Compiler TmpFile  -- ^ Resulting tmp path
newTmpFile :: String -> Compiler TmpFile
newTmpFile String
suffix = do
    String
path <- Compiler String
mkPath
    IO () -> Compiler ()
forall a. IO a -> Compiler a
compilerUnsafeIO (IO () -> Compiler ()) -> IO () -> Compiler ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
makeDirectories String
path
    String -> Compiler ()
debugCompiler (String -> Compiler ()) -> String -> Compiler ()
forall a b. (a -> b) -> a -> b
$ String
"newTmpFile " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path
    TmpFile -> Compiler TmpFile
forall (m :: * -> *) a. Monad m => a -> m a
return (TmpFile -> Compiler TmpFile) -> TmpFile -> Compiler TmpFile
forall a b. (a -> b) -> a -> b
$ String -> TmpFile
TmpFile String
path
  where
    mkPath :: Compiler String
mkPath = do
        Int
rand <- IO Int -> Compiler Int
forall a. IO a -> Compiler a
compilerUnsafeIO (IO Int -> Compiler Int) -> IO Int -> Compiler Int
forall a b. (a -> b) -> a -> b
$ IO Int
forall a. Random a => IO a
randomIO :: Compiler Int
        String
tmp  <- Configuration -> String
tmpDirectory (Configuration -> String)
-> (CompilerRead -> Configuration) -> CompilerRead -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompilerRead -> Configuration
compilerConfig (CompilerRead -> String)
-> Compiler CompilerRead -> Compiler String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler CompilerRead
compilerAsk
        let path :: String
path = String
tmp String -> ShowS
</> [String] -> String
Store.hash [Int -> String
forall a. Show a => a -> String
show Int
rand] String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
suffix
        Bool
exists <- IO Bool -> Compiler Bool
forall a. IO a -> Compiler a
compilerUnsafeIO (IO Bool -> Compiler Bool) -> IO Bool -> Compiler Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesFileExist String
path
        if Bool
exists then Compiler String
mkPath else String -> Compiler String
forall (m :: * -> *) a. Monad m => a -> m a
return String
path