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

Test.Method.Dynamic

Description

 
Synopsis

Documentation

data DynamicShow Source #

Dynamic value whose content is showable. Using this type instead of Dynamic is recommended because it gives better error messages.

Instances

Instances details
Show DynamicShow Source # 
Instance details

Defined in Test.Method.Dynamic

DynamicLike DynamicShow Source # 
Instance details

Defined in Test.Method.Dynamic

(Typeable a, Show a) => ToDyn DynamicShow a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: a -> DynamicShow Source #

(Typeable a, Show a) => FromDyn DynamicShow a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: DynamicShow -> a Source #

data Dynamic #

A value of type Dynamic is an object encapsulated together with its type.

A Dynamic may only represent a monomorphic value; an attempt to create a value of type Dynamic from a polymorphically-typed expression will result in an ambiguity error (see toDyn).

Showing a value of type Dynamic returns a pretty-printed representation of the object's type; useful for debugging.

Instances

Instances details
Show Dynamic

Since: base-2.1

Instance details

Defined in Data.Dynamic

Exception Dynamic

Since: base-4.0.0.0

Instance details

Defined in Data.Dynamic

DynamicLike Dynamic Source # 
Instance details

Defined in Test.Method.Dynamic

Typeable a => ToDyn Dynamic a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: a -> Dynamic Source #

Typeable a => FromDyn Dynamic a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: Dynamic -> a Source #

castMethod :: (ToDyn (Args method) (Args method'), FromDyn (Ret method) (Ret method'), Method method, Method method', Base method ~ Base method') => method -> method' Source #

convert a dynamically-typed method to a polymorphic method.

  fDyn :: String -> DynamicShow -> Dynamic -> IO [DynamicShow]
  fDyn = ...
  fPoly :: (Typeable a, Show a, Typeable b, Typeable c, Show c) => String -> a -> b -> IO [c]
  fPoly = castMethod fDyn
  

dynArg :: (Typeable a, DynamicLike b) => Matcher a -> Matcher b Source #

Convert given matcher to dynamic matcher. The dynamic matcher matches a dynamic value only if the value has the type of given matcher.

class DynamicLike a where Source #

Generalizes Dynamic and DynamicShow

Methods

asDyn :: a -> Dynamic Source #

Instances

Instances details
DynamicLike Dynamic Source # 
Instance details

Defined in Test.Method.Dynamic

DynamicLike DynamicShow Source # 
Instance details

Defined in Test.Method.Dynamic

class FromDyn a b where Source #

FromDyn a b provides a function to convert type a to type b, where b is a type whose dynamic type occurences are replaced by concrete types.

For example: FromDyn (Int, Dynamic, Maybe Dynamic) (Int, Bool, Maybe String)

Minimal complete definition

Nothing

Methods

fromDyn :: a -> b Source #

convert dynamic value to specified type. It thows runtime exception if the dynamic value does not have specified type.

default fromDyn :: (Generic a, Generic b, FromDyn' (Rep a) (Rep b)) => a -> b Source #

Instances

Instances details
FromDyn a a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: a -> a Source #

Typeable a => FromDyn Dynamic a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: Dynamic -> a Source #

(Typeable a, Show a) => FromDyn DynamicShow a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: DynamicShow -> a Source #

FromDyn a b => FromDyn [a] [b] Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: [a] -> [b] Source #

FromDyn a b => FromDyn (Maybe a) (Maybe b) Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: Maybe a -> Maybe b Source #

(ToDyn a a', FromDyn b b') => FromDyn (a -> b) (a' -> b') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a -> b) -> a' -> b' Source #

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

Defined in Test.Method.Dynamic

Methods

fromDyn :: Either a b -> Either a' b' Source #

(FromDyn a a', FromDyn b b') => FromDyn (a, b) (a', b') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a, b) -> (a', b') Source #

(FromDyn a b, FromDyn c d) => FromDyn (a :* c) (b :* d) Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a :* c) -> b :* d Source #

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

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a, b, c) -> (a', b', c') Source #

(FromDyn a a', FromDyn b b', FromDyn c c', FromDyn d d') => FromDyn (a, b, c, d) (a', b', c', d') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a, b, c, d) -> (a', b', c', d') Source #

(FromDyn a a', FromDyn b b', FromDyn c c', FromDyn d d', FromDyn e e') => FromDyn (a, b, c, d, e) (a', b', c', d', e') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a, b, c, d, e) -> (a', b', c', d', e') Source #

(FromDyn a a', FromDyn b b', FromDyn c c', FromDyn d d', FromDyn e e', FromDyn f f') => FromDyn (a, b, c, d, e, f) (a', b', c', d', e', f') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a, b, c, d, e, f) -> (a', b', c', d', e', f') Source #

(FromDyn a a', FromDyn b b', FromDyn c c', FromDyn d d', FromDyn e e', FromDyn f f', FromDyn g g') => FromDyn (a, b, c, d, e, f, g) (a', b', c', d', e', f', g') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

fromDyn :: (a, b, c, d, e, f, g) -> (a', b', c', d', e', f', g') Source #

class ToDyn a b where Source #

ToDyn a b provides a function to convert type b to type a, where b is a type whose dynamic type occurences are replaced by concrete types.

For example: ToDyn (Int, Dynamic, Maybe Dynamic) (Int, Bool, Maybe String)

Minimal complete definition

Nothing

Methods

toDyn :: b -> a Source #

convert value of specified type to dynamic value

default toDyn :: (Generic a, Generic b, ToDyn' (Rep a) (Rep b)) => b -> a Source #

Instances

Instances details
ToDyn a a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: a -> a Source #

Typeable a => ToDyn Dynamic a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: a -> Dynamic Source #

(Typeable a, Show a) => ToDyn DynamicShow a Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: a -> DynamicShow Source #

ToDyn a b => ToDyn [a] [b] Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: [b] -> [a] Source #

ToDyn a b => ToDyn (Maybe a) (Maybe b) Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: Maybe b -> Maybe a Source #

(FromDyn a a', ToDyn b b') => ToDyn (a -> b) (a' -> b') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: (a' -> b') -> a -> b Source #

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

Defined in Test.Method.Dynamic

Methods

toDyn :: Either a' b' -> Either a b Source #

(ToDyn a a', ToDyn b b') => ToDyn (a, b) (a', b') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: (a', b') -> (a, b) Source #

(ToDyn a b, ToDyn c d) => ToDyn (a :* c) (b :* d) Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: (b :* d) -> a :* c Source #

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

Defined in Test.Method.Dynamic

Methods

toDyn :: (a', b', c') -> (a, b, c) Source #

(ToDyn a a', ToDyn b b', ToDyn c c', ToDyn d d') => ToDyn (a, b, c, d) (a', b', c', d') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: (a', b', c', d') -> (a, b, c, d) Source #

(ToDyn a a', ToDyn b b', ToDyn c c', ToDyn d d', ToDyn e e') => ToDyn (a, b, c, d, e) (a', b', c', d', e') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: (a', b', c', d', e') -> (a, b, c, d, e) Source #

(ToDyn a a', ToDyn b b', ToDyn c c', ToDyn d d', ToDyn e e', ToDyn f f') => ToDyn (a, b, c, d, e, f) (a', b', c', d', e', f') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: (a', b', c', d', e', f') -> (a, b, c, d, e, f) Source #

(ToDyn a a', ToDyn b b', ToDyn c c', ToDyn d d', ToDyn e e', ToDyn f f', ToDyn g g') => ToDyn (a, b, c, d, e, f, g) (a', b', c', d', e', f', g') Source # 
Instance details

Defined in Test.Method.Dynamic

Methods

toDyn :: (a', b', c', d', e', f', g') -> (a, b, c, d, e, f, g) Source #

class Typeable (a :: k) #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#