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
newtype CopyFile = CopyFile FilePath
    deriving (Binary, Eq, Ord, Show, Typeable)
instance Writable CopyFile where
#if MIN_VERSION_directory(1,2,6)
    write dst (Item _ (CopyFile src)) = copyFileWithMetadata src dst
#else
    write dst (Item _ (CopyFile src)) = copyFile src dst
#endif
copyFileCompiler :: Compiler (Item CopyFile)
copyFileCompiler = do
    identifier <- getUnderlying
    provider   <- compilerProvider <$> compilerAsk
    makeItem $ CopyFile $ resourceFilePath provider identifier
newtype TmpFile = TmpFile FilePath
    deriving (Typeable)
instance Binary TmpFile where
    put _ = return ()
    get   = error $
        "Hakyll.Core.File.TmpFile: You tried to load a TmpFile, however, " ++
        "this is not possible since these are deleted as soon as possible."
instance Writable TmpFile where
    write dst (Item _ (TmpFile fp)) = renameFile fp dst
newTmpFile :: String            
           -> Compiler TmpFile  
newTmpFile suffix = do
    path <- mkPath
    compilerUnsafeIO $ makeDirectories path
    debugCompiler $ "newTmpFile " ++ path
    return $ TmpFile path
  where
    mkPath = do
        rand <- compilerUnsafeIO $ randomIO :: Compiler Int
        tmp  <- tmpDirectory . compilerConfig <$> compilerAsk
        let path = tmp </> Store.hash [show rand] ++ "-" ++ suffix
        exists <- compilerUnsafeIO $ doesFileExist path
        if exists then mkPath else return path