method-0.4.0.0: rebindable methods for improving testability
LicenseBSD-3
Maintainerautotaker@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Test.Method.Monitor

Description

Validating method calls by monitoring

Synopsis

Documentation

data Event args ret Source #

Event args ret is a function call event

Instances

Instances details
(Eq args, Eq ret) => Eq (Event args ret) Source # 
Instance details

Defined in Test.Method.Monitor.Internal

Methods

(==) :: Event args ret -> Event args ret -> Bool #

(/=) :: Event args ret -> Event args ret -> Bool #

(Ord args, Ord ret) => Ord (Event args ret) Source # 
Instance details

Defined in Test.Method.Monitor.Internal

Methods

compare :: Event args ret -> Event args ret -> Ordering #

(<) :: Event args ret -> Event args ret -> Bool #

(<=) :: Event args ret -> Event args ret -> Bool #

(>) :: Event args ret -> Event args ret -> Bool #

(>=) :: Event args ret -> Event args ret -> Bool #

max :: Event args ret -> Event args ret -> Event args ret #

min :: Event args ret -> Event args ret -> Event args ret #

(Show args, Show ret) => Show (Event args ret) Source # 
Instance details

Defined in Test.Method.Monitor.Internal

Methods

showsPrec :: Int -> Event args ret -> ShowS #

show :: Event args ret -> String #

showList :: [Event args ret] -> ShowS #

data Monitor args ret Source #

Monitor arg ret is an event monitor of methods, which logs method calls.

newMonitor :: IO (Monitor args ret) Source #

Generate new instance of Monitor

watch :: (Method method, MonadUnliftIO (Base method)) => Monitor (Args method) (Ret method) -> method -> method Source #

Simplified version of watchBy. It is suitable to monitor single method.

watchBy :: (Method method, MonadUnliftIO (Base method)) => (Args method -> args) -> (Ret method -> ret) -> Monitor args ret -> method -> method Source #

watchBy fArgs fRet monitor method decorates method so that monitor logs the method calls. This function is suited for monitoring multiple methods.

fArgs and fRet is converter for arguments/return values of given method.

foo :: Int -> IO String
foo = ...
bar :: Int -> String -> IO ()
bar = ...

data MonitorArgs = FooArgs Int | BarArgs (Int,String) deriving(Eq,Show)
data MonitorRet = FooRet String | BarRet () deriving(Eq, Show)

foo' :: Monitor MonitorArgs MonitorRet -> Int -> IO String
foo' monitor = watch monitor (FooArgs . toTuple) FooRet foo
bar' :: Monitor MonitorArgs MonitorRet -> Int -> String -> IO ()
bar' monitor = watch monitor (BarArgs . toTuple) BarRet bar

listenEventLog :: MonadIO m => Monitor args ret -> m [Event args ret] Source #

Get current event logs from monitor

withMonitor :: MonadIO m => (Monitor args ret -> m a) -> m (a, [Event args ret]) Source #

withMonitor f calls f with Monitor, and then returns monitored event logs during the function call in addition to the return value of the function call

withMonitor_ :: MonadIO m => (Monitor args ret -> m ()) -> m [Event args ret] Source #

withMonitor_ f calls f with Monitor, and returns event logs during the call.

times :: Matcher Int -> Matcher (Event args ret) -> Matcher [Event args ret] Source #

times countMatcher eventMatcher counts events that matches eventMatcher, and then the count matches countMatcher

call :: Matcher args -> Matcher (Event args ret) Source #

call matcher matches method call whose arguments matches matcher