network-transport-tests-0.3.0: Unit tests for Network.Transport implementations

Safe HaskellSafe
LanguageHaskell2010

Network.Transport.Tests.Traced

Description

Add tracing to the IO monad (see examples).

Usage
{-# LANGUAGE RebindableSyntax #-}
import Prelude hiding (catch, (>>=), (>>), return, fail)
import Traced
Example
test1 :: IO Int
test1 = do
  Left x  <- return (Left 1 :: Either Int Int)
  putStrLn "Hello world"
  Right y <- return (Left 2 :: Either Int Int)
  return (x + y)

outputs

Hello world
*** Exception: user error (Pattern match failure in do expression at Traced.hs:187:3-9)
Trace:
0  Left 2
1  Left 1
Guards

Use the following idiom instead of using guard:

test2 :: IO Int
test2 = do
  Left x <- return (Left 1 :: Either Int Int)
  True   <- return (x == 3)
  return x

The advantage of this idiom is that it gives you line number information when the guard fails:

*Traced> test2
*** Exception: user error (Pattern match failure in do expression at Traced.hs:193:3-6)
Trace:
0  Left 1
Synopsis

Documentation

class MonadS m where Source #

Like Monad but bind is only defined for Traceable instances

Methods

returnS :: a -> m a Source #

bindS :: Traceable a => m a -> (a -> m b) -> m b Source #

failS :: String -> m a Source #

seqS :: m a -> m b -> m b Source #

Instances
MonadS IO Source #

Add tracing to IO (see examples)

Instance details

Defined in Network.Transport.Tests.Traced

Methods

returnS :: a -> IO a Source #

bindS :: Traceable a => IO a -> (a -> IO b) -> IO b Source #

failS :: String -> IO a Source #

seqS :: IO a -> IO b -> IO b Source #

return :: MonadS m => a -> m a Source #

Redefinition of return

(>>=) :: (MonadS m, Traceable a) => m a -> (a -> m b) -> m b Source #

Redefinition of >>=

(>>) :: MonadS m => m a -> m b -> m b Source #

Redefinition of >>

fail :: MonadS m => String -> m a Source #

Redefinition of fail

ifThenElse :: Bool -> a -> a -> a Source #

Definition of ifThenElse for use with RebindableSyntax

data Showable Source #

Constructors

Show a => Showable a 
Instances
Show Showable Source # 
Instance details

Defined in Network.Transport.Tests.Traced

class Traceable a where Source #

Methods

trace :: a -> Maybe Showable Source #

Instances
Traceable Bool Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable Float Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable Int Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable Int32 Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable Int64 Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable Word32 Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable Word64 Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable () Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: () -> Maybe Showable Source #

Traceable ThreadId Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable IOException Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable SomeException Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable ByteString Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Traceable Transport Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable EndPoint Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable Connection Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable Event Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable EndPointAddress Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Traceable [Char] Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: [Char] -> Maybe Showable Source #

Traceable a => Traceable [a] Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: [a] -> Maybe Showable Source #

Traceable a => Traceable (Maybe a) Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: Maybe a -> Maybe Showable Source #

Traceable (Chan a) Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

Methods

trace :: Chan a -> Maybe Showable Source #

Traceable (MVar a) Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: MVar a -> Maybe Showable Source #

Show err => Traceable (TransportError err) Source # 
Instance details

Defined in Network.Transport.Tests.Auxiliary

(Traceable a, Traceable b) => Traceable (Either a b) Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: Either a b -> Maybe Showable Source #

(Traceable a, Traceable b) => Traceable (a, b) Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: (a, b) -> Maybe Showable Source #

(Traceable a, Traceable b, Traceable c) => Traceable (a, b, c) Source # 
Instance details

Defined in Network.Transport.Tests.Traced

Methods

trace :: (a, b, c) -> Maybe Showable Source #