| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Log.Extra.File
Contents
Synopsis
- logEmergencyTH :: Q Exp
- logAlertTH :: Q Exp
- logCriticalTH :: Q Exp
- logErrorTH :: Q Exp
- logWarningTH :: Q Exp
- logNoticeTH :: Q Exp
- logInfoTH :: Q Exp
- logInformationalTH :: Q Exp
- logDebugTH :: Q Exp
- logMessageTH :: Q Exp
- data WithFile a = WithFile {
- msgLoc :: Loc
- discardFile :: a
- renderWithFile :: (a -> Doc ann) -> WithFile a -> Doc ann
- logSeverityMessageTH :: Severity -> Q Exp
- liftLoc :: Loc -> Q Exp
- data Loc = Loc {}
Getting Started
logging-effect-extra-file supplements logging-effect
with TH splices that capture file information.
Quickstart using file info and severity
testAppFileAndSeverity ::MonadLog(WithSeverity(WithFile(Docann))) m => m () testAppFileAndSeverity = do $(logEmergencyTH) "GAH! All systems are down!!!" $(logAlertTH) "Red alert!" $(logCriticalTH) "Critical hit!" $(logErrorTH) "Errors abound!" $(logWarningTH) "Cargo number 2331 has commandeered the vessel" $(logNoticeTH) "Heads up, but it's no biggie." $(logInfoTH) "Does anyone read these?" $(logDebugTH) "Sleuthing with log messages..."
Quickstart using only file info
testAppFileOnly ::MonadLog(WithFile(Docann)) m => m () testAppFileOnly = $(logMessageTH) "Heyo!!!"
Convenience logging combinators (TH)
logging-effect-extra-file provides combinators for:
- adding file info to messages (module name and line number)
- adding both file info and severity to messages
In the former case, WithFile will be at the outer-most level of your log
message stack. In the latter case, WithSeverity will be at the outer-most
level of your log message stack, wrapping WithFile.
The package makes no assumptions on what is inside your log messages though.
There is a logXTH combinator for each level in Severity.
With severity
logEmergencyTH :: Q Exp Source #
Generates a function that logs an Emergency message with info from the
source file.
$(logEmergencyTH) "GAH! All systems are down!!!"
logAlertTH :: Q Exp Source #
Generates a function that logs an Alert message with info from the
source file.
$(logAlertTH) "Red alert!"
logCriticalTH :: Q Exp Source #
Generates a function that logs a Critical message with info from the
source file.
$(logCriticalTH) "Critical hit!"
logErrorTH :: Q Exp Source #
Generates a function that logs an Error message with info from the
source file.
$(logErrorTH) "Errors abound!"
logWarningTH :: Q Exp Source #
Generates a function that logs a Warning message with info from the
source file.
$(logWarningTH) "Cargo number 2331 has commandeered the vessel"
logNoticeTH :: Q Exp Source #
Generates a function that logs a Notice message with info from the
source file.
$(logNoticeTH) "Heads up, but it's no biggie."
Generates a function that logs an Informational message with info from the
source file.
$(logInfoTH) "Does anyone read these?"
logInformationalTH :: Q Exp Source #
Deprecated: logInformationalTH is deprecated in favor of logInfoTH.
Generates a function that logs an Informational message with info from the
source file.
$(logInformationalTH) "Does anyone read these?"
logDebugTH :: Q Exp Source #
Generates a function that logs a Debug message with info from the
source file.
$(logDebugTH) "Sleuthing with log messages..."
Without severity
logMessageTH :: Q Exp Source #
Generates a function that logs a message with info from the source file.
$(logMessageTH) "Burn after reading."
Message transformers
File info
Add "File" information to a log message.
Constructors
| WithFile | |
Fields
| |
Instances
| Functor WithFile Source # | |
| Foldable WithFile Source # | |
Defined in Control.Monad.Log.Extra.File Methods fold :: Monoid m => WithFile m -> m # foldMap :: Monoid m => (a -> m) -> WithFile a -> m # foldr :: (a -> b -> b) -> b -> WithFile a -> b # foldr' :: (a -> b -> b) -> b -> WithFile a -> b # foldl :: (b -> a -> b) -> b -> WithFile a -> b # foldl' :: (b -> a -> b) -> b -> WithFile a -> b # foldr1 :: (a -> a -> a) -> WithFile a -> a # foldl1 :: (a -> a -> a) -> WithFile a -> a # elem :: Eq a => a -> WithFile a -> Bool # maximum :: Ord a => WithFile a -> a # minimum :: Ord a => WithFile a -> a # | |
| Traversable WithFile Source # | |
Defined in Control.Monad.Log.Extra.File | |
| Eq a => Eq (WithFile a) Source # | |
| Ord a => Ord (WithFile a) Source # | |
Defined in Control.Monad.Log.Extra.File | |
| Show a => Show (WithFile a) Source # | |
renderWithFile :: (a -> Doc ann) -> WithFile a -> Doc ann Source #
Given a way to render the underlying message a, render a message with its
file info.
>>>:set -XOverloadedStrings>>>let loc = Loc "SomeFile.hs" "some-package" "SomeModule" (1, 1) (1, 1)>>>renderWithFile id (WithFile loc "Some message")[some-package:SomeModule SomeFile.hs:1:1] Some message
Utilities
logSeverityMessageTH :: Severity -> Q Exp Source #
Generates a function that logs a message with the given Severity and
info from the source file.
Re-exports
Constructors
| Loc | |
Fields
| |
Instances
| Eq Loc | |
| Data Loc | |
Defined in Language.Haskell.TH.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc # dataTypeOf :: Loc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Loc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) # gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r # gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc # | |
| Ord Loc | |
| Show Loc | |
| Generic Loc | |
| type Rep Loc | |
Defined in Language.Haskell.TH.Syntax type Rep Loc = D1 (MetaData "Loc" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Loc" PrefixI True) ((S1 (MetaSel (Just "loc_filename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "loc_package") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "loc_module") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "loc_start") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CharPos) :*: S1 (MetaSel (Just "loc_end") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CharPos))))) | |