log-effect-0.4.0.1: An extensible log effect using extensible-effects

Safe HaskellNone

Control.Eff.Log

Synopsis

Documentation

data Log a v Source

Constructors

Log a v 

Instances

type Logger m l = forall v. Log l v -> m ()Source

a monadic action that does the real logging

logE :: (Typeable l, Member (Log l) r) => l -> Eff r ()Source

Log something.

filterLog :: (Typeable l, Member (Log l) r) => (l -> Bool) -> Eff r a -> Eff r aSource

Filter Log entries with a predicate.

Note that, most of the time an explicit type signature for the predicate will be required.

filterLog' :: (Typeable l, Member (Log l) r) => (l -> Bool) -> proxy l -> Eff r a -> Eff r aSource

Filter Log entries with a predicate and a proxy.

This is the same as filterLog but with a proxy l for type inference.

runLogPure :: Typeable l => Eff (Log l :> r) a -> Eff r (a, [l])Source

Collect log messages in a list.

runLogStdout :: (Typeable l, ToLogStr l, SetMember Lift (Lift IO) r) => proxy l -> Eff (Log l :> r) a -> Eff r aSource

Log to stdout.

runLogStderr :: (Typeable l, ToLogStr l, SetMember Lift (Lift IO) r) => proxy l -> Eff (Log l :> r) a -> Eff r aSource

Log to stderr.

runLogFile :: (Typeable l, ToLogStr l, SetMember Lift (Lift IO) r) => FilePath -> proxy l -> Eff (Log l :> r) a -> Eff r aSource

Log to file.

runLogWithLoggerSet :: (Typeable l, ToLogStr l, SetMember Lift (Lift IO) r) => LoggerSet -> proxy l -> Eff (Log l :> r) a -> Eff r aSource

Log to a file using a LoggerSet.

Note, that you will still have to call flushLogStr on the LoggerSet at one point.

With that function you can combine a logger in a surrounding IO action with a logger in the Eff effect.

data Proxy a = Proxy

 main :: IO ()
 main = do
     loggerSet <- newStderrLoggerSet defaultBufSize
     pushLogStr loggerSet "logging from outer space^WIO\n"
     runLift $ runLogWithLoggerSet loggerSet (Proxy :: Proxy String) $
         logE ("logging from within Eff" :: String)
     flushLogStr loggerSet

runLog :: (Typeable l, Typeable1 m, SetMember Lift (Lift m) r) => Logger m l -> Eff (Log l :> r) a -> Eff r aSource

Run the Logger action in the base monad for every log line.