hslogger-1.2.9/0000755000175000017500000000000012525527476015104 5ustar00jgoerzenjgoerzen00000000000000hslogger-1.2.9/LICENSE0000600000175000017500000000272012525527476016102 0ustar00jgoerzenjgoerzen00000000000000Copyright (c) 2004 - 2011 John Goerzen 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 John Goerzen nor the names of the 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 HOLDER 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. hslogger-1.2.9/winbuild.bat0000600000175000017500000000011212525527476017373 0ustar00jgoerzenjgoerzen00000000000000ghc -package Cabal Setup.hs -o setup.exe setup configure setup build hslogger-1.2.9/Setup.hs0000600000175000017500000000011212525527476016522 0ustar00jgoerzenjgoerzen00000000000000#!/usr/bin/env runhaskell import Distribution.Simple main = defaultMain hslogger-1.2.9/src/0000755000175000017500000000000012525527476015673 5ustar00jgoerzenjgoerzen00000000000000hslogger-1.2.9/src/System/0000755000175000017500000000000012525527476017157 5ustar00jgoerzenjgoerzen00000000000000hslogger-1.2.9/src/System/Log.hs0000600000175000017500000000271612525527476020232 0ustar00jgoerzenjgoerzen00000000000000{- | Module : System.Log Copyright : Copyright (C) 2004-2011 John Goerzen License : BSD3 Maintainer : John Goerzen Stability : experimental Portability: portable Haskell Logging Framework Written by John Goerzen, jgoerzen\@complete.org This module defines basic types used for logging. Extensive documentation is available in "System.Log.Logger". -} module System.Log(-- * Types Priority(..), LogRecord ) where {- | Priorities are used to define how important a log message is. Users can filter log messages based on priorities. These have their roots on the traditional syslog system. The standard definitions are given below, but you are free to interpret them however you like. They are listed here in ascending importance order. -} data Priority = DEBUG -- ^ Debug messages | INFO -- ^ Information | NOTICE -- ^ Normal runtime conditions | WARNING -- ^ General Warnings | ERROR -- ^ General Errors | CRITICAL -- ^ Severe situations | ALERT -- ^ Take immediate action | EMERGENCY -- ^ System is unusable deriving (Eq, Ord, Enum, Bounded, Show, Read) {- | Internal type of log records -} type LogRecord = (Priority, String) hslogger-1.2.9/src/System/Log/0000755000175000017500000000000012525527476017700 5ustar00jgoerzenjgoerzen00000000000000hslogger-1.2.9/src/System/Log/Handler/0000755000175000017500000000000012525527476021255 5ustar00jgoerzenjgoerzen00000000000000hslogger-1.2.9/src/System/Log/Handler/Growl.hs0000600000175000017500000001120612525527476022673 0ustar00jgoerzenjgoerzen00000000000000{- | Module : System.Log.Handler.Growl Copyright : Copyright (C) 2007-2011 John Goerzen License : BSD3 Maintainer : Richard M. Neswold, Jr. Stability : provisional Portability: portable Simple log handlers Written by Richard M. Neswold, Jr. rich.neswold\@gmail.com -} module System.Log.Handler.Growl(addTarget, growlHandler) where import Data.Char import Data.Word import Network.Socket import Network.BSD import System.Log import System.Log.Handler import System.Log.Formatter data GrowlHandler = GrowlHandler { priority :: Priority, formatter :: LogFormatter GrowlHandler, appName :: String, skt :: Socket, targets :: [HostAddress] } instance LogHandler GrowlHandler where setLevel gh p = gh { priority = p } getLevel = priority setFormatter gh f = gh { formatter = f } getFormatter = formatter emit gh lr _ = let pkt = buildNotification gh nmGeneralMsg lr in mapM_ (sendNote (skt gh) pkt) (targets gh) close gh = let pkt = buildNotification gh nmClosingMsg (WARNING, "Connection closing.") s = skt gh in mapM_ (sendNote s pkt) (targets gh) >> sClose s sendNote :: Socket -> String -> HostAddress -> IO Int sendNote s pkt ha = sendTo s pkt (SockAddrInet 9887 ha) -- Right now there are two "notification names": "message" and -- "disconnecting". All log messages are sent using the "message" -- name. When the handler gets closed properly, the "disconnecting" -- notification gets sent. nmGeneralMsg :: String nmGeneralMsg = "message" nmClosingMsg :: String nmClosingMsg = "disconnecting" {- | Creates a Growl handler. Once a Growl handler has been created, machines that are to receive the message have to be specified. -} growlHandler :: String -- ^ The name of the service -> Priority -- ^ Priority of handler -> IO GrowlHandler growlHandler nm pri = do { s <- socket AF_INET Datagram 0 ; return GrowlHandler { priority = pri, appName = nm, formatter=nullFormatter, skt = s, targets = [] } } -- Converts a Word16 into a string of two characters. The value is -- emitted in network byte order. emit16 :: Word16 -> String emit16 v = let (h, l) = (fromEnum v) `divMod` 256 in [chr h, chr l] emitLen16 :: [a] -> String emitLen16 = emit16 . fromIntegral . length -- Takes a Service record and generates a network packet -- representing the service. buildRegistration :: GrowlHandler -> String buildRegistration s = concat fields where fields = [ ['\x1', '\x4'], emitLen16 (appName s), emitLen8 appNotes, emitLen8 appNotes, appName s, foldl packIt [] appNotes, ['\x0' .. (chr (length appNotes - 1))] ] packIt a b = a ++ (emitLen16 b) ++ b appNotes = [ nmGeneralMsg, nmClosingMsg ] emitLen8 v = [chr $ length v] {- | Adds a remote machine's address to the list of targets that will receive log messages. Calling this function sends a registration packet to the machine. This function will throw an exception if the host name cannot be found. -} addTarget :: HostName -> GrowlHandler -> IO GrowlHandler addTarget hn gh = do { he <- getHostByName hn ; let ha = hostAddress he sa = SockAddrInet 9887 ha in do { sendTo (skt gh) (buildRegistration gh) sa ; return gh { targets = ha:(targets gh) } } } -- Converts a Priority type into the subset of integers needed in the -- network packet's flag field. toFlags :: Priority -> Word16 toFlags DEBUG = 12 toFlags INFO = 10 toFlags NOTICE = 0 toFlags WARNING = 2 toFlags ERROR = 3 -- Same as WARNING, but "sticky" bit set toFlags CRITICAL = 3 -- Same as WARNING, but "sticky" bit set toFlags ALERT = 4 toFlags EMERGENCY = 5 -- Same as ALERT, but "sticky" bit set -- Creates a network packet containing a notification record. buildNotification :: GrowlHandler -> String -> LogRecord -> String buildNotification gh nm (p, msg) = concat fields where fields = [ ['\x1', '\x5'], emit16 (toFlags p), emitLen16 nm, emit16 0, emitLen16 msg, emitLen16 (appName gh), nm, [], msg, appName gh ] hslogger-1.2.9/src/System/Log/Handler/Simple.hs0000600000175000017500000000703512525527476023037 0ustar00jgoerzenjgoerzen00000000000000{- | Module : System.Log.Handler.Simple Copyright : Copyright (C) 2004-2011 John Goerzen License : BSD3 Maintainer : John Goerzen Stability : provisional Portability: portable Simple log handlers Written by John Goerzen, jgoerzen\@complete.org -} module System.Log.Handler.Simple(streamHandler, fileHandler, GenericHandler (..), verboseStreamHandler) where #if !MIN_VERSION_base(4,6,0) import Prelude hiding (catch) #endif import Control.Exception (SomeException, catch) import Data.Char (ord) import System.Log import System.Log.Handler import System.Log.Formatter import System.IO import Control.Concurrent.MVar {- | A helper data type. -} data GenericHandler a = GenericHandler {priority :: Priority, formatter :: LogFormatter (GenericHandler a), privData :: a, writeFunc :: a -> String -> IO (), closeFunc :: a -> IO () } instance LogHandler (GenericHandler a) where setLevel sh p = sh{priority = p} getLevel sh = priority sh setFormatter sh f = sh{formatter = f} getFormatter sh = formatter sh emit sh (_,msg) _ = (writeFunc sh) (privData sh) msg close sh = (closeFunc sh) (privData sh) {- | Create a stream log handler. Log messages sent to this handler will be sent to the stream used initially. Note that the 'close' method will have no effect on stream handlers; it does not actually close the underlying stream. -} streamHandler :: Handle -> Priority -> IO (GenericHandler Handle) streamHandler h pri = do lock <- newMVar () let mywritefunc hdl msg = withMVar lock (\_ -> do writeToHandle hdl msg hFlush hdl ) return (GenericHandler {priority = pri, formatter = nullFormatter, privData = h, writeFunc = mywritefunc, closeFunc = \x -> return ()}) where writeToHandle hdl msg = hPutStrLn hdl msg `catch` (handleWriteException hdl msg) handleWriteException :: Handle -> String -> SomeException -> IO () handleWriteException hdl msg e = let msg' = "Error writing log message: " ++ show e ++ " (original message: " ++ msg ++ ")" in hPutStrLn hdl (encodingSave msg') encodingSave = concatMap (\c -> if ord c > 127 then "\\" ++ show (ord c) else [c]) {- | Create a file log handler. Log messages sent to this handler will be sent to the filename specified, which will be opened in Append mode. Calling 'close' on the handler will close the file. -} fileHandler :: FilePath -> Priority -> IO (GenericHandler Handle) fileHandler fp pri = do h <- openFile fp AppendMode sh <- streamHandler h pri return (sh{closeFunc = hClose}) {- | Like 'streamHandler', but note the priority and logger name along with each message. -} verboseStreamHandler :: Handle -> Priority -> IO (GenericHandler Handle) verboseStreamHandler h pri = let fmt = simpleLogFormatter "[$loggername/$prio] $msg" in do hndlr <- streamHandler h pri return $ setFormatter hndlr fmt hslogger-1.2.9/src/System/Log/Handler/Log4jXML.hs0000600000175000017500000002040612525527476023143 0ustar00jgoerzenjgoerzen00000000000000{-# LANGUAGE CPP #-} {- | Module : System.Log.Handler.Log4jXML Copyright : Copyright (C) 2007-2011 John Goerzen License : BSD3 Maintainer : bjorn.buckwalter@gmail.com Stability : experimental Portability: GHC only? log4j[1] XMLLayout log handlers. Written by Bjorn Buckwalter, bjorn.buckwalter\@gmail.com -} module System.Log.Handler.Log4jXML ( -- * Introduction {- | This module provides handlers for hslogger that are compatible with log4j's XMLLayout. In particular log messages created by the handlers can be published directly to the GUI-based log viewer Chainsaw v2[2]. The set of log levels in hslogger is richer than the basic set of log4j levels. Two sets of handlers are provided with hslogger4j, one which produces logs with hslogger's levels and one which \"demotes\" them to the basic log4j levels. If full hslogger levels are used some Java installation (see below) is necessary to make Chainsaw aware of them. Usage of the handlers in hslogger4j is analoguous to usage of the 'System.Log.Handler.Simple.StreamHandler' and 'System.Log.Handler.Simple.FileHandler' in "System.Log.Handler.Simple". The following handlers are provided: -} -- ** Handlers with hslogger levels log4jStreamHandler, log4jFileHandler, -- ** Handlers with log4j levels log4jStreamHandler', log4jFileHandler' -- * Java install process {- | This is only necessary if you want to use the hslogger levels. Add @hslogger4j.jar@ from @contrib\/java@ to your classpath. To use you will also need to have the jars @log4j-1.3alpha-7.jar@ and @log4j-xml-1.3alpha-7.jar@ that are distributed with Chainsaw on your classpath. (On Mac OS X I added all three jars to @~\/Library\/Java\/Extensions@. It seems that it is not sufficient that Chainsaw already includes its jars in the classpath when launching - perhaps the plugin classloader does not inherit Chainsaw's classpath. Adding the jars to @~\/.chainsaw\/plugins@ wouldn't work either.) If for whatever reason you have to rebuild the hslogger4j jar just run @ant@[3] in the @contrib\/java@ directory. The new jar will be created in the @contrib\/java\/dist@ directory. The Java source code is copyright The Apache Software Foundation and licensed under the Apache Licence version 2.0. -} -- * Chainsaw setup {- | If you are only using the basic log4j levels just use Chainsaw's regular facilities to browse logs or listen for log messages (e.g. @XMLSocketReceiver@). If you want to use the hslogger levels the easiest way to set up Chainsaw is to load the plugins in @hslogger4j-plugins.xml@ in @contrib\/java@ when launching Chainsaw. Two receivers will be defined, one that listens for logmessages and one for reading log files. Edit the properties of those receivers as needed (e.g. @port@, @fileURL@) and restart them. You will also want to modify Chainsaw's formatting preferences to display levels as text instead of icons. -} -- * Example usage {- | In the IO monad: > lh2 <- log4jFileHandler "log.xml" DEBUG > updateGlobalLogger rootLoggerName (addHandler lh2) > h <- connectTo "localhost" (PortNumber 4448) > lh <- log4jStreamHandler h NOTICE > updateGlobalLogger rootLoggerName (addHandler lh) -} -- * References {- | (1) (2) (3) -} ) where import Control.Concurrent (ThreadId, myThreadId) -- myThreadId is GHC only! import Control.Concurrent.MVar import Data.List (isPrefixOf) import System.IO #if MIN_VERSION_time(1,5,0) import Data.Time.Format (defaultTimeLocale) #else import System.Locale (defaultTimeLocale) #endif import Data.Time import System.Log import System.Log.Handler import System.Log.Handler.Simple (streamHandler, GenericHandler(..)) -- Handler that logs to a handle rendering message priorities according -- to the supplied function. log4jHandler :: (Priority -> String) -> Handle -> Priority -> IO (GenericHandler Handle) log4jHandler showPrio h pri = do hndlr <- streamHandler h pri return $ setFormatter hndlr xmlFormatter where -- A Log Formatter that creates an XML element representing a log4j event/message. xmlFormatter :: a -> (Priority,String) -> String -> IO String xmlFormatter _ (prio,msg) logger = do time <- getCurrentTime thread <- myThreadId return . show $ Elem "log4j:event" [ ("logger" , logger ) , ("timestamp", millis time ) , ("level" , showPrio prio) , ("thread" , show thread ) ] (Just $ Elem "log4j:message" [] (Just $ CDATA msg)) where -- This is an ugly hack to get a unix epoch with milliseconds. -- The use of "take 3" causes the milliseconds to always be -- rounded downwards, which I suppose may be the expected -- behaviour for time. millis t = formatTime defaultTimeLocale "%s" t ++ (take 3 $ formatTime defaultTimeLocale "%q" t) -- | Create a stream log handler that uses hslogger priorities. log4jStreamHandler :: Handle -> Priority -> IO (GenericHandler Handle) log4jStreamHandler = log4jHandler show {- | Create a stream log handler that uses log4j levels (priorities). The priorities of messages are shoehorned into log4j levels as follows: @ DEBUG -> DEBUG INFO, NOTICE -> INFO WARNING -> WARN ERROR, CRITICAL, ALERT -> ERROR EMERGENCY -> FATAL @ This is useful when the log will only be consumed by log4j tools and you don't want to go out of your way transforming the log or configuring the tools. -} log4jStreamHandler' :: Handle -> Priority -> IO (GenericHandler Handle) log4jStreamHandler' = log4jHandler show' where show' :: Priority -> String show' NOTICE = "INFO" show' WARNING = "WARN" show' CRITICAL = "ERROR" show' ALERT = "ERROR" show' EMERGENCY = "FATAL" show' p = show p -- Identical for DEBUG, INFO, ERROR. -- | Create a file log handler that uses hslogger priorities. log4jFileHandler :: FilePath -> Priority -> IO (GenericHandler Handle) log4jFileHandler fp pri = do h <- openFile fp AppendMode sh <- log4jStreamHandler h pri return (sh{closeFunc = hClose}) {- | Create a file log handler that uses log4j levels (see 'log4jStreamHandler'' for mappings). -} log4jFileHandler' :: FilePath -> Priority -> IO (GenericHandler Handle) log4jFileHandler' fp pri = do h <- openFile fp AppendMode sh <- log4jStreamHandler' h pri return (sh{closeFunc = hClose}) -- A type for building and showing XML elements. Could use a fancy XML -- library but am reluctant to introduce dependencies. data XML = Elem String [(String, String)] (Maybe XML) | CDATA String instance Show XML where show (CDATA s) = "" where escapeCDATA = replace "]]>" "]]<" -- The best we can do, I guess. show (Elem name attrs child) = "<" ++ name ++ showAttrs attrs ++ showChild child where showAttrs [] = "" showAttrs ((k,v):as) = " " ++ k ++ "=\"" ++ escapeAttr v ++ "\"" ++ showAttrs as where escapeAttr = replace "\"" """ . replace "<" "<" . replace "&" "&" showChild Nothing = "/>" showChild (Just c) = ">" ++ show c ++ "" -- Replaces instances of first list by second list in third list. -- Definition blatantly stoled from jethr0's comment at -- http://bluebones.net/2007/01/replace-in-haskell/. Can be swapped -- with definition (or import) from MissingH. replace :: Eq a => [a] -> [a] -> [a] -> [a] replace _ _ [ ] = [] replace from to xs@(a:as) = if isPrefixOf from xs then to ++ drop (length from) xs else a : replace from to as hslogger-1.2.9/src/System/Log/Handler/Syslog.hs0000600000175000017500000002557312525527476023075 0ustar00jgoerzenjgoerzen00000000000000{-# LANGUAGE CPP #-} {- | Module : System.Log.Handler.Syslog Copyright : Copyright (C) 2004-2011 John Goerzen License : BSD3 Maintainer : John Goerzen Stability : provisional Portability: portable Syslog handler for the Haskell Logging Framework Written by John Goerzen, jgoerzen\@complete.org This module implements an interface to the Syslog service commonly found in Unix\/Linux systems. This interface is primarily of interest to developers of servers, as Syslog does not typically display messages in an interactive fashion. This module is written in pure Haskell and is capable of logging to a local or remote machine using the Syslog protocol. You can create a new Syslog 'LogHandler' by calling 'openlog'. More information on the Haskell Logging Framework can be found at "System.Log.Logger". This module can also be used outside of the rest of that framework for those interested in that. -} module System.Log.Handler.Syslog( -- * Handler Initialization openlog, -- * Advanced handler initialization #ifndef mingw32_HOST_OS openlog_local, #endif openlog_remote, openlog_generic, -- * Data Types Facility(..), Option(..) ) where import qualified Control.Exception as E import System.Log import System.Log.Formatter import System.Log.Handler import Data.Bits import Network.Socket as S import Network.BSD import Data.List #ifndef mingw32_HOST_OS import System.Posix.Process(getProcessID) #endif import System.IO import Control.Monad (void, when) code_of_pri :: Priority -> Int code_of_pri p = case p of EMERGENCY -> 0 ALERT -> 1 CRITICAL -> 2 ERROR -> 3 WARNING -> 4 NOTICE -> 5 INFO -> 6 DEBUG -> 7 {- | Facilities are used by the system to determine where messages are sent. -} data Facility = KERN -- ^ Kernel messages; you should likely never use this in your programs | USER -- ^ General userland messages. Use this if nothing else is appropriate | MAIL -- ^ E-Mail system | DAEMON -- ^ Daemon (server process) messages | AUTH -- ^ Authentication or security messages | SYSLOG -- ^ Internal syslog messages; you should likely never use this in your programs | LPR -- ^ Printer messages | NEWS -- ^ Usenet news | UUCP -- ^ UUCP messages | CRON -- ^ Cron messages | AUTHPRIV -- ^ Private authentication messages | FTP -- ^ FTP messages | LOCAL0 -- ^ LOCAL0 through LOCAL7 are reserved for you to customize as you wish | LOCAL1 | LOCAL2 | LOCAL3 | LOCAL4 | LOCAL5 | LOCAL6 | LOCAL7 deriving (Eq, Show, Read) code_of_fac :: Facility -> Int code_of_fac f = case f of KERN -> 0 USER -> 1 MAIL -> 2 DAEMON -> 3 AUTH -> 4 SYSLOG -> 5 LPR -> 6 NEWS -> 7 UUCP -> 8 CRON -> 9 AUTHPRIV -> 10 FTP -> 11 LOCAL0 -> 16 LOCAL1 -> 17 LOCAL2 -> 18 LOCAL3 -> 19 LOCAL4 -> 20 LOCAL5 -> 21 LOCAL6 -> 22 LOCAL7 -> 23 makeCode :: Facility -> Priority -> Int makeCode fac pri = let faccode = code_of_fac fac pricode = code_of_pri pri in (faccode `shiftL` 3) .|. pricode {- | Options for 'openlog'. -} data Option = PID -- ^ Automatically log process ID (PID) with each message | PERROR -- ^ Send a copy of each message to stderr deriving (Eq,Show,Read) data SyslogHandler = SyslogHandler {options :: [Option], facility :: Facility, identity :: String, logsocket :: Socket, address :: SockAddr, sock_type :: SocketType, priority :: Priority, formatter :: LogFormatter SyslogHandler } {- | Initialize the Syslog system using the local system's default interface, \/dev\/log. Will return a new 'System.Log.Handler.LogHandler'. On Windows, instead of using \/dev\/log, this will attempt to send UDP messages to something listening on the syslog port (514) on localhost. Use 'openlog_remote' if you need more control. -} openlog :: String -- ^ The name of this program -- will be prepended to every log message -> [Option] -- ^ A list of 'Option's. The list [] is perfectly valid. ['PID'] is probably most common here. -> Facility -- ^ The 'Facility' value to pass to the syslog system for every message logged -> Priority -- ^ Messages logged below this priority will be ignored. To include every message, set this to 'DEBUG'. -> IO SyslogHandler -- ^ Returns the new handler #ifdef mingw32_HOST_OS openlog = openlog_remote AF_INET "localhost" 514 #elif darwin_HOST_OS openlog = openlog_local "/var/run/syslog" #else openlog = openlog_local "/dev/log" #endif {- | Initialize the Syslog system using an arbitrary Unix socket (FIFO). Not supported under Windows. -} #ifndef mingw32_HOST_OS openlog_local :: String -- ^ Path to FIFO -> String -- ^ Program name -> [Option] -- ^ 'Option's -> Facility -- ^ Facility value -> Priority -- ^ Priority limit -> IO SyslogHandler openlog_local fifopath ident options fac pri = do (s, t) <- do -- "/dev/log" is usually Datagram, -- but most of syslog loggers allow it to be -- of Stream type. glibc's" openlog()" -- does roughly the similar thing: -- http://www.gnu.org/software/libc/manual/html_node/openlog.html s <- socket AF_UNIX Stream 0 tryStream s `E.catch` (onIOException (fallbackToDgram s)) openlog_generic s (SockAddrUnix fifopath) t ident options fac pri where onIOException :: IO a -> E.IOException -> IO a onIOException a _ = a tryStream :: Socket -> IO (Socket, SocketType) tryStream s = do connect s (SockAddrUnix fifopath) return (s, Stream) fallbackToDgram :: Socket -> IO (Socket, SocketType) fallbackToDgram s = do S.sClose s -- close Stream variant d <- socket AF_UNIX Datagram 0 return (d, Datagram) #endif {- | Log to a remote server via UDP. -} openlog_remote :: Family -- ^ Usually AF_INET or AF_INET6; see Network.Socket -> HostName -- ^ Remote hostname. Some use @localhost@ -> PortNumber -- ^ 514 is the default for syslog -> String -- ^ Program name -> [Option] -- ^ 'Option's -> Facility -- ^ Facility value -> Priority -- ^ Priority limit -> IO SyslogHandler openlog_remote fam hostname port ident options fac pri = do he <- getHostByName hostname s <- socket fam Datagram 0 let addr = SockAddrInet port (head (hostAddresses he)) openlog_generic s addr Datagram ident options fac pri {- | The most powerful initialization mechanism. Takes an open datagram socket. -} openlog_generic :: Socket -- ^ A datagram socket -> SockAddr -- ^ Address for transmissions -> SocketType -- ^ socket connection mode (stream / datagram) -> String -- ^ Program name -> [Option] -- ^ 'Option's -> Facility -- ^ Facility value -> Priority -- ^ Priority limit -> IO SyslogHandler openlog_generic sock addr sock_t ident opt fac pri = return (SyslogHandler {options = opt, facility = fac, identity = ident, logsocket = sock, address = addr, sock_type = sock_t, priority = pri, formatter = syslogFormatter }) syslogFormatter :: LogFormatter SyslogHandler syslogFormatter sh (p,msg) logname = let format = "[$loggername/$prio] $msg" in varFormatter [] format sh (p,msg) logname instance LogHandler SyslogHandler where setLevel sh p = sh{priority = p} getLevel sh = priority sh setFormatter sh f = sh{formatter = f} getFormatter sh = formatter sh emit sh (_, msg) _ = do when (elem PERROR (options sh)) (hPutStrLn stderr msg) pidPart <- getPidPart void $ sendstr (toSyslogFormat msg pidPart) where sendstr :: String -> IO String sendstr [] = return [] sendstr omsg = do sent <- case sock_type sh of Datagram -> sendTo (logsocket sh) omsg (address sh) Stream -> send (logsocket sh) omsg sendstr (genericDrop sent omsg) toSyslogFormat msg pidPart = "<" ++ code ++ ">" ++ identity' ++ pidPart ++ ": " ++ msg ++ "\0" code = show (makeCode (facility sh) (priority sh)) identity' = identity sh getPidPart = if elem PID (options sh) then getPid >>= \pid -> return ("[" ++ pid ++ "]") else return "" getPid :: IO String getPid = #ifndef mingw32_HOST_OS getProcessID >>= return . show #else return "windows" #endif close sh = sClose (logsocket sh) hslogger-1.2.9/src/System/Log/Formatter.hs0000600000175000017500000001066612525527476022200 0ustar00jgoerzenjgoerzen00000000000000{- Copyright (c) 2005-2011 John Goerzen License: BSD3 -} {- | Definition of log formatter support A few basic, and extendable formatters are defined. Please see "System.Log.Logger" for extensive documentation on the logging system. -} module System.Log.Formatter( LogFormatter , nullFormatter , simpleLogFormatter , tfLogFormatter , varFormatter ) where import Data.List import Control.Applicative ((<$>)) import Control.Concurrent (myThreadId) #ifndef mingw32_HOST_OS import System.Posix.Process (getProcessID) #endif #if MIN_VERSION_time(1,5,0) import Data.Time.Format (defaultTimeLocale) #else import System.Locale (defaultTimeLocale) #endif import Data.Time (getZonedTime,getCurrentTime,formatTime) import System.Log -- | A LogFormatter is used to format log messages. Note that it is paramterized on the -- 'Handler' to allow the formatter to use information specific to the handler -- (an example of can be seen in the formatter used in 'System.Log.Handler.Syslog') type LogFormatter a = a -- ^ The LogHandler that the passed message came from -> LogRecord -- ^ The log message and priority -> String -- ^ The logger name -> IO String -- ^ The formatted log message -- | Returns the passed message as is, ie. no formatting is done. nullFormatter :: LogFormatter a nullFormatter _ (_,msg) _ = return msg -- | Takes a format string, and returns a formatter that may be used to -- format log messages. The format string may contain variables prefixed with -- a $-sign which will be replaced at runtime with corresponding values. The -- currently supported variables are: -- -- * @$msg@ - The actual log message -- -- * @$loggername@ - The name of the logger -- -- * @$prio@ - The priority level of the message -- -- * @$tid@ - The thread ID -- -- * @$pid@ - Process ID (Not available on windows) -- -- * @$time@ - The current time -- -- * @$utcTime@ - The current time in UTC Time simpleLogFormatter :: String -> LogFormatter a simpleLogFormatter format h (prio, msg) loggername = tfLogFormatter "%F %X %Z" format h (prio,msg) loggername -- | Like 'simpleLogFormatter' but allow the time format to be specified in the first -- parameter (this is passed to 'Date.Time.Format.formatTime') tfLogFormatter :: String -> String -> LogFormatter a tfLogFormatter timeFormat format = do varFormatter [("time", formatTime defaultTimeLocale timeFormat <$> getZonedTime) ,("utcTime", formatTime defaultTimeLocale timeFormat <$> getCurrentTime) ] format -- | An extensible formatter that allows new substition /variables/ to be defined. -- Each variable has an associated IO action that is used to produce the -- string to substitute for the variable name. The predefined variables are the same -- as for 'simpleLogFormatter' /excluding/ @$time@ and @$utcTime@. varFormatter :: [(String, IO String)] -> String -> LogFormatter a varFormatter vars format h (prio,msg) loggername = do outmsg <- replaceVarM (vars++[("msg", return msg) ,("prio", return $ show prio) ,("loggername", return loggername) ,("tid", show <$> myThreadId) #ifndef mingw32_HOST_OS ,("pid", show <$> getProcessID) #endif ] ) format return outmsg -- | Replace some '$' variables in a string with supplied values replaceVarM :: [(String, IO String)] -- ^ A list of (variableName, action to get the replacement string) pairs -> String -- ^ String to perform substitution on -> IO String -- ^ Resulting string replaceVarM _ [] = return [] replaceVarM keyVals (s:ss) | s=='$' = do (f,rest) <- replaceStart keyVals ss repRest <- replaceVarM keyVals rest return $ f ++ repRest | otherwise = replaceVarM keyVals ss >>= return . (s:) where replaceStart [] str = return ("$",str) replaceStart ((k,v):kvs) str | k `isPrefixOf` str = do vs <- v return (vs, drop (length k) str) | otherwise = replaceStart kvs str hslogger-1.2.9/src/System/Log/Logger.hs0000600000175000017500000005217512525527476021455 0ustar00jgoerzenjgoerzen00000000000000{- | Module : System.Log.Logger Copyright : Copyright (C) 2004-2011 John Goerzen License : BSD3 Maintainer : John Goerzen Stability : provisional Portability: portable Haskell Logging Framework, Primary Interface Written by John Goerzen, jgoerzen\@complete.org Welcome to the error and information logging system for Haskell. This system is patterned after Python\'s @logging@ module, and some of the documentation here was based on documentation there. To log a message, you perform operations on 'Logger's. Each 'Logger' has a name, and they are arranged hierarchically. Periods serve as separators. Therefore, a 'Logger' named \"foo\" is the parent of loggers \"foo.printing\", \"foo.html\", and \"foo.io\". These names can be anything you want. They're used to indicate the area of an application or library in which a logged message originates. Later you will see how you can use this concept to fine-tune logging behaviors based on specific application areas. You can also tune logging behaviors based upon how important a message is. Each message you log will have an importance associated with it. The different importance levels are given by the 'Priority' type. I've also provided some convenient functions that correspond to these importance levels: 'debugM' through 'emergencyM' log messages with the specified importance. Now, an importance level (or 'Priority') is associated not just with a particular message but also with a 'Logger'. If the 'Priority' of a given log message is lower than the 'Priority' configured in the 'Logger', that message is ignored. This way, you can globally control how verbose your logging output is. Now, let's follow what happens under the hood when you log a message. We'll assume for the moment that you are logging something with a high enough 'Priority' that it passes the test in your 'Logger'. In your code, you'll call 'logM' or something like 'debugM' to log the message. Your 'Logger' decides to accept the message. What next? Well, we also have a notion of /handlers/ ('LogHandler's, to be precise). A 'LogHandler' is a thing that takes a message and sends it somewhere. That \"somewhere\" may be your screen (via standard error), your system's logging infrastructure (via syslog), a file, or other things. Each 'Logger' can have zero or more 'LogHandler's associated with it. When your 'Logger' has a message to log, it passes it to every 'LogHandler' it knows of to process. What's more, it is also passed to /all handlers of all ancestors of the Logger/, regardless of whether those 'Logger's would normally have passed on the message. Each 'Logger' can /optionally/ store a 'Priority'. If a given Logger does not have a Priority, and you log a message to that logger, the system will use the priority of the parent of the destination logger to find out whether to log the message. If the parent has no priority associated with it, the system continues walking up the tree to figure out a priority until it hits the root logger. In this way, you can easily adjust the priority of an entire subtree of loggers. When a new logger is created, it has no priority by default. The exception is the root logger, which has a WARNING priority by default. To give you one extra little knob to turn, 'LogHandler's can also have importance levels ('Priority') associated with them in the same way that 'Logger's do. They act just like the 'Priority' value in the 'Logger's -- as a filter. It's useful, for instance, to make sure that under no circumstances will a mere 'DEBUG' message show up in your syslog. There are three built-in handlers given in two built-in modules: "System.Log.Handler.Simple" and "System.Log.Handler.Syslog". There is a special logger known as the /root logger/ that sits at the top of the logger hierarchy. It is always present, and handlers attached there will be called for every message. You can use 'getRootLogger' to get it or 'rootLoggerName' to work with it by name. The formatting of log messages may be customized by setting a 'LogFormatter' on the desired 'LogHandler'. There are a number of simple formatters defined in "System.Log.Formatter", which may be used directly, or extend to create your own formatter. Here's an example to illustrate some of these concepts: > import System.Log.Logger > import System.Log.Handler.Syslog > import System.Log.Handler.Simple > import System.Log.Handler (setFormatter) > import System.Log.Formatter > > -- By default, all messages of level WARNING and above are sent to stderr. > -- Everything else is ignored. > > -- "MyApp.Component" is an arbitrary string; you can tune > -- logging behavior based on it later. > main = do > debugM "MyApp.Component" "This is a debug message -- never to be seen" > warningM "MyApp.Component2" "Something Bad is about to happen." > > -- Copy everything to syslog from here on out. > s <- openlog "SyslogStuff" [PID] USER DEBUG > updateGlobalLogger rootLoggerName (addHandler s) > > errorM "MyApp.Component" "This is going to stderr and syslog." > > -- Now we'd like to see everything from BuggyComponent > -- at DEBUG or higher go to syslog and stderr. > -- Also, we'd like to still ignore things less than > -- WARNING in other areas. > -- > -- So, we adjust the Logger for MyApp.BuggyComponent. > > updateGlobalLogger "MyApp.BuggyComponent" > (setLevel DEBUG) > > -- This message will go to syslog and stderr > debugM "MyApp.BuggyComponent" "This buggy component is buggy" > > -- This message will go to syslog and stderr too. > warningM "MyApp.BuggyComponent" "Still Buggy" > > -- This message goes nowhere. > debugM "MyApp.WorkingComponent" "Hello" > > -- Now we decide we'd also like to log everything from BuggyComponent at DEBUG > -- or higher to a file for later diagnostics. We'd also like to customize the > -- format of the log message, so we use a 'simpleLogFormatter' > > h <- fileHandler "debug.log" DEBUG >>= \lh -> return $ > setFormatter lh (simpleLogFormatter "[$time : $loggername : $prio] $msg") > updateGlobalLogger "MyApp.BuggyComponent" (addHandler h) > > -- This message will go to syslog and stderr, > -- and to the file "debug.log" with a format like : > -- [2010-05-23 16:47:28 : MyApp.BuggyComponent : DEBUG] Some useful diagnostics... > debugM "MyApp.BuggyComponent" "Some useful diagnostics..." > > -} module System.Log.Logger( -- * Basic Types Logger, -- ** Re-Exported from System.Log Priority(..), -- * Logging Messages -- ** Basic logM, -- ** Utility Functions -- These functions are wrappers for 'logM' to -- make your job easier. debugM, infoM, noticeM, warningM, errorM, criticalM, alertM, emergencyM, removeAllHandlers, traplogging, -- ** Logging to a particular Logger by object logL, -- * Logger Manipulation {- | These functions help you work with loggers. There are some special things to be aware of. First of all, whenever you first access a given logger by name, it magically springs to life. It has a default 'Priority' of Nothing and an empty handler list -- which means that it will inherit whatever its parents do. -} -- ** Finding \/ Creating Loggers getLogger, getRootLogger, rootLoggerName, -- ** Modifying Loggers {- | Keep in mind that \"modification\" here is modification in the Haskell sense. We do not actually cause mutation in a specific 'Logger'. Rather, we return you a new 'Logger' object with the change applied. Also, please note that these functions will not have an effect on the global 'Logger' hierarchy. You may use your new 'Logger's locally, but other functions won't see the changes. To make a change global, you'll need to use 'updateGlobalLogger' or 'saveGlobalLogger'. -} addHandler, removeHandler, setHandlers, getLevel, setLevel, clearLevel, -- ** Saving Your Changes {- | These functions commit changes you've made to loggers to the global logger hierarchy. -} saveGlobalLogger, updateGlobalLogger ) where import System.Log import System.Log.Handler(LogHandler, close) import System.Log.Formatter(LogFormatter) import qualified System.Log.Handler(handle) import System.Log.Handler.Simple import System.IO import System.IO.Unsafe import Control.Concurrent.MVar import Data.List(map, isPrefixOf) import Data.Maybe import qualified Data.Map as Map import qualified Control.Exception import Control.Monad.Error --------------------------------------------------------------------------- -- Basic logger types --------------------------------------------------------------------------- data HandlerT = forall a. LogHandler a => HandlerT a data Logger = Logger { level :: Maybe Priority, handlers :: [HandlerT], name :: String} type LogTree = Map.Map String Logger {- | This is the base class for the various log handlers. They should all adhere to this class. -} --------------------------------------------------------------------------- -- Utilities --------------------------------------------------------------------------- -- | The name of the root logger, which is always defined and present -- on the system. rootLoggerName :: String rootLoggerName = "" --------------------------------------------------------------------------- -- Logger Tree Storage --------------------------------------------------------------------------- -- | The log tree. Initialize it with a default root logger -- and (FIXME) a logger for MissingH itself. {-# NOINLINE logTree #-} logTree :: MVar LogTree -- note: only kick up tree if handled locally logTree = unsafePerformIO $ do h <- streamHandler stderr DEBUG newMVar (Map.singleton rootLoggerName (Logger {level = Just WARNING, name = "", handlers = [HandlerT h]})) {- | Given a name, return all components of it, starting from the root. Example return value: >["", "MissingH", "System.Cmd.Utils", "System.Cmd.Utils.pOpen"] -} componentsOfName :: String -> [String] componentsOfName name = let joinComp [] _ = [] joinComp (x:xs) [] = x : joinComp xs x joinComp (x:xs) accum = let newlevel = accum ++ "." ++ x in newlevel : joinComp xs newlevel in rootLoggerName : joinComp (split "." name) [] --------------------------------------------------------------------------- -- Logging With Location --------------------------------------------------------------------------- {- | Log a message using the given logger at a given priority. -} logM :: String -- ^ Name of the logger to use -> Priority -- ^ Priority of this message -> String -- ^ The log text itself -> IO () logM logname pri msg = do l <- getLogger logname logL l pri msg --------------------------------------------------------------------------- -- Utility functions --------------------------------------------------------------------------- {- | Log a message at 'DEBUG' priority -} debugM :: String -- ^ Logger name -> String -- ^ Log message -> IO () debugM s = logM s DEBUG {- | Log a message at 'INFO' priority -} infoM :: String -- ^ Logger name -> String -- ^ Log message -> IO () infoM s = logM s INFO {- | Log a message at 'NOTICE' priority -} noticeM :: String -- ^ Logger name -> String -- ^ Log message -> IO () noticeM s = logM s NOTICE {- | Log a message at 'WARNING' priority -} warningM :: String -- ^ Logger name -> String -- ^ Log message -> IO () warningM s = logM s WARNING {- | Log a message at 'ERROR' priority -} errorM :: String -- ^ Logger name -> String -- ^ Log message -> IO () errorM s = logM s ERROR {- | Log a message at 'CRITICAL' priority -} criticalM :: String -- ^ Logger name -> String -- ^ Log message -> IO () criticalM s = logM s CRITICAL {- | Log a message at 'ALERT' priority -} alertM :: String -- ^ Logger name -> String -- ^ Log message -> IO () alertM s = logM s ALERT {- | Log a message at 'EMERGENCY' priority -} emergencyM :: String -- ^ Logger name -> String -- ^ Log message -> IO () emergencyM s = logM s EMERGENCY --------------------------------------------------------------------------- -- Public Logger Interaction Support --------------------------------------------------------------------------- -- | Returns the logger for the given name. If no logger with that name -- exists, creates new loggers and any necessary parent loggers, with -- no connected handlers. getLogger :: String -> IO Logger getLogger lname = modifyMVar logTree $ \lt -> case Map.lookup lname lt of Just x -> return (lt, x) -- A logger exists; return it and leave tree Nothing -> do -- Add logger(s). Then call myself to retrieve it. let newlt = createLoggers (componentsOfName lname) lt let result = fromJust $ Map.lookup lname newlt return (newlt, result) where createLoggers :: [String] -> LogTree -> LogTree createLoggers [] lt = lt -- No names to add; return tree unmodified createLoggers (x:xs) lt = -- Add logger to tree if Map.member x lt then createLoggers xs lt else createLoggers xs (Map.insert x (defaultLogger {name=x}) lt) defaultLogger = Logger Nothing [] undefined -- | Returns the root logger. getRootLogger :: IO Logger getRootLogger = getLogger rootLoggerName -- | Log a message, assuming the current logger's level permits it. logL :: Logger -> Priority -> String -> IO () logL l pri msg = handle l (pri, msg) -- | Handle a log request. handle :: Logger -> LogRecord -> IO () handle l (pri, msg) = let parentLoggers :: String -> IO [Logger] parentLoggers [] = return [] parentLoggers name = let pname = (head . drop 1 . reverse . componentsOfName) name in do parent <- getLogger pname next <- parentLoggers pname return (parent : next) parentHandlers :: String -> IO [HandlerT] parentHandlers name = parentLoggers name >>= (return . concatMap handlers) -- Get the priority we should use. Find the first logger in the tree, -- starting here, with a set priority. If even root doesn't have one, -- assume DEBUG. getLoggerPriority :: String -> IO Priority getLoggerPriority name = do pl <- parentLoggers name case catMaybes . map level $ (l : pl) of [] -> return DEBUG (x:_) -> return x in do lp <- getLoggerPriority (name l) if pri >= lp then do ph <- parentHandlers (name l) sequence_ (handlerActions (ph ++ (handlers l)) (pri, msg) (name l)) else return () -- | Call a handler given a HandlerT. callHandler :: LogRecord -> String -> HandlerT -> IO () callHandler lr loggername ht = case ht of HandlerT x -> System.Log.Handler.handle x lr loggername -- | Generate IO actions for the handlers. handlerActions :: [HandlerT] -> LogRecord -> String -> [IO ()] handlerActions h lr loggername = map (callHandler lr loggername ) h -- | Add handler to 'Logger'. Returns a new 'Logger'. addHandler :: LogHandler a => a -> Logger -> Logger addHandler h l= l{handlers = (HandlerT h) : (handlers l)} -- | Remove a handler from the 'Logger'. Handlers are removed in the reverse -- order they were added, so the following property holds for any 'LogHandler' -- @h@: -- -- > removeHandler . addHandler h = id -- -- If no handlers are associated with the 'Logger', it is returned unchanged. -- -- The root logger's default handler that writes every message to stderr can -- be removed by using this function before any handlers have been added -- to the root logger: -- -- > updateGlobalLogger rootLoggerName removeHandler removeHandler :: Logger -> Logger removeHandler l = case hs of [] -> l _ -> l{handlers = tail hs} where hs = handlers l -- | Set the 'Logger'\'s list of handlers to the list supplied. -- All existing handlers are removed first. setHandlers :: LogHandler a => [a] -> Logger -> Logger setHandlers hl l = l{handlers = map (\h -> HandlerT h) hl} -- | Returns the "level" of the logger. Items beneath this -- level will be ignored. getLevel :: Logger -> Maybe Priority getLevel l = level l -- | Sets the "level" of the 'Logger'. Returns a new -- 'Logger' object with the new level. setLevel :: Priority -> Logger -> Logger setLevel p l = l{level = Just p} -- | Clears the "level" of the 'Logger'. It will now inherit the level of -- | its parent. clearLevel :: Logger -> Logger clearLevel l = l {level = Nothing} -- | Updates the global record for the given logger to take into -- account any changes you may have made. saveGlobalLogger :: Logger -> IO () saveGlobalLogger l = modifyMVar_ logTree (\lt -> return $ Map.insert (name l) l lt) {- | Helps you make changes on the given logger. Takes a function that makes changes and writes those changes back to the global database. Here's an example from above (\"s\" is a 'LogHandler'): > updateGlobalLogger "MyApp.BuggyComponent" > (setLevel DEBUG . setHandlers [s]) -} updateGlobalLogger :: String -- ^ Logger name -> (Logger -> Logger) -- ^ Function to call -> IO () updateGlobalLogger ln func = do l <- getLogger ln saveGlobalLogger (func l) -- | Allow gracefull shutdown. Release all opened files/handlers/etc. removeAllHandlers :: IO () removeAllHandlers = modifyMVar_ logTree $ \lt -> do let allHandlers = Map.fold (\l r -> concat [r, handlers l]) [] lt mapM_ (\(HandlerT h) -> close h) allHandlers return $ Map.map (\l -> l {handlers = []}) lt {- | Traps exceptions that may occur, logging them, then passing them on. Takes a logger name, priority, leading description text (you can set it to @\"\"@ if you don't want any), and action to run. -} traplogging :: String -- Logger name -> Priority -- Logging priority -> String -- Descriptive text to prepend to logged messages -> IO a -- Action to run -> IO a -- Return value traplogging logger priority desc action = let realdesc = case desc of "" -> "" x -> x ++ ": " handler :: Control.Exception.SomeException -> IO a handler e = do logM logger priority (realdesc ++ (show e)) Control.Exception.throw e -- Re-raise it in Control.Exception.catch action handler {- This function pulled in from MissingH to avoid a dep on it -} split :: Eq a => [a] -> [a] -> [[a]] split _ [] = [] split delim str = let (firstline, remainder) = breakList (isPrefixOf delim) str in firstline : case remainder of [] -> [] x -> if x == delim then [] : [] else split delim (drop (length delim) x) -- This function also pulled from MissingH breakList :: ([a] -> Bool) -> [a] -> ([a], [a]) breakList func = spanList (not . func) -- This function also pulled from MissingH spanList :: ([a] -> Bool) -> [a] -> ([a], [a]) spanList _ [] = ([],[]) spanList func list@(x:xs) = if func list then (x:ys,zs) else ([],list) where (ys,zs) = spanList func xs hslogger-1.2.9/src/System/Log/Handler.hs0000600000175000017500000000420412525527476021601 0ustar00jgoerzenjgoerzen00000000000000{- | Module : System.Log.Handler Copyright : Copyright (C) 2004-2011 John Goerzen License : BSD3 Maintainer : John Goerzen Stability : provisional Portability: portable Definition of log handler support For some handlers, check out "System.Log.Handler.Simple" and "System.Log.Handler.Syslog". Please see "System.Log.Logger" for extensive documentation on the logging system. Written by John Goerzen, jgoerzen\@complete.org -} module System.Log.Handler(-- * Basic Types LogHandler(..) ) where import System.Log import System.Log.Formatter import System.IO {- | All log handlers should adhere to this. -} {- | This is the base class for the various log handlers. They should all adhere to this class. -} class LogHandler a where -- | Sets the log level. 'handle' will drop -- items beneath this level. setLevel :: a -> Priority -> a -- | Gets the current level. getLevel :: a -> Priority -- | Set a log formatter to customize the log format for this Handler setFormatter :: a -> LogFormatter a -> a getFormatter :: a -> LogFormatter a getFormatter h = nullFormatter -- | Logs an event if it meets the requirements -- given by the most recent call to 'setLevel'. handle :: a -> LogRecord -> String-> IO () handle h (pri, msg) logname = if pri >= (getLevel h) then do formattedMsg <- (getFormatter h) h (pri,msg) logname emit h (pri, formattedMsg) logname else return () -- | Forces an event to be logged regardless of -- the configured level. emit :: a -> LogRecord -> String -> IO () -- | Closes the logging system, causing it to close -- any open files, etc. close :: a -> IO () hslogger-1.2.9/testsrc/0000755000175000017500000000000012525527476016573 5ustar00jgoerzenjgoerzen00000000000000hslogger-1.2.9/testsrc/Tests.hs0000600000175000017500000000034212525527476020220 0ustar00jgoerzenjgoerzen00000000000000{- arch-tag: Tests main file Copyright (C) 2004 John Goerzen License: BSD3 -} module Tests(tests) where import Test.HUnit test1 = TestCase ("x" @=? "x") tests = TestList [TestLabel "test1" test1] hslogger-1.2.9/testsrc/runtests.hs0000600000175000017500000000026412525527476021010 0ustar00jgoerzenjgoerzen00000000000000{- arch-tag: Test runner Copyright (C) 2004-2011 John Goerzen License: BSD3 -} module Main where import Test.HUnit import Tests main = runTestTT tests hslogger-1.2.9/hslogger.cabal0000600000175000017500000000405412525527476017675 0ustar00jgoerzenjgoerzen00000000000000Name: hslogger Version: 1.2.9 License: BSD3 Maintainer: John Goerzen Author: John Goerzen Stability: Stable Copyright: Copyright (c) 2004-2012 John Goerzen license-file: LICENSE build-type: Simple Homepage: http://software.complete.org/hslogger Synopsis: Versatile logging framework Description: hslogger is a logging framework for Haskell, roughly similar to Python's logging module. . hslogger lets each log message have a priority and source be associated with it. The programmer can then define global handlers that route or filter messages based on the priority and source. hslogger also has a syslog handler built in. Category: Interfaces extra-source-files: LICENSE, contrib/java/build.xml, contrib/java/hslogger4j.jar, contrib/java/hslogger4j-plugins.xml, contrib/java/org/haskell/hslogger/HsloggerLevel.java, contrib/java/org/haskell/hslogger/LogFileXMLReceiver.java, contrib/java/org/haskell/hslogger/XMLDecoder.java, testsrc/Tests.hs, testsrc/runtests.hs, winbuild.bat Cabal-Version: >= 1.6 flag small_base description: choose the new smaller, split-up base package. flag buildtests description: Build the executable to run unit tests default: False Library Exposed-Modules: System.Log, System.Log.Handler, System.Log.Formatter, System.Log.Handler.Simple, System.Log.Handler.Syslog, System.Log.Handler.Growl, System.Log.Handler.Log4jXML, System.Log.Logger Extensions: CPP, ExistentialQuantification Build-Depends: network, mtl if !os(windows) Build-Depends: unix if flag(small_base) build-depends: base >= 4 && < 5, containers, directory, process, time, old-locale else build-depends: base < 3, time -- GHC-Options: -O2 Hs-Source-Dirs: src Executable runtests if flag(buildtests) Buildable: True else Buildable: False Main-Is: runtests.hs HS-Source-Dirs: testsrc, . Extensions: ExistentialQuantification, OverlappingInstances, UndecidableInstances, CPP