gore-and-ash-logging-2.0.1.0: Core module for gore-and-ash with logging utilities

Copyright(c) Anton Gushcha, 2015-2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.Logging

Contents

Description

The module contains all API for Gore&Ash logging module. The module doesn't depends on others core modules and could be place in any place in game monad stack.

The core module is not pure on it first phase and could be used with IO as end monad. See ModuleStack documentation.

Example of embedding:

-- | Application monad is monad stack build from given list of modules over base monad (IO)
type AppStack = ModuleStack [LoggingT, ... other modules ... ] IO
newtype AppState = AppState (ModuleState AppStack)
  deriving (Generic)

instance NFData AppState

-- | Wrapper around type family
newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, LoggingMonad, ... other modules monads ... )

instance GameModule AppMonad AppState where
  type ModuleState AppMonad = AppState
  runModule (AppMonad m) (AppState s) = do
    (a, s') <- runModule m s
    return (a, AppState s')
  newModuleState = AppState $ newModuleState
  withModule _ = withModule (Proxy :: Proxy AppStack)
  cleanupModule (AppState s) = cleanupModule s

-- | Arrow that is build over the monad stack
type AppWire a b = GameWire AppMonad a b

playerActor :: ActorMonad m => (PlayerId -> Player) -> GameActor m PlayerId Game Player playerActor initialPlayer = makeActor $ i -> stateWire (initialPlayer i) $ mainController i where mainController i = proc (g, p) -> do

@

Synopsis

Low-level API

data LoggingState s Source

Inner state of logger.

s
next state, states of modules are chained via nesting

Instances

data LoggingT s m a Source

Monad transformer of logging core module.

s
- State of next core module in modules chain;
m
- Next monad in modules monad stack;
a
- Type of result value;

How to embed module:

type AppStack = ModuleStack [LoggingT, ... other modules ... ] IO

newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, LoggingMonad)

The module is pure within first phase (see ModuleStack docs) and could be used with Identity end monad.

Instances

MonadBase IO m => MonadBase IO (LoggingT s m) Source 
MonadError e m => MonadError e (LoggingT s m) Source 
MonadTrans (LoggingT s) Source 
Monad m => MonadState (LoggingState s) (LoggingT s m) Source 
Monad m => Monad (LoggingT s m) Source 
Functor m => Functor (LoggingT s m) Source 
MonadFix m => MonadFix (LoggingT s m) Source 
Monad m => Applicative (LoggingT s m) Source 
MonadIO m => MonadIO (LoggingT s m) Source 
MonadThrow m => MonadThrow (LoggingT s m) Source 
MonadMask m => MonadMask (LoggingT s m) Source 
MonadCatch m => MonadCatch (LoggingT s m) Source 
MonadResource m => MonadResource (LoggingT s m) Source 
MonadIO m => LoggingMonad (LoggingT s m) Source 
type ModuleState (LoggingT s m) = LoggingState s Source 

data LoggingLevel Source

Describes important of logging message

Constructors

LogDebug

Used for detailed logging

LogInfo

Used for messages about normal operation of application

LogWarn

Used for recoverable errors or defaulting to fallback behavior

LogError

Used before throwing an exception or fatal fales

LogMuted

Special case of message, that never goes to console, but saved into file

class MonadIO m => LoggingMonad m where Source

Low level API for module

Methods

putMsgM :: LoggingLevel -> Text -> m () Source

Put message to the console.

putMsgLnM :: LoggingLevel -> Text -> m () Source

Put message and new line to the console.

loggingSetHandle :: Handle -> m () Source

Setting current logging file handler

loggingSetFilter :: LoggingLevel -> [LoggingSink] -> m () Source

Setting allowed sinks for given logging level.

By default all messages are passed into file and console.

Instances

loggingSetFile Source

Arguments

:: LoggingMonad m 
=> FilePath

Path to logging file

-> Bool

If False, rewrites contents of the file, if True opens in append mode

-> m () 

Helper to set logging file as local path

Arrow API

logA :: LoggingMonad m => LoggingLevel -> GameWire m Text () Source

Put message to console on every frame without newline

logALn :: LoggingMonad m => LoggingLevel -> GameWire m Text () Source

Put message to console on every frame

logE :: LoggingMonad m => LoggingLevel -> GameWire m (Event Text) (Event ()) Source

Put message to console on event without newline

logELn :: LoggingMonad m => LoggingLevel -> GameWire m (Event Text) (Event ()) Source

Put message to console on event

Every frame

logDebugA :: LoggingMonad m => GameWire m Text () Source

Put info msg to console

logInfoA :: LoggingMonad m => GameWire m Text () Source

Put info msg to console

logWarnA :: LoggingMonad m => GameWire m Text () Source

Put warn msg to console

logErrorA :: LoggingMonad m => GameWire m Text () Source

Put error msg to console

Event based

logDebugE :: LoggingMonad m => GameWire m (Event Text) (Event ()) Source

Put info msg to console on event

logInfoE :: LoggingMonad m => GameWire m (Event Text) (Event ()) Source

Put info msg to console on event

logWarnE :: LoggingMonad m => GameWire m (Event Text) (Event ()) Source

Put warn msg to console on event

logErrorE :: LoggingMonad m => GameWire m (Event Text) (Event ()) Source

Put error msg to console on event

Event tracing

traceEvent :: LoggingMonad m => (a -> Text) -> GameWire m (Event a) (Event ()) Source

Prints event with given function

traceEventShow :: (TextShow a, LoggingMonad m) => GameWire m (Event a) (Event ()) Source

Prints event