{-# LANGUAGE Safe #-}
module System.Log.FastLogger.File
( FileLogSpec(..)
, TimedFileLogSpec (..)
, check
, rotate
, prefixTime
) where
import Data.ByteString.Char8 (unpack)
import System.Directory (doesFileExist, doesDirectoryExist, getPermissions, writable, renameFile)
import System.FilePath (takeDirectory, dropFileName, takeFileName, (</>))
import System.Log.FastLogger.Imports
import System.Log.FastLogger.Types (TimeFormat, FormattedTime)
data FileLogSpec = FileLogSpec {
log_file :: FilePath
, log_file_size :: Integer
, log_backup_number :: Int
}
data TimedFileLogSpec = TimedFileLogSpec {
timed_log_file :: FilePath
, timed_timefmt :: TimeFormat
, timed_same_timeframe :: FormattedTime -> FormattedTime -> Bool
, timed_post_process :: FilePath -> IO ()
}
check :: FilePath -> IO ()
check file = do
dirExist <- doesDirectoryExist dir
unless dirExist $ fail $ dir ++ " does not exist or is not a directory."
dirPerm <- getPermissions dir
unless (writable dirPerm) $ fail $ dir ++ " is not writable."
exist <- doesFileExist file
when exist $ do
perm <- getPermissions file
unless (writable perm) $ fail $ file ++ " is not writable."
where
dir = takeDirectory file
rotate :: FileLogSpec -> IO ()
rotate spec = mapM_ move srcdsts
where
path = log_file spec
n = log_backup_number spec
dsts' = reverse . ("":) . map (('.':). show) $ [0..n-1]
dsts = map (path++) dsts'
srcs = tail dsts
srcdsts = zip srcs dsts
move (src,dst) = do
exist <- doesFileExist src
when exist $ renameFile src dst
prefixTime :: FormattedTime -> FilePath -> FilePath
prefixTime time path = dropFileName path </> unpack time ++ "-" ++ takeFileName path