fast-logger-2.4.1/0000755000000000000000000000000012562640726012130 5ustar0000000000000000fast-logger-2.4.1/ChangeLog.md0000644000000000000000000000017012562640726014277 0ustar0000000000000000## 2.3.0 * Move from blaze-builder to `Data.ByteString.Builder` [#55](https://github.com/kazu-yamamoto/logger/pull/55) fast-logger-2.4.1/fast-logger.cabal0000644000000000000000000000277512562640726015341 0ustar0000000000000000Name: fast-logger Version: 2.4.1 Author: Kazu Yamamoto Maintainer: Kazu Yamamoto License: BSD3 License-File: LICENSE Synopsis: A fast logging system Description: A fast logging system Category: System Cabal-Version: >= 1.8 Build-Type: Simple extra-source-files: README.md ChangeLog.md Library GHC-Options: -Wall Exposed-Modules: System.Log.FastLogger System.Log.FastLogger.File Other-Modules: System.Log.FastLogger.IO System.Log.FastLogger.IORef System.Log.FastLogger.LogStr System.Log.FastLogger.Logger Build-Depends: base >= 4.4 && < 5 , array , auto-update >= 0.1.2 , bytestring , bytestring-builder , directory , filepath , text Test-Suite spec Main-Is: Spec.hs Hs-Source-Dirs: test Type: exitcode-stdio-1.0 Ghc-Options: -Wall -threaded Build-Depends: base >= 4 && < 5 , bytestring , directory , fast-logger , hspec Source-Repository head Type: git Location: git://github.com/kazu-yamamoto/logger.git fast-logger-2.4.1/LICENSE0000644000000000000000000000276512562640726013147 0ustar0000000000000000Copyright (c) 2009, IIJ Innovation Institute Inc. All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of the copyright holders nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. fast-logger-2.4.1/README.md0000644000000000000000000000004612562640726013407 0ustar0000000000000000## fast-logger A fast logging system fast-logger-2.4.1/Setup.hs0000644000000000000000000000005612562640726013565 0ustar0000000000000000import Distribution.Simple main = defaultMain fast-logger-2.4.1/System/0000755000000000000000000000000012562640726013414 5ustar0000000000000000fast-logger-2.4.1/System/Log/0000755000000000000000000000000012562640726014135 5ustar0000000000000000fast-logger-2.4.1/System/Log/FastLogger.hs0000644000000000000000000001266312562640726016536 0ustar0000000000000000-- | This module provides a fast logging system which -- scales on multicore environments (i.e. +RTS -N\). {-# LANGUAGE BangPatterns, CPP #-} {-# LANGUAGE Safe #-} module System.Log.FastLogger ( -- * Creating a logger set LoggerSet , newFileLoggerSet , newStdoutLoggerSet , newStderrLoggerSet , newLoggerSet -- * Buffer size , BufSize , defaultBufSize -- * Renewing and removing a logger set , renewLoggerSet , rmLoggerSet -- * Log messages , LogStr , ToLogStr(..) , fromLogStr , logStrLength -- * Writing a log message , pushLogStr , pushLogStrLn -- * Flushing buffered log messages , flushLogStr -- * File rotation , module System.Log.FastLogger.File ) where #if __GLASGOW_HASKELL__ < 709 import Control.Applicative ((<$>)) #endif import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceAction) import Control.Concurrent (getNumCapabilities, myThreadId, threadCapability, takeMVar) import Control.Monad (when, replicateM) import Data.Array (Array, listArray, (!), bounds) import Data.Maybe (isJust) import GHC.IO.Device (close) import GHC.IO.FD (FD(..), openFile, stderr, stdout) import GHC.IO.IOMode (IOMode(..)) import System.Log.FastLogger.File import System.Log.FastLogger.IO import System.Log.FastLogger.IORef import System.Log.FastLogger.LogStr import System.Log.FastLogger.Logger ---------------------------------------------------------------- -- | Opening a log file. logOpen :: FilePath -> IO FD logOpen file = fst <$> openFile file AppendMode False ---------------------------------------------------------------- -- | A set of loggers. -- The number of loggers is the capabilities of GHC RTS. -- You can specify it with \"+RTS -N\\". -- A buffer is prepared for each capability. data LoggerSet = LoggerSet (Maybe FilePath) (IORef FD) (Array Int Logger) (IO ()) -- | Creating a new 'LoggerSet' using a file. newFileLoggerSet :: BufSize -> FilePath -> IO LoggerSet newFileLoggerSet size file = logOpen file >>= newFDLoggerSet size (Just file) -- | Creating a new 'LoggerSet' using stdout. newStdoutLoggerSet :: BufSize -> IO LoggerSet newStdoutLoggerSet size = newFDLoggerSet size Nothing stdout -- | Creating a new 'LoggerSet' using stderr. newStderrLoggerSet :: BufSize -> IO LoggerSet newStderrLoggerSet size = newFDLoggerSet size Nothing stderr {-# DEPRECATED newLoggerSet "Use newFileLoggerSet etc instead" #-} -- | Creating a new 'LoggerSet'. -- If 'Nothing' is specified to the second argument, -- stdout is used. -- Please note that the minimum 'BufSize' is 1. newLoggerSet :: BufSize -> Maybe FilePath -> IO LoggerSet newLoggerSet size = maybe (newStdoutLoggerSet size) (newFileLoggerSet size) -- | Creating a new 'LoggerSet' using a FD. newFDLoggerSet :: BufSize -> Maybe FilePath -> FD -> IO LoggerSet newFDLoggerSet size mfile fd = do n <- getNumCapabilities loggers <- replicateM n $ newLogger (max 1 size) let arr = listArray (0,n-1) loggers fref <- newIORef fd flush <- mkDebounce defaultDebounceSettings { debounceAction = flushLogStrRaw fref arr } return $ LoggerSet mfile fref arr flush -- | Writing a log message to the corresponding buffer. -- If the buffer becomes full, the log messages in the buffer -- are written to its corresponding file, stdout, or stderr. pushLogStr :: LoggerSet -> LogStr -> IO () pushLogStr (LoggerSet _ fref arr flush) logmsg = do (i, _) <- myThreadId >>= threadCapability -- The number of capability could be dynamically changed. -- So, let's check the upper boundary of the array. let u = snd $ bounds arr lim = u + 1 j | i < lim = i | otherwise = i `mod` lim let logger = arr ! j fd <- readIORef fref pushLog fd logger logmsg flush -- | Same as 'pushLogStr' but also appends a newline. pushLogStrLn :: LoggerSet -> LogStr -> IO () pushLogStrLn loggerSet logStr = pushLogStr loggerSet (logStr <> toLogStr "\n") -- | Flushing log messages in buffers. -- This function must be called explicitly when the program is -- being terminated. -- -- Note: Since version 2.1.6, this function does not need to be -- explicitly called, as every push includes an auto-debounced flush -- courtesy of the auto-update package. Since version 2.2.2, this -- function can be used to force flushing outside of the debounced -- flush calls. flushLogStr :: LoggerSet -> IO () flushLogStr (LoggerSet _ fref arr _) = flushLogStrRaw fref arr flushLogStrRaw :: IORef FD -> Array Int Logger -> IO () flushLogStrRaw fref arr = do let (l,u) = bounds arr fd <- readIORef fref mapM_ (flushIt fd) [l .. u] where flushIt fd i = flushLog fd (arr ! i) -- | Renewing the internal file information in 'LoggerSet'. -- This does nothing for stdout and stderr. renewLoggerSet :: LoggerSet -> IO () renewLoggerSet (LoggerSet Nothing _ _ _) = return () renewLoggerSet (LoggerSet (Just file) fref _ _) = do newfd <- logOpen file oldfd <- atomicModifyIORef' fref (\fd -> (newfd, fd)) close oldfd -- | Flushing the buffers, closing the internal file information -- and freeing the buffers. rmLoggerSet :: LoggerSet -> IO () rmLoggerSet (LoggerSet mfile fref arr _) = do let (l,u) = bounds arr fd <- readIORef fref let nums = [l .. u] mapM_ (flushIt fd) nums mapM_ freeIt nums when (isJust mfile) $ close fd where flushIt fd i = flushLog fd (arr ! i) freeIt i = do let (Logger mbuf _ _) = arr ! i takeMVar mbuf >>= freeBuffer fast-logger-2.4.1/System/Log/FastLogger/0000755000000000000000000000000012562640726016172 5ustar0000000000000000fast-logger-2.4.1/System/Log/FastLogger/File.hs0000644000000000000000000000243412562640726017410 0ustar0000000000000000{-# LANGUAGE Safe #-} module System.Log.FastLogger.File where import Control.Monad (unless, when) import System.Directory (doesFileExist, doesDirectoryExist, getPermissions, writable, renameFile) import System.FilePath (takeDirectory) -- | The spec for logging files data FileLogSpec = FileLogSpec { log_file :: FilePath , log_file_size :: Integer , log_backup_number :: Int } -- | Checking if a log file can be written. check :: FileLogSpec -> IO () check spec = 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 file = log_file spec dir = takeDirectory file -- | Rotating log files. 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 fast-logger-2.4.1/System/Log/FastLogger/IO.hs0000644000000000000000000000251012562640726017033 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE Trustworthy #-} module System.Log.FastLogger.IO where import Data.ByteString.Builder.Extra (Next(..)) import qualified Data.ByteString.Builder.Extra as BBE import Data.ByteString.Internal (ByteString(..)) import Data.Word (Word8) import Foreign.ForeignPtr (withForeignPtr) import Foreign.Marshal.Alloc (mallocBytes, free) import Foreign.Ptr (Ptr, plusPtr) import System.Log.FastLogger.LogStr type Buffer = Ptr Word8 -- | The type for buffer size of each core. type BufSize = Int -- | The default buffer size (4,096 bytes). defaultBufSize :: BufSize defaultBufSize = 4096 getBuffer :: BufSize -> IO Buffer getBuffer = mallocBytes freeBuffer :: Buffer -> IO () freeBuffer = free toBufIOWith :: Buffer -> BufSize -> (Buffer -> Int -> IO ()) -> Builder -> IO () toBufIOWith buf !size io builder = loop $ BBE.runBuilder builder where loop writer = do (len, next) <- writer buf size io buf len case next of Done -> return () More minSize writer' | size < minSize -> error "toBufIOWith: More: minSize" | otherwise -> loop writer' Chunk (PS fptr off siz) writer' | len == 0 -> loop writer' -- flushing | otherwise -> withForeignPtr fptr $ \ptr -> io (ptr `plusPtr` off) siz fast-logger-2.4.1/System/Log/FastLogger/IORef.hs0000644000000000000000000000066312562640726017477 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE Safe #-} module System.Log.FastLogger.IORef ( IORef , newIORef , readIORef , atomicModifyIORef' ) where import Data.IORef #if !MIN_VERSION_base(4, 6, 0) atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b atomicModifyIORef' ref f = do b <- atomicModifyIORef ref (\x -> let (a, b) = f x in (a, a `seq` b)) b `seq` return b #endif fast-logger-2.4.1/System/Log/FastLogger/Logger.hs0000644000000000000000000000533412562640726017752 0ustar0000000000000000{-# LANGUAGE BangPatterns, CPP #-} {-# LANGUAGE Safe #-} module System.Log.FastLogger.Logger ( Logger(..) , newLogger , pushLog , flushLog ) where import Control.Concurrent (MVar, newMVar, withMVar) import Control.Monad (when) import Foreign.Ptr (plusPtr) import GHC.IO.FD (FD, writeRawBufferPtr) import System.Log.FastLogger.IO import System.Log.FastLogger.LogStr import System.Log.FastLogger.IORef ---------------------------------------------------------------- data Logger = Logger (MVar Buffer) !BufSize (IORef LogStr) ---------------------------------------------------------------- newLogger :: BufSize -> IO Logger newLogger size = do buf <- getBuffer size mbuf <- newMVar buf lref <- newIORef mempty return $ Logger mbuf size lref ---------------------------------------------------------------- pushLog :: FD -> Logger -> LogStr -> IO () pushLog fd logger@(Logger mbuf size ref) nlogmsg@(LogStr nlen nbuilder) | nlen > size = do flushLog fd logger withMVar mbuf $ \buf -> toBufIOWith buf size (write fd) nbuilder | otherwise = do mmsg <- atomicModifyIORef' ref checkBuf case mmsg of Nothing -> return () Just msg -> withMVar mbuf $ \buf -> writeLogStr fd buf size msg where checkBuf ologmsg@(LogStr olen _) | size < olen + nlen = (nlogmsg, Just ologmsg) | otherwise = (ologmsg <> nlogmsg, Nothing) ---------------------------------------------------------------- flushLog :: FD -> Logger -> IO () flushLog fd (Logger mbuf size lref) = do logmsg <- atomicModifyIORef' lref (\old -> (mempty, old)) -- If a special buffer is prepared for flusher, this MVar could -- be removed. But such a code does not contribute logging speed -- according to experiment. And even with the special buffer, -- there is no grantee that this function is exclusively called -- for a buffer. So, we use MVar here. -- This is safe and speed penalty can be ignored. withMVar mbuf $ \buf -> writeLogStr fd buf size logmsg ---------------------------------------------------------------- -- | Writting 'LogStr' using a buffer in blocking mode. -- The size of 'LogStr' must be smaller or equal to -- the size of buffer. writeLogStr :: FD -> Buffer -> BufSize -> LogStr -> IO () writeLogStr fd buf size (LogStr len builder) | size < len = error "writeLogStr" | otherwise = toBufIOWith buf size (write fd) builder write :: FD -> Buffer -> Int -> IO () write fd buf len' = loop buf (fromIntegral len') where loop bf !len = do written <- writeRawBufferPtr "write" fd bf 0 (fromIntegral len) when (written < len) $ loop (bf `plusPtr` fromIntegral written) (len - written) fast-logger-2.4.1/System/Log/FastLogger/LogStr.hs0000644000000000000000000000441412562640726017743 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE Safe #-} module System.Log.FastLogger.LogStr ( Builder , LogStr(..) , logStrLength , fromLogStr , ToLogStr(..) , mempty , (<>) ) where import Data.ByteString.Builder (Builder) import qualified Data.ByteString.Builder as B import Data.ByteString (ByteString) import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as S8 import qualified Data.ByteString.Lazy as BL #if __GLASGOW_HASKELL__ < 709 import Data.Monoid (Monoid, mempty, mappend) #endif #if MIN_VERSION_base(4,5,0) import Data.Monoid ((<>)) #endif import Data.String (IsString(..)) import qualified Data.Text as T import qualified Data.Text.Encoding as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Encoding as TL ---------------------------------------------------------------- #if !MIN_VERSION_base(4,5,0) (<>) :: Monoid m => m -> m -> m (<>) = mappend #endif toBuilder :: ByteString -> Builder toBuilder = B.byteString fromBuilder :: Builder -> ByteString #if MIN_VERSION_bytestring(0,10,0) fromBuilder = BL.toStrict . B.toLazyByteString #else fromBuilder = BS.concat . BL.toChunks . B.toLazyByteString #endif ---------------------------------------------------------------- -- | Log message builder. Use ('<>') to append two LogStr in O(1). data LogStr = LogStr !Int Builder instance Monoid LogStr where mempty = LogStr 0 (toBuilder BS.empty) LogStr s1 b1 `mappend` LogStr s2 b2 = LogStr (s1 + s2) (b1 <> b2) instance IsString LogStr where fromString = toLogStr . TL.pack class ToLogStr msg where toLogStr :: msg -> LogStr instance ToLogStr LogStr where toLogStr = id instance ToLogStr S8.ByteString where toLogStr bs = LogStr (BS.length bs) (toBuilder bs) instance ToLogStr BL.ByteString where toLogStr = toLogStr . S8.concat . BL.toChunks instance ToLogStr String where toLogStr = toLogStr . TL.pack instance ToLogStr T.Text where toLogStr = toLogStr . T.encodeUtf8 instance ToLogStr TL.Text where toLogStr = toLogStr . TL.encodeUtf8 -- | Obtaining the length of 'LogStr'. logStrLength :: LogStr -> Int logStrLength (LogStr n _) = n -- | Converting 'LogStr' to 'ByteString'. fromLogStr :: LogStr -> ByteString fromLogStr (LogStr _ builder) = fromBuilder builder fast-logger-2.4.1/test/0000755000000000000000000000000012562640726013107 5ustar0000000000000000fast-logger-2.4.1/test/Spec.hs0000644000000000000000000000005412562640726014334 0ustar0000000000000000{-# OPTIONS_GHC -F -pgmF hspec-discover #-}