{-# LANGUAGE OverloadedStrings #-} {-| Module : System.Posix.IO.Log Description : Helper methods for viewing & writing log files Copyright : (c) Philip Woods 2015 License : AGPL-3 Maintainer : elzairthesorcerer@gmail.com Stability : experimental Portabiltity : Linux -} module System.Posix.IO.Log ( getCurrentLog, writeLog ) where import Control.Monad (liftM) import qualified Data.Text as DT import qualified Data.Text.IO as DTI import Data.Info (ProjectInfo(..), LogInfo(..), tPathRoot) import Data.UnixTime (getUnixTime, UnixTime(utSeconds, utMicroSeconds)) import System.Directory (createDirectoryIfMissing, getDirectoryContents) -- | Retrieve the contents of the most recent log file getCurrentLog :: ProjectInfo -- ^ The given project -> IO LogInfo -- ^ Contents and metadata of log file getCurrentLog info = do dir <- return $ getLogPath info createDirectoryIfMissing True dir dirContents <- getFilteredContents dir case dirContents of Left err -> return $ LogInfo{provider_info = provider info, repository_info = repository info, branch_info = branch info, log_info = DT.pack err} Right files -> do latest <- return $ maximum files contents <- DTI.readFile $ dir ++ latest return $ LogInfo{provider_info = provider info, repository_info = repository info, branch_info = branch info, log_info = contents} where getFilteredContents dir = do dirContents <- liftM filterDots $ getDirectoryContents dir if (length dirContents) == 0 then return $ Left $ "No logfiles in " ++ dir else return $ Right dirContents filterDots = filter (\x -> x /= "." && x /= "..") -- | Write new log file writeLog :: ProjectInfo -- ^ The given project -> DT.Text -- ^ Contents to write -> IO () -- ^ No return value writeLog info contents = do logPath <- return $ getLogPath info createDirectoryIfMissing True logPath fileName <- getFullTime DTI.writeFile (logPath ++ fileName) contents where getFullTime = do time <- getUnixTime seconds <- (return . fromEnum . utSeconds) time useconds <- (return . fromEnum . utMicroSeconds) time return $ show $ seconds * 1000000 + useconds -- | Retrieve the absolute path to the log directory for a given project getLogPath :: ProjectInfo -- ^ The given project -> FilePath -- ^ Path to log directory for given project getLogPath info = let p = provider info r = repository info b = branch info in DT.unpack $ DT.concat [tPathRoot, "logs/", p, "/", r, "/", b, "/"]