{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Provider.Internal
( ResourceInfo (..)
, Provider (..)
, newProvider
, resourceList
, resourceExists
, resourceFilePath
, resourceString
, resourceLBS
, resourceModified
, resourceModificationTime
) where
import Control.DeepSeq (NFData (..), deepseq)
import Control.Monad (forM)
import Data.Binary (Binary (..))
import qualified Data.ByteString.Lazy as BL
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Data.Set (Set)
import qualified Data.Set as S
import Data.Time (Day (..), UTCTime (..))
import Data.Typeable (Typeable)
import System.Directory (getModificationTime)
import System.FilePath (addExtension, (</>))
#if !MIN_VERSION_directory(1,2,0)
import Data.Time (readTime)
import System.Locale (defaultTimeLocale)
import System.Time (formatCalendarTime, toCalendarTime)
#endif
import Hakyll.Core.Identifier
import Hakyll.Core.Store (Store)
import qualified Hakyll.Core.Store as Store
import Hakyll.Core.Util.File
newtype BinaryTime = BinaryTime {BinaryTime -> UTCTime
unBinaryTime :: UTCTime}
deriving (BinaryTime -> BinaryTime -> Bool
(BinaryTime -> BinaryTime -> Bool)
-> (BinaryTime -> BinaryTime -> Bool) -> Eq BinaryTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BinaryTime -> BinaryTime -> Bool
$c/= :: BinaryTime -> BinaryTime -> Bool
== :: BinaryTime -> BinaryTime -> Bool
$c== :: BinaryTime -> BinaryTime -> Bool
Eq, BinaryTime -> ()
(BinaryTime -> ()) -> NFData BinaryTime
forall a. (a -> ()) -> NFData a
rnf :: BinaryTime -> ()
$crnf :: BinaryTime -> ()
NFData, Eq BinaryTime
Eq BinaryTime
-> (BinaryTime -> BinaryTime -> Ordering)
-> (BinaryTime -> BinaryTime -> Bool)
-> (BinaryTime -> BinaryTime -> Bool)
-> (BinaryTime -> BinaryTime -> Bool)
-> (BinaryTime -> BinaryTime -> Bool)
-> (BinaryTime -> BinaryTime -> BinaryTime)
-> (BinaryTime -> BinaryTime -> BinaryTime)
-> Ord BinaryTime
BinaryTime -> BinaryTime -> Bool
BinaryTime -> BinaryTime -> Ordering
BinaryTime -> BinaryTime -> BinaryTime
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 :: BinaryTime -> BinaryTime -> BinaryTime
$cmin :: BinaryTime -> BinaryTime -> BinaryTime
max :: BinaryTime -> BinaryTime -> BinaryTime
$cmax :: BinaryTime -> BinaryTime -> BinaryTime
>= :: BinaryTime -> BinaryTime -> Bool
$c>= :: BinaryTime -> BinaryTime -> Bool
> :: BinaryTime -> BinaryTime -> Bool
$c> :: BinaryTime -> BinaryTime -> Bool
<= :: BinaryTime -> BinaryTime -> Bool
$c<= :: BinaryTime -> BinaryTime -> Bool
< :: BinaryTime -> BinaryTime -> Bool
$c< :: BinaryTime -> BinaryTime -> Bool
compare :: BinaryTime -> BinaryTime -> Ordering
$ccompare :: BinaryTime -> BinaryTime -> Ordering
$cp1Ord :: Eq BinaryTime
Ord, Int -> BinaryTime -> ShowS
[BinaryTime] -> ShowS
BinaryTime -> String
(Int -> BinaryTime -> ShowS)
-> (BinaryTime -> String)
-> ([BinaryTime] -> ShowS)
-> Show BinaryTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BinaryTime] -> ShowS
$cshowList :: [BinaryTime] -> ShowS
show :: BinaryTime -> String
$cshow :: BinaryTime -> String
showsPrec :: Int -> BinaryTime -> ShowS
$cshowsPrec :: Int -> BinaryTime -> ShowS
Show, Typeable)
instance Binary BinaryTime where
put :: BinaryTime -> Put
put (BinaryTime (UTCTime (ModifiedJulianDay Integer
d) DiffTime
dt)) =
Integer -> Put
forall t. Binary t => t -> Put
put Integer
d Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Rational -> Put
forall t. Binary t => t -> Put
put (DiffTime -> Rational
forall a. Real a => a -> Rational
toRational DiffTime
dt)
get :: Get BinaryTime
get = (UTCTime -> BinaryTime) -> Get UTCTime -> Get BinaryTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UTCTime -> BinaryTime
BinaryTime (Get UTCTime -> Get BinaryTime) -> Get UTCTime -> Get BinaryTime
forall a b. (a -> b) -> a -> b
$ Day -> DiffTime -> UTCTime
UTCTime
(Day -> DiffTime -> UTCTime)
-> Get Day -> Get (DiffTime -> UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Integer -> Day
ModifiedJulianDay (Integer -> Day) -> Get Integer -> Get Day
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Integer
forall t. Binary t => Get t
get)
Get (DiffTime -> UTCTime) -> Get DiffTime -> Get UTCTime
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Rational -> DiffTime
forall a. Fractional a => Rational -> a
fromRational (Rational -> DiffTime) -> Get Rational -> Get DiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Rational
forall t. Binary t => Get t
get)
data ResourceInfo = ResourceInfo
{ ResourceInfo -> BinaryTime
resourceInfoModified :: BinaryTime
, ResourceInfo -> Maybe Identifier
resourceInfoMetadata :: Maybe Identifier
} deriving (Int -> ResourceInfo -> ShowS
[ResourceInfo] -> ShowS
ResourceInfo -> String
(Int -> ResourceInfo -> ShowS)
-> (ResourceInfo -> String)
-> ([ResourceInfo] -> ShowS)
-> Show ResourceInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResourceInfo] -> ShowS
$cshowList :: [ResourceInfo] -> ShowS
show :: ResourceInfo -> String
$cshow :: ResourceInfo -> String
showsPrec :: Int -> ResourceInfo -> ShowS
$cshowsPrec :: Int -> ResourceInfo -> ShowS
Show, Typeable)
instance Binary ResourceInfo where
put :: ResourceInfo -> Put
put (ResourceInfo BinaryTime
mtime Maybe Identifier
meta) = BinaryTime -> Put
forall t. Binary t => t -> Put
put BinaryTime
mtime Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe Identifier -> Put
forall t. Binary t => t -> Put
put Maybe Identifier
meta
get :: Get ResourceInfo
get = BinaryTime -> Maybe Identifier -> ResourceInfo
ResourceInfo (BinaryTime -> Maybe Identifier -> ResourceInfo)
-> Get BinaryTime -> Get (Maybe Identifier -> ResourceInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get BinaryTime
forall t. Binary t => Get t
get Get (Maybe Identifier -> ResourceInfo)
-> Get (Maybe Identifier) -> Get ResourceInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Maybe Identifier)
forall t. Binary t => Get t
get
instance NFData ResourceInfo where
rnf :: ResourceInfo -> ()
rnf (ResourceInfo BinaryTime
mtime Maybe Identifier
meta) = BinaryTime -> ()
forall a. NFData a => a -> ()
rnf BinaryTime
mtime () -> () -> ()
`seq` Maybe Identifier -> ()
forall a. NFData a => a -> ()
rnf Maybe Identifier
meta () -> () -> ()
`seq` ()
data Provider = Provider
{
Provider -> String
providerDirectory :: FilePath
,
Provider -> Map Identifier ResourceInfo
providerFiles :: Map Identifier ResourceInfo
,
Provider -> Map Identifier ResourceInfo
providerOldFiles :: Map Identifier ResourceInfo
,
Provider -> Store
providerStore :: Store
} deriving (Int -> Provider -> ShowS
[Provider] -> ShowS
Provider -> String
(Int -> Provider -> ShowS)
-> (Provider -> String) -> ([Provider] -> ShowS) -> Show Provider
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Provider] -> ShowS
$cshowList :: [Provider] -> ShowS
show :: Provider -> String
$cshow :: Provider -> String
showsPrec :: Int -> Provider -> ShowS
$cshowsPrec :: Int -> Provider -> ShowS
Show)
newProvider :: Store
-> (FilePath -> IO Bool)
-> FilePath
-> IO Provider
newProvider :: Store -> (String -> IO Bool) -> String -> IO Provider
newProvider Store
store String -> IO Bool
ignore String
directory = do
[Identifier]
list <- (String -> Identifier) -> [String] -> [Identifier]
forall a b. (a -> b) -> [a] -> [b]
map String -> Identifier
fromFilePath ([String] -> [Identifier]) -> IO [String] -> IO [Identifier]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO Bool) -> String -> IO [String]
getRecursiveContents String -> IO Bool
ignore String
directory
let universe :: Set Identifier
universe = [Identifier] -> Set Identifier
forall a. Ord a => [a] -> Set a
S.fromList [Identifier]
list
Map Identifier ResourceInfo
files <- ([(Identifier, ResourceInfo)] -> Map Identifier ResourceInfo)
-> IO [(Identifier, ResourceInfo)]
-> IO (Map Identifier ResourceInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Map Identifier ResourceInfo -> Map Identifier ResourceInfo
maxmtime (Map Identifier ResourceInfo -> Map Identifier ResourceInfo)
-> ([(Identifier, ResourceInfo)] -> Map Identifier ResourceInfo)
-> [(Identifier, ResourceInfo)]
-> Map Identifier ResourceInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Identifier, ResourceInfo)] -> Map Identifier ResourceInfo
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList) (IO [(Identifier, ResourceInfo)]
-> IO (Map Identifier ResourceInfo))
-> IO [(Identifier, ResourceInfo)]
-> IO (Map Identifier ResourceInfo)
forall a b. (a -> b) -> a -> b
$ [Identifier]
-> (Identifier -> IO (Identifier, ResourceInfo))
-> IO [(Identifier, ResourceInfo)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Identifier]
list ((Identifier -> IO (Identifier, ResourceInfo))
-> IO [(Identifier, ResourceInfo)])
-> (Identifier -> IO (Identifier, ResourceInfo))
-> IO [(Identifier, ResourceInfo)]
forall a b. (a -> b) -> a -> b
$ \Identifier
identifier -> do
ResourceInfo
rInfo <- String -> Set Identifier -> Identifier -> IO ResourceInfo
getResourceInfo String
directory Set Identifier
universe Identifier
identifier
(Identifier, ResourceInfo) -> IO (Identifier, ResourceInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (Identifier
identifier, ResourceInfo
rInfo)
Map Identifier ResourceInfo
oldFiles <- Map Identifier ResourceInfo
-> Maybe (Map Identifier ResourceInfo)
-> Map Identifier ResourceInfo
forall a. a -> Maybe a -> a
fromMaybe Map Identifier ResourceInfo
forall a. Monoid a => a
mempty (Maybe (Map Identifier ResourceInfo)
-> Map Identifier ResourceInfo)
-> (Result (Map Identifier ResourceInfo)
-> Maybe (Map Identifier ResourceInfo))
-> Result (Map Identifier ResourceInfo)
-> Map Identifier ResourceInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result (Map Identifier ResourceInfo)
-> Maybe (Map Identifier ResourceInfo)
forall a. Result a -> Maybe a
Store.toMaybe (Result (Map Identifier ResourceInfo)
-> Map Identifier ResourceInfo)
-> IO (Result (Map Identifier ResourceInfo))
-> IO (Map Identifier ResourceInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Store -> [String] -> IO (Result (Map Identifier ResourceInfo))
forall a.
(Binary a, Typeable a) =>
Store -> [String] -> IO (Result a)
Store.get Store
store [String]
oldKey
Map Identifier ResourceInfo
oldFiles Map Identifier ResourceInfo -> IO () -> IO ()
forall a b. NFData a => a -> b -> b
`deepseq` Store -> [String] -> Map Identifier ResourceInfo -> IO ()
forall a. (Binary a, Typeable a) => Store -> [String] -> a -> IO ()
Store.set Store
store [String]
oldKey Map Identifier ResourceInfo
files
Provider -> IO Provider
forall (m :: * -> *) a. Monad m => a -> m a
return (Provider -> IO Provider) -> Provider -> IO Provider
forall a b. (a -> b) -> a -> b
$ String
-> Map Identifier ResourceInfo
-> Map Identifier ResourceInfo
-> Store
-> Provider
Provider String
directory Map Identifier ResourceInfo
files Map Identifier ResourceInfo
oldFiles Store
store
where
oldKey :: [String]
oldKey = [String
"Hakyll.Core.Provider.Internal.newProvider", String
"oldFiles"]
maxmtime :: Map Identifier ResourceInfo -> Map Identifier ResourceInfo
maxmtime Map Identifier ResourceInfo
files = ((ResourceInfo -> ResourceInfo)
-> Map Identifier ResourceInfo -> Map Identifier ResourceInfo)
-> Map Identifier ResourceInfo
-> (ResourceInfo -> ResourceInfo)
-> Map Identifier ResourceInfo
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ResourceInfo -> ResourceInfo)
-> Map Identifier ResourceInfo -> Map Identifier ResourceInfo
forall a b k. (a -> b) -> Map k a -> Map k b
M.map Map Identifier ResourceInfo
files ((ResourceInfo -> ResourceInfo) -> Map Identifier ResourceInfo)
-> (ResourceInfo -> ResourceInfo) -> Map Identifier ResourceInfo
forall a b. (a -> b) -> a -> b
$ \rInfo :: ResourceInfo
rInfo@(ResourceInfo BinaryTime
mtime Maybe Identifier
meta) ->
let metaMod :: Maybe BinaryTime
metaMod = (ResourceInfo -> BinaryTime)
-> Maybe ResourceInfo -> Maybe BinaryTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ResourceInfo -> BinaryTime
resourceInfoModified (Maybe ResourceInfo -> Maybe BinaryTime)
-> Maybe ResourceInfo -> Maybe BinaryTime
forall a b. (a -> b) -> a -> b
$ Maybe Identifier
meta Maybe Identifier
-> (Identifier -> Maybe ResourceInfo) -> Maybe ResourceInfo
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Identifier -> Map Identifier ResourceInfo -> Maybe ResourceInfo)
-> Map Identifier ResourceInfo -> Identifier -> Maybe ResourceInfo
forall a b c. (a -> b -> c) -> b -> a -> c
flip Identifier -> Map Identifier ResourceInfo -> Maybe ResourceInfo
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Map Identifier ResourceInfo
files
in ResourceInfo
rInfo {resourceInfoModified :: BinaryTime
resourceInfoModified = BinaryTime
-> (BinaryTime -> BinaryTime) -> Maybe BinaryTime -> BinaryTime
forall b a. b -> (a -> b) -> Maybe a -> b
maybe BinaryTime
mtime (BinaryTime -> BinaryTime -> BinaryTime
forall a. Ord a => a -> a -> a
max BinaryTime
mtime) Maybe BinaryTime
metaMod}
getResourceInfo :: FilePath -> Set Identifier -> Identifier -> IO ResourceInfo
getResourceInfo :: String -> Set Identifier -> Identifier -> IO ResourceInfo
getResourceInfo String
directory Set Identifier
universe Identifier
identifier = do
UTCTime
mtime <- String -> IO UTCTime
fileModificationTime (String -> IO UTCTime) -> String -> IO UTCTime
forall a b. (a -> b) -> a -> b
$ String
directory String -> ShowS
</> Identifier -> String
toFilePath Identifier
identifier
ResourceInfo -> IO ResourceInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (ResourceInfo -> IO ResourceInfo)
-> ResourceInfo -> IO ResourceInfo
forall a b. (a -> b) -> a -> b
$ BinaryTime -> Maybe Identifier -> ResourceInfo
ResourceInfo (UTCTime -> BinaryTime
BinaryTime UTCTime
mtime) (Maybe Identifier -> ResourceInfo)
-> Maybe Identifier -> ResourceInfo
forall a b. (a -> b) -> a -> b
$
if Identifier
mdRsc Identifier -> Set Identifier -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set Identifier
universe then Identifier -> Maybe Identifier
forall a. a -> Maybe a
Just Identifier
mdRsc else Maybe Identifier
forall a. Maybe a
Nothing
where
mdRsc :: Identifier
mdRsc = String -> Identifier
fromFilePath (String -> Identifier) -> String -> Identifier
forall a b. (a -> b) -> a -> b
$ (String -> ShowS) -> String -> ShowS
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> ShowS
addExtension String
"metadata" ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Identifier -> String
toFilePath Identifier
identifier
resourceList :: Provider -> [Identifier]
resourceList :: Provider -> [Identifier]
resourceList = Map Identifier ResourceInfo -> [Identifier]
forall k a. Map k a -> [k]
M.keys (Map Identifier ResourceInfo -> [Identifier])
-> (Provider -> Map Identifier ResourceInfo)
-> Provider
-> [Identifier]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Provider -> Map Identifier ResourceInfo
providerFiles
resourceExists :: Provider -> Identifier -> Bool
resourceExists :: Provider -> Identifier -> Bool
resourceExists Provider
provider =
(Identifier -> Map Identifier ResourceInfo -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`M.member` Provider -> Map Identifier ResourceInfo
providerFiles Provider
provider) (Identifier -> Bool)
-> (Identifier -> Identifier) -> Identifier -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe String -> Identifier -> Identifier
setVersion Maybe String
forall a. Maybe a
Nothing
resourceFilePath :: Provider -> Identifier -> FilePath
resourceFilePath :: Provider -> Identifier -> String
resourceFilePath Provider
p Identifier
i = Provider -> String
providerDirectory Provider
p String -> ShowS
</> Identifier -> String
toFilePath Identifier
i
resourceString :: Provider -> Identifier -> IO String
resourceString :: Provider -> Identifier -> IO String
resourceString Provider
p Identifier
i = String -> IO String
readFile (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ Provider -> Identifier -> String
resourceFilePath Provider
p Identifier
i
resourceLBS :: Provider -> Identifier -> IO BL.ByteString
resourceLBS :: Provider -> Identifier -> IO ByteString
resourceLBS Provider
p Identifier
i = String -> IO ByteString
BL.readFile (String -> IO ByteString) -> String -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Provider -> Identifier -> String
resourceFilePath Provider
p Identifier
i
resourceModified :: Provider -> Identifier -> Bool
resourceModified :: Provider -> Identifier -> Bool
resourceModified Provider
p Identifier
r = case (Maybe ResourceInfo
ri, Maybe ResourceInfo
oldRi) of
(Maybe ResourceInfo
Nothing, Maybe ResourceInfo
_) -> Bool
False
(Just ResourceInfo
_, Maybe ResourceInfo
Nothing) -> Bool
True
(Just ResourceInfo
n, Just ResourceInfo
o) ->
ResourceInfo -> BinaryTime
resourceInfoModified ResourceInfo
n BinaryTime -> BinaryTime -> Bool
forall a. Ord a => a -> a -> Bool
> ResourceInfo -> BinaryTime
resourceInfoModified ResourceInfo
o Bool -> Bool -> Bool
||
ResourceInfo -> Maybe Identifier
resourceInfoMetadata ResourceInfo
n Maybe Identifier -> Maybe Identifier -> Bool
forall a. Eq a => a -> a -> Bool
/= ResourceInfo -> Maybe Identifier
resourceInfoMetadata ResourceInfo
o
where
normal :: Identifier
normal = Maybe String -> Identifier -> Identifier
setVersion Maybe String
forall a. Maybe a
Nothing Identifier
r
ri :: Maybe ResourceInfo
ri = Identifier -> Map Identifier ResourceInfo -> Maybe ResourceInfo
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Identifier
normal (Provider -> Map Identifier ResourceInfo
providerFiles Provider
p)
oldRi :: Maybe ResourceInfo
oldRi = Identifier -> Map Identifier ResourceInfo -> Maybe ResourceInfo
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Identifier
normal (Provider -> Map Identifier ResourceInfo
providerOldFiles Provider
p)
resourceModificationTime :: Provider -> Identifier -> UTCTime
resourceModificationTime :: Provider -> Identifier -> UTCTime
resourceModificationTime Provider
p Identifier
i =
case Identifier -> Map Identifier ResourceInfo -> Maybe ResourceInfo
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Maybe String -> Identifier -> Identifier
setVersion Maybe String
forall a. Maybe a
Nothing Identifier
i) (Provider -> Map Identifier ResourceInfo
providerFiles Provider
p) of
Just ResourceInfo
ri -> BinaryTime -> UTCTime
unBinaryTime (BinaryTime -> UTCTime) -> BinaryTime -> UTCTime
forall a b. (a -> b) -> a -> b
$ ResourceInfo -> BinaryTime
resourceInfoModified ResourceInfo
ri
Maybe ResourceInfo
Nothing -> String -> UTCTime
forall a. HasCallStack => String -> a
error (String -> UTCTime) -> String -> UTCTime
forall a b. (a -> b) -> a -> b
$
String
"Hakyll.Core.Provider.Internal.resourceModificationTime: " String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"resource " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Identifier -> String
forall a. Show a => a -> String
show Identifier
i String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" does not exist"
fileModificationTime :: FilePath -> IO UTCTime
fileModificationTime :: String -> IO UTCTime
fileModificationTime String
fp = do
#if MIN_VERSION_directory(1,2,0)
String -> IO UTCTime
getModificationTime String
fp
#else
ct <- toCalendarTime =<< getModificationTime fp
let str = formatCalendarTime defaultTimeLocale "%s" ct
return $ readTime defaultTimeLocale "%s" str
#endif