Hello community,
here is the log from the commit of package ghc-fast-logger for openSUSE:Factory
checked in at 2019-10-18 14:34:08
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-fast-logger (Old)
and /work/SRC/openSUSE:Factory/.ghc-fast-logger.new.2352 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-fast-logger"
Fri Oct 18 14:34:08 2019 rev:17 rq:737200 version:3.0.0
Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-fast-logger/ghc-fast-logger.changes
2019-06-19 21:12:03.542722606 +0200
+++
/work/SRC/openSUSE:Factory/.ghc-fast-logger.new.2352/ghc-fast-logger.changes
2019-10-18 14:34:08.928127611 +0200
@@ -1,0 +2,29 @@
+Fri Oct 4 02:02:00 UTC 2019 - [email protected]
+
+- Update fast-logger to version 3.0.0.
+ ## 3.0.0
+
+ * Allowing the callback logger to be generic.
[#182](https://github.com/kazu-yamamoto/logger/pull/180) This is a BREAKING
CHANGE. Users should do:
+ 1. Importing `LogType'` and related constructors because `LogType` is now
a type alias.
+ 2. Using `{-# LANGUAGE GADTs #-}`, even if you aren't using anything new,
any time you try and `case` over values of type `LogType'`.
+
+ ## 2.4.17
+
+ * Obtaining a fresh fd from IORef just before writing.
[#180](https://github.com/kazu-yamamoto/logger/pull/180)
+
+ ## 2.4.16
+
+ * Using strict language extensions.
+
+ ## 2.4.15
+
+ * Rescuing GHC 7.8.
+
+-------------------------------------------------------------------
+Fri Sep 6 06:40:04 UTC 2019 - [email protected]
+
+- Update fast-logger to version 2.4.17.
+ Upstream has not updated the file "ChangeLog.md" since the last
+ release.
+
+-------------------------------------------------------------------
Old:
----
fast-logger-2.4.16.tar.gz
New:
----
fast-logger-3.0.0.tar.gz
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Other differences:
------------------
++++++ ghc-fast-logger.spec ++++++
--- /var/tmp/diff_new_pack.EekI7M/_old 2019-10-18 14:34:09.472126194 +0200
+++ /var/tmp/diff_new_pack.EekI7M/_new 2019-10-18 14:34:09.480126174 +0200
@@ -19,7 +19,7 @@
%global pkg_name fast-logger
%bcond_with tests
Name: ghc-%{pkg_name}
-Version: 2.4.16
+Version: 3.0.0
Release: 0
Summary: A fast logging system
License: BSD-3-Clause
++++++ fast-logger-2.4.16.tar.gz -> fast-logger-3.0.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/ChangeLog.md
new/fast-logger-3.0.0/ChangeLog.md
--- old/fast-logger-2.4.16/ChangeLog.md 2019-06-13 08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/ChangeLog.md 2019-10-04 03:05:51.000000000 +0200
@@ -1,3 +1,21 @@
+## 3.0.0
+
+* Allowing the callback logger to be generic.
[#182](https://github.com/kazu-yamamoto/logger/pull/180) This is a BREAKING
CHANGE. Users should do:
+ 1. Importing `LogType'` and related constructors because `LogType` is now a
type alias.
+ 2. Using `{-# LANGUAGE GADTs #-}`, even if you aren't using anything new,
any time you try and `case` over values of type `LogType'`.
+
+## 2.4.17
+
+* Obtaining a fresh fd from IORef just before writing.
[#180](https://github.com/kazu-yamamoto/logger/pull/180)
+
+## 2.4.16
+
+* Using strict language extensions.
+
+## 2.4.15
+
+* Rescuing GHC 7.8.
+
## 2.4.14
* Add `ToLogStr` instances for the following types: signed integers, unsigned
integers, floating-point numbers. These instances all use decimal encodings.
[#177](https://github.com/kazu-yamamoto/logger/pull/177)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/File.hs
new/fast-logger-3.0.0/System/Log/FastLogger/File.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/File.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger/File.hs 2019-10-04
03:05:51.000000000 +0200
@@ -8,10 +8,11 @@
, prefixTime
) where
-import Control.Monad (unless, when)
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)
-- | The spec for logging files
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/FileIO.hs
new/fast-logger-3.0.0/System/Log/FastLogger/FileIO.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/FileIO.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger/FileIO.hs 2019-10-04
03:05:51.000000000 +0200
@@ -1,19 +1,20 @@
module System.Log.FastLogger.FileIO where
-import Data.Word (Word8)
import Foreign.Ptr (Ptr)
import GHC.IO.Device (close)
import GHC.IO.FD (openFile, stderr, stdout, writeRawBufferPtr)
import qualified GHC.IO.FD as POSIX (FD(..))
import GHC.IO.IOMode (IOMode(..))
+import System.Log.FastLogger.Imports
+
type FD = POSIX.FD
closeFD :: FD -> IO ()
closeFD = close
openFileFD :: FilePath -> IO FD
-openFileFD f = fst `fmap` openFile f AppendMode False
+openFileFD f = fst <$> openFile f AppendMode False
getStderrFD :: IO FD
getStderrFD = return stderr
@@ -21,5 +22,7 @@
getStdoutFD :: IO FD
getStdoutFD = return stdout
-writeRawBufferPtr2FD :: FD -> Ptr Word8 -> Int -> IO Int
-writeRawBufferPtr2FD fd bf len = fromIntegral `fmap` writeRawBufferPtr "write"
fd bf 0 (fromIntegral len)
+writeRawBufferPtr2FD :: IORef FD -> Ptr Word8 -> Int -> IO Int
+writeRawBufferPtr2FD fdref bf len = do
+ fd <- readIORef fdref
+ fromIntegral <$> writeRawBufferPtr "write" fd bf 0 (fromIntegral len)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/IO.hs
new/fast-logger-3.0.0/System/Log/FastLogger/IO.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/IO.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger/IO.hs 2019-10-04
03:05:51.000000000 +0200
@@ -5,11 +5,11 @@
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.Imports
import System.Log.FastLogger.LogStr
type Buffer = Ptr Word8
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/IORef.hs
new/fast-logger-3.0.0/System/Log/FastLogger/IORef.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/IORef.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger/IORef.hs 1970-01-01
01:00:00.000000000 +0100
@@ -1,21 +0,0 @@
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE Safe #-}
-
-module System.Log.FastLogger.IORef (
- IORef
- , newIORef
- , readIORef
- , atomicModifyIORef'
- , writeIORef
- ) 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
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/Imports.hs
new/fast-logger-3.0.0/System/Log/FastLogger/Imports.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/Imports.hs 1970-01-01
01:00:00.000000000 +0100
+++ new/fast-logger-3.0.0/System/Log/FastLogger/Imports.hs 2019-10-04
03:05:51.000000000 +0200
@@ -0,0 +1,27 @@
+{-# LANGUAGE Trustworthy #-}
+
+module System.Log.FastLogger.Imports (
+ ByteString(..)
+ , module Control.Applicative
+ , module Control.Monad
+ , module Data.IORef
+ , module Data.List
+ , module Data.Int
+ , module Data.Monoid
+ , module Data.Ord
+ , module Data.Word
+ , module Data.Maybe
+ , module Numeric
+ ) where
+
+import Control.Applicative
+import Control.Monad
+import Data.ByteString.Internal (ByteString(..))
+import Data.IORef
+import Data.Int
+import Data.List
+import Data.Maybe
+import Data.Monoid
+import Data.Ord
+import Data.Word
+import Numeric
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/LogStr.hs
new/fast-logger-3.0.0/System/Log/FastLogger/LogStr.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/LogStr.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger/LogStr.hs 2019-10-04
03:05:51.000000000 +0200
@@ -12,35 +12,23 @@
, (<>)
) where
+import qualified Data.ByteString as BS
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
#if MIN_VERSION_base(4,9,0)
import qualified Data.Semigroup as Semi (Semigroup(..))
#endif
import Data.String (IsString(..))
-import Data.Int (Int8,Int16,Int32,Int64)
-import Data.Word (Word,Word8,Word16,Word32,Word64)
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
-----------------------------------------------------------------
+import System.Log.FastLogger.Imports
-#if !MIN_VERSION_base(4,5,0)
-(<>) :: Monoid m => m -> m -> m
-(<>) = mappend
-#endif
+----------------------------------------------------------------
toBuilder :: ByteString -> Builder
toBuilder = B.byteString
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/Logger.hs
new/fast-logger-3.0.0/System/Log/FastLogger/Logger.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/Logger.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger/Logger.hs 2019-10-04
03:05:51.000000000 +0200
@@ -1,4 +1,5 @@
-{-# LANGUAGE BangPatterns, CPP #-}
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}
module System.Log.FastLogger.Logger (
@@ -8,46 +9,43 @@
, flushLog
) where
+
import Control.Concurrent (MVar, newMVar, withMVar)
-import Control.Monad (when)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (plusPtr)
+
import System.Log.FastLogger.FileIO
import System.Log.FastLogger.IO
+import System.Log.FastLogger.Imports
import System.Log.FastLogger.LogStr
-import System.Log.FastLogger.IORef
----------------------------------------------------------------
-data Logger = Logger (MVar Buffer) !BufSize (IORef LogStr)
+data Logger = Logger !BufSize (MVar Buffer) (IORef LogStr)
----------------------------------------------------------------
newLogger :: BufSize -> IO Logger
-newLogger size = do
- buf <- getBuffer size
- mbuf <- newMVar buf
- lref <- newIORef mempty
- return $ Logger mbuf size lref
+newLogger size = Logger size <$> (getBuffer size >>= newMVar)
+ <*> newIORef mempty
----------------------------------------------------------------
-pushLog :: FD -> Logger -> LogStr -> IO ()
-pushLog fd logger@(Logger mbuf size ref) nlogmsg@(LogStr nlen nbuilder)
+pushLog :: IORef FD -> Logger -> LogStr -> IO ()
+pushLog fdref logger@(Logger size mbuf ref) nlogmsg@(LogStr nlen nbuilder)
| nlen > size = do
- flushLog fd logger
-
+ flushLog fdref logger
-- Make sure we have a large enough buffer to hold the entire
-- contents, thereby allowing for a single write system call and
-- avoiding interleaving. This does not address the possibility
-- of write not writing the entire buffer at once.
allocaBytes nlen $ \buf -> withMVar mbuf $ \_ ->
- toBufIOWith buf nlen (write fd) nbuilder
+ toBufIOWith buf nlen (write fdref) nbuilder
| otherwise = do
mmsg <- atomicModifyIORef' ref checkBuf
case mmsg of
Nothing -> return ()
- Just msg -> withMVar mbuf $ \buf -> writeLogStr fd buf size msg
+ Just msg -> withMVar mbuf $ \buf -> writeLogStr fdref buf size msg
where
checkBuf ologmsg@(LogStr olen _)
| size < olen + nlen = (nlogmsg, Just ologmsg)
@@ -55,8 +53,8 @@
----------------------------------------------------------------
-flushLog :: FD -> Logger -> IO ()
-flushLog fd (Logger mbuf size lref) = do
+flushLog :: IORef FD -> Logger -> IO ()
+flushLog fdref (Logger size mbuf 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
@@ -64,26 +62,26 @@
-- 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
+ withMVar mbuf $ \buf -> writeLogStr fdref 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
+writeLogStr :: IORef FD
-> Buffer
-> BufSize
-> LogStr
-> IO ()
-writeLogStr fd buf size (LogStr len builder)
+writeLogStr fdref buf size (LogStr len builder)
| size < len = error "writeLogStr"
- | otherwise = toBufIOWith buf size (write fd) builder
+ | otherwise = toBufIOWith buf size (write fdref) builder
-write :: FD -> Buffer -> Int -> IO ()
-write fd buf len' = loop buf (fromIntegral len')
+write :: IORef FD -> Buffer -> Int -> IO ()
+write fdref buf len' = loop buf (fromIntegral len')
where
loop bf !len = do
- written <- writeRawBufferPtr2FD fd bf len
+ written <- writeRawBufferPtr2FD fdref bf len
when (written < len) $
loop (bf `plusPtr` fromIntegral written) (len - written)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger/Types.hs
new/fast-logger-3.0.0/System/Log/FastLogger/Types.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger/Types.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger/Types.hs 2019-10-04
03:05:51.000000000 +0200
@@ -4,10 +4,10 @@
, FormattedTime
) where
-import Data.ByteString (ByteString)
+import System.Log.FastLogger.Imports
----------------------------------------------------------------
-
+
-- | Type aliaes for date format and formatted date.
type FormattedTime = ByteString
type TimeFormat = ByteString
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/System/Log/FastLogger.hs
new/fast-logger-3.0.0/System/Log/FastLogger.hs
--- old/fast-logger-2.4.16/System/Log/FastLogger.hs 2019-06-13
08:59:13.000000000 +0200
+++ new/fast-logger-3.0.0/System/Log/FastLogger.hs 2019-10-04
03:05:51.000000000 +0200
@@ -1,3 +1,7 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE GADTs #-}
+
-- | This module provides a fast logging system which
-- scales on multicore environments (i.e. +RTS -N\<x\>).
--
@@ -5,9 +9,6 @@
-- when program is run on more than one core thus users
-- should rely more on message timestamps than on their order in the
-- log.
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE OverloadedStrings #-}
-
module System.Log.FastLogger (
-- * Creating a logger set
LoggerSet
@@ -34,7 +35,7 @@
-- * FastLogger
, FastLogger
, TimedFastLogger
- , LogType(..)
+ , LogType'(..), LogType
, newFastLogger
, withFastLogger
, newTimedFastLogger
@@ -47,24 +48,19 @@
, module System.Log.FastLogger.Types
) where
-#if __GLASGOW_HASKELL__ < 709
-import Control.Applicative ((<$>))
-#endif
import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceAction)
import Control.Concurrent (getNumCapabilities, myThreadId, threadCapability,
takeMVar, MVar, newMVar, tryTakeMVar, putMVar)
import Control.Exception (handle, SomeException(..), bracket)
-import Control.Monad (when, replicateM)
import Data.Array (Array, listArray, (!), bounds)
-import Data.Foldable (forM_)
-import Data.Maybe (isJust)
import System.EasyFile (getFileSize)
+
+import System.Log.FastLogger.Date
import System.Log.FastLogger.File
-import System.Log.FastLogger.IO
import System.Log.FastLogger.FileIO
-import System.Log.FastLogger.IORef
+import System.Log.FastLogger.IO
+import System.Log.FastLogger.Imports
import System.Log.FastLogger.LogStr
import System.Log.FastLogger.Logger
-import System.Log.FastLogger.Date
import System.Log.FastLogger.Types
----------------------------------------------------------------
@@ -111,7 +107,7 @@
-- 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
+pushLogStr (LoggerSet _ fdref 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.
@@ -120,8 +116,7 @@
j | i < lim = i
| otherwise = i `mod` lim
let logger = arr ! j
- fd <- readIORef fref
- pushLog fd logger logmsg
+ pushLog fdref logger logmsg
flush
-- | Same as 'pushLogStr' but also appends a newline.
@@ -141,12 +136,11 @@
flushLogStr (LoggerSet _ fref arr _) = flushLogStrRaw fref arr
flushLogStrRaw :: IORef FD -> Array Int Logger -> IO ()
-flushLogStrRaw fref arr = do
+flushLogStrRaw fdref arr = do
let (l,u) = bounds arr
- fd <- readIORef fref
- mapM_ (flushIt fd) [l .. u]
+ mapM_ flushIt [l .. u]
where
- flushIt fd i = flushLog fd (arr ! i)
+ flushIt i = flushLog fdref (arr ! i)
-- | Renewing the internal file information in 'LoggerSet'.
-- This does nothing for stdout and stderr.
@@ -160,17 +154,17 @@
-- | Flushing the buffers, closing the internal file information
-- and freeing the buffers.
rmLoggerSet :: LoggerSet -> IO ()
-rmLoggerSet (LoggerSet mfile fref arr _) = do
+rmLoggerSet (LoggerSet mfile fdref arr _) = do
let (l,u) = bounds arr
- fd <- readIORef fref
let nums = [l .. u]
- mapM_ (flushIt fd) nums
+ mapM_ flushIt nums
mapM_ freeIt nums
+ fd <- readIORef fdref
when (isJust mfile) $ closeFD fd
where
- flushIt fd i = flushLog fd (arr ! i)
+ flushIt i = flushLog fdref (arr ! i)
freeIt i = do
- let (Logger mbuf _ _) = arr ! i
+ let (Logger _ mbuf _) = arr ! i
takeMVar mbuf >>= freeBuffer
----------------------------------------------------------------
@@ -179,7 +173,7 @@
type FastLogger = LogStr -> IO ()
-- | 'TimedFastLogger' pass 'FormattedTime' to callback and simply log its
result.
-- this can be used to customize how to log timestamp.
---
+--
-- Usually, one would write a wrapper on top of 'TimedFastLogger', for example:
--
-- @
@@ -190,34 +184,39 @@
-- @
type TimedFastLogger = (FormattedTime -> LogStr) -> IO ()
+type LogType = LogType' LogStr
+
-- | Logger Type.
-data LogType
- = LogNone -- ^ No logging.
- | LogStdout BufSize -- ^ Logging to stdout.
+data LogType' a where
+ LogNone :: LogType' LogStr -- ^ No logging.
+ LogStdout :: BufSize -> LogType' LogStr
+ -- ^ Logging to stdout.
-- 'BufSize' is a buffer size
-- for each capability.
- | LogStderr BufSize -- ^ Logging to stderr.
+ LogStderr :: BufSize -> LogType' LogStr
+ -- ^ Logging to stderr.
-- 'BufSize' is a buffer size
-- for each capability.
- | LogFileNoRotate FilePath BufSize
+ LogFileNoRotate :: FilePath -> BufSize -> LogType' LogStr
-- ^ Logging to a file.
-- 'BufSize' is a buffer size
-- for each capability.
- | LogFile FileLogSpec BufSize -- ^ Logging to a file.
+ LogFile :: FileLogSpec -> BufSize -> LogType' LogStr
+ -- ^ Logging to a file.
-- 'BufSize' is a buffer size
-- for each capability.
-- File rotation is done on-demand.
- | LogFileTimedRotate TimedFileLogSpec BufSize -- ^ Logging to a file.
+ LogFileTimedRotate :: TimedFileLogSpec -> BufSize -> LogType' LogStr -- ^
Logging to a file.
-- 'BufSize' is a buffer size
-- for each capability.
-- Rotation happens based on check
specified
-- in 'TimedFileLogSpec'.
- | LogCallback (LogStr -> IO ()) (IO ()) -- ^ Logging with a log and flush
action.
- -- run flush after log each
message.
+ LogCallback :: (v -> IO ()) -> IO () -> LogType' v -- ^ Logging with a
log and flush action.
+ -- run flush after
log each message.
-- | Initialize a 'FastLogger' without attaching timestamp
-- a tuple of logger and clean up action are returned.
-newFastLogger :: LogType -> IO (FastLogger, IO ())
+newFastLogger :: LogType' v -> IO (v -> IO (), IO ())
newFastLogger typ = case typ of
LogNone -> return (const noOp, noOp)
LogStdout bsize -> newStdoutLoggerSet bsize >>=
stdLoggerInit
@@ -350,7 +349,9 @@
unlock Nothing = return ()
unlock (Just (LoggerSet current_path a b c)) = do
putMVar mvar $ LoggerSet (Just new_file_path) a b c
- forM_ current_path (timed_post_process spec)
+ case current_path of
+ Nothing -> return ()
+ Just path -> timed_post_process spec path
rotateFiles Nothing = return ()
rotateFiles (Just (LoggerSet _ a b c)) = renewLoggerSet $ LoggerSet (Just
new_file_path) a b c
new_file_path = prefixTime now $ timed_log_file spec
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/fast-logger-2.4.16/fast-logger.cabal
new/fast-logger-3.0.0/fast-logger.cabal
--- old/fast-logger-2.4.16/fast-logger.cabal 2019-06-13 08:59:13.000000000
+0200
+++ new/fast-logger-3.0.0/fast-logger.cabal 2019-10-04 03:05:51.000000000
+0200
@@ -1,5 +1,5 @@
Name: fast-logger
-Version: 2.4.16
+Version: 3.0.0
Author: Kazu Yamamoto <[email protected]>
Maintainer: Kazu Yamamoto <[email protected]>
License: BSD3
@@ -20,12 +20,12 @@
System.Log.FastLogger.File
System.Log.FastLogger.Date
System.Log.FastLogger.Types
- Other-Modules: System.Log.FastLogger.IO
+ Other-Modules: System.Log.FastLogger.Imports
+ System.Log.FastLogger.IO
System.Log.FastLogger.FileIO
- System.Log.FastLogger.IORef
System.Log.FastLogger.LogStr
System.Log.FastLogger.Logger
- Build-Depends: base >= 4.5 && < 5
+ Build-Depends: base >= 4.7 && < 5
, array
, auto-update >= 0.1.2
, easy-file >= 0.2