{-# LANGUAGE LambdaCase #-} module MBug.Cache (cachedIO, cachedIO_) where import qualified Data.ByteString.Lazy as BL import Data.Text (Text) import qualified Data.Text as T import Data.Time.Clock (diffUTCTime, getCurrentTime) import System.Directory ( createDirectoryIfMissing , doesFileExist , getModificationTime ) import System.Environment.XDG.BaseDir ( getUserCacheDir , getUserCacheFile ) -- | Cache file is stale if is does not exist or if its modification -- time is more than 15 minutes from now in past. isCacheFileStale :: FilePath -> IO Bool isCacheFileStale path = doesFileExist path >>= \case False -> pure False True -> do now <- getCurrentTime mtime <- getModificationTime path pure $ diffUTCTime now mtime < 900 -- | Perform IO action labeled with some 'Text' value, if no actions -- with same label were executed for last 15 minutes; return path to -- file, containing cached value and value itself. cachedIO :: Text -> IO BL.ByteString -> IO (FilePath, BL.ByteString) cachedIO label action = do getUserCacheDir "mbug" >>= createDirectoryIfMissing True cache <- getUserCacheFile "mbug" (T.unpack label) isCacheFileStale cache >>= \case True -> (,) <$> pure cache <*> BL.readFile cache False -> action >>= \output -> do BL.writeFile cache output pure (cache, output) -- | Same as 'cachedIO', but ignore information about cache file. cachedIO_ :: Text -> IO BL.ByteString -> IO BL.ByteString cachedIO_ label action = fmap snd $ cachedIO label action