{-# LANGUAGE CPP #-}
module Network.Gitit.Cache ( expireCachedFile
, lookupCache
, cacheContents )
where
import qualified Data.ByteString as B (ByteString, readFile, writeFile)
import System.FilePath
import System.Directory (doesFileExist, removeFile, createDirectoryIfMissing, getModificationTime)
import Data.Time.Clock (UTCTime)
#if MIN_VERSION_directory(1,2,0)
#else
import System.Time (ClockTime(..))
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
#endif
import Network.Gitit.State
import Network.Gitit.Types
import Control.Monad
import Control.Monad.Trans (liftIO)
import Text.Pandoc.UTF8 (encodePath)
expireCachedFile :: String -> GititServerPart ()
expireCachedFile file = do
cfg <- getConfig
let target = encodePath $ cacheDir cfg </> file
exists <- liftIO $ doesFileExist target
when exists $ liftIO $ do
liftIO $ removeFile target
expireCachedPDF target (defaultExtension cfg)
expireCachedPDF :: String -> String -> IO ()
expireCachedPDF file ext =
when (takeExtension file == "." ++ ext) $ do
let pdfname = file ++ ".export.pdf"
exists <- doesFileExist pdfname
when exists $ removeFile pdfname
lookupCache :: String -> GititServerPart (Maybe (UTCTime, B.ByteString))
lookupCache file = do
cfg <- getConfig
let target = encodePath $ cacheDir cfg </> file
exists <- liftIO $ doesFileExist target
if exists
then liftIO $ do
#if MIN_VERSION_directory(1,2,0)
modtime <- getModificationTime target
#else
TOD secs _ <- getModificationTime target
let modtime = posixSecondsToUTCTime $ fromIntegral secs
#endif
contents <- B.readFile target
return $ Just (modtime, contents)
else return Nothing
cacheContents :: String -> B.ByteString -> GititServerPart ()
cacheContents file contents = do
cfg <- getConfig
let target = encodePath $ cacheDir cfg </> file
let targetDir = takeDirectory target
liftIO $ do
createDirectoryIfMissing True targetDir
B.writeFile target contents
expireCachedPDF target (defaultExtension cfg)