{-# 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
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
$cput :: CopyFile -> Put
put :: CopyFile -> Put
$cget :: Get CopyFile
get :: Get CopyFile
$cputList :: [CopyFile] -> Put
putList :: [CopyFile] -> Put
Binary, CopyFile -> CopyFile -> Bool
(CopyFile -> CopyFile -> Bool)
-> (CopyFile -> CopyFile -> Bool) -> Eq CopyFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CopyFile -> CopyFile -> Bool
== :: CopyFile -> CopyFile -> Bool
$c/= :: CopyFile -> CopyFile -> Bool
/= :: 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
$ccompare :: CopyFile -> CopyFile -> Ordering
compare :: CopyFile -> CopyFile -> Ordering
$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
>= :: CopyFile -> CopyFile -> Bool
$cmax :: CopyFile -> CopyFile -> CopyFile
max :: CopyFile -> CopyFile -> CopyFile
$cmin :: CopyFile -> CopyFile -> CopyFile
min :: CopyFile -> CopyFile -> CopyFile
Ord, Int -> CopyFile -> FilePath -> FilePath
[CopyFile] -> FilePath -> FilePath
CopyFile -> FilePath
(Int -> CopyFile -> FilePath -> FilePath)
-> (CopyFile -> FilePath)
-> ([CopyFile] -> FilePath -> FilePath)
-> Show CopyFile
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
$cshowsPrec :: Int -> CopyFile -> FilePath -> FilePath
showsPrec :: Int -> CopyFile -> FilePath -> FilePath
$cshow :: CopyFile -> FilePath
show :: CopyFile -> FilePath
$cshowList :: [CopyFile] -> FilePath -> FilePath
showList :: [CopyFile] -> FilePath -> FilePath
Show, Typeable)
instance Writable CopyFile where
#if MIN_VERSION_directory(1,2,6)
write :: FilePath -> Item CopyFile -> IO ()
write FilePath
dst (Item Identifier
_ (CopyFile FilePath
src)) = FilePath -> FilePath -> IO ()
copyFileWithMetadata FilePath
src FilePath
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
$ FilePath -> CopyFile
CopyFile (FilePath -> CopyFile) -> FilePath -> CopyFile
forall a b. (a -> b) -> a -> b
$ Provider -> Identifier -> FilePath
resourceFilePath Provider
provider Identifier
identifier
newtype TmpFile = TmpFile FilePath
deriving (Typeable)
instance Binary TmpFile where
put :: TmpFile -> Put
put TmpFile
_ = () -> Put
forall a. a -> PutM a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
get :: Get TmpFile
get = FilePath -> Get TmpFile
forall a. HasCallStack => FilePath -> a
error (FilePath -> Get TmpFile) -> FilePath -> Get TmpFile
forall a b. (a -> b) -> a -> b
$
FilePath
"Hakyll.Core.File.TmpFile: You tried to load a TmpFile, however, " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
"this is not possible since these are deleted as soon as possible."
instance Writable TmpFile where
write :: FilePath -> Item TmpFile -> IO ()
write FilePath
dst (Item Identifier
_ (TmpFile FilePath
fp)) = FilePath -> FilePath -> IO ()
renameFile FilePath
fp FilePath
dst
newTmpFile :: String
-> Compiler TmpFile
newTmpFile :: FilePath -> Compiler TmpFile
newTmpFile FilePath
suffix = do
FilePath
path <- Compiler FilePath
mkPath
IO () -> Compiler ()
forall a. IO a -> Compiler a
compilerUnsafeIO (IO () -> Compiler ()) -> IO () -> Compiler ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
makeDirectories FilePath
path
FilePath -> Compiler ()
debugCompiler (FilePath -> Compiler ()) -> FilePath -> Compiler ()
forall a b. (a -> b) -> a -> b
$ FilePath
"newTmpFile " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
path
TmpFile -> Compiler TmpFile
forall a. a -> Compiler a
forall (m :: * -> *) a. Monad m => a -> m a
return (TmpFile -> Compiler TmpFile) -> TmpFile -> Compiler TmpFile
forall a b. (a -> b) -> a -> b
$ FilePath -> TmpFile
TmpFile FilePath
path
where
mkPath :: Compiler FilePath
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 (m :: * -> *). (Random a, MonadIO m) => m a
randomIO :: Compiler Int
FilePath
tmp <- Configuration -> FilePath
tmpDirectory (Configuration -> FilePath)
-> (CompilerRead -> Configuration) -> CompilerRead -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompilerRead -> Configuration
compilerConfig (CompilerRead -> FilePath)
-> Compiler CompilerRead -> Compiler FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler CompilerRead
compilerAsk
let path :: FilePath
path = FilePath
tmp FilePath -> FilePath -> FilePath
</> [FilePath] -> FilePath
Store.hash [Int -> FilePath
forall a. Show a => a -> FilePath
show Int
rand] FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
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
$ FilePath -> IO Bool
doesFileExist FilePath
path
if Bool
exists then Compiler FilePath
mkPath else FilePath -> Compiler FilePath
forall a. a -> Compiler a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
path