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

Control.Method.Internal

Description

 
Synopsis

Documentation

class TupleLike a where Source #

Associated Types

type AsTuple a Source #

Methods

fromTuple :: AsTuple a -> a Source #

toTuple :: a -> AsTuple a Source #

Instances

Instances details
TupleLike Nil Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple Nil Source #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil)))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> a :* (b :* (c :* (d :* (e :* (f :* Nil))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) -> a :* (b :* (c :* (d :* (e :* Nil)))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* Nil))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

TupleLike (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* Nil)))) -> a :* (b :* (c :* (d :* Nil))) Source #

toTuple :: (a :* (b :* (c :* (d :* Nil)))) -> AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

TupleLike (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* Nil))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* Nil))) -> a :* (b :* (c :* Nil)) Source #

toTuple :: (a :* (b :* (c :* Nil))) -> AsTuple (a :* (b :* (c :* Nil))) Source #

TupleLike (a :* (b :* Nil)) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* Nil)) Source #

Methods

fromTuple :: AsTuple (a :* (b :* Nil)) -> a :* (b :* Nil) Source #

toTuple :: (a :* (b :* Nil)) -> AsTuple (a :* (b :* Nil)) Source #

TupleLike (a :* Nil) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* Nil) Source #

Methods

fromTuple :: AsTuple (a :* Nil) -> a :* Nil Source #

toTuple :: (a :* Nil) -> AsTuple (a :* Nil) Source #

data Nil Source #

Nullary tuple

Constructors

Nil 

Instances

Instances details
Eq Nil Source # 
Instance details

Defined in Control.Method.Internal

Methods

(==) :: Nil -> Nil -> Bool #

(/=) :: Nil -> Nil -> Bool #

Ord Nil Source # 
Instance details

Defined in Control.Method.Internal

Methods

compare :: Nil -> Nil -> Ordering #

(<) :: Nil -> Nil -> Bool #

(<=) :: Nil -> Nil -> Bool #

(>) :: Nil -> Nil -> Bool #

(>=) :: Nil -> Nil -> Bool #

max :: Nil -> Nil -> Nil #

min :: Nil -> Nil -> Nil #

Show Nil Source # 
Instance details

Defined in Control.Method.Internal

Methods

showsPrec :: Int -> Nil -> ShowS #

show :: Nil -> String #

showList :: [Nil] -> ShowS #

TupleLike Nil Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple Nil Source #

ArgsMatcher Nil Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher Nil Source #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil)))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> a :* (b :* (c :* (d :* (e :* (f :* Nil))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) -> a :* (b :* (c :* (d :* (e :* Nil)))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* Nil))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

TupleLike (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* Nil)))) -> a :* (b :* (c :* (d :* Nil))) Source #

toTuple :: (a :* (b :* (c :* (d :* Nil)))) -> AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

TupleLike (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* Nil))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* Nil))) -> a :* (b :* (c :* Nil)) Source #

toTuple :: (a :* (b :* (c :* Nil))) -> AsTuple (a :* (b :* (c :* Nil))) Source #

TupleLike (a :* (b :* Nil)) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* Nil)) Source #

Methods

fromTuple :: AsTuple (a :* (b :* Nil)) -> a :* (b :* Nil) Source #

toTuple :: (a :* (b :* Nil)) -> AsTuple (a :* (b :* Nil)) Source #

TupleLike (a :* Nil) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* Nil) Source #

Methods

fromTuple :: AsTuple (a :* Nil) -> a :* Nil Source #

toTuple :: (a :* Nil) -> AsTuple (a :* Nil) Source #

ArgsMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> Matcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

ArgsMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> Matcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

ArgsMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) -> Matcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

ArgsMatcher (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* Nil)))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* Nil)))) -> Matcher (a :* (b :* (c :* (d :* Nil)))) Source #

ArgsMatcher (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* Nil))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* Nil))) -> Matcher (a :* (b :* (c :* Nil))) Source #

ArgsMatcher (a :* (b :* Nil)) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* Nil)) Source #

Methods

args :: EachMatcher (a :* (b :* Nil)) -> Matcher (a :* (b :* Nil)) Source #

ArgsMatcher (a :* Nil) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* Nil) Source #

Methods

args :: EachMatcher (a :* Nil) -> Matcher (a :* Nil) Source #

type AsTuple Nil Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple Nil = ()
type EachMatcher Nil Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher Nil = ()
type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) = (a, b, c, d, e, f, g)
type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) = (a, b, c, d, e, f)
type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) = (a, b, c, d, e)
type AsTuple (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* Nil)))) = (a, b, c, d)
type AsTuple (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* Nil))) = (a, b, c)
type AsTuple (a :* (b :* Nil)) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* Nil)) = (a, b)
type AsTuple (a :* Nil) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* Nil) = a
type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) = (Matcher a, Matcher b, Matcher c, Matcher d, Matcher e, Matcher f, Matcher g)
type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) = (Matcher a, Matcher b, Matcher c, Matcher d, Matcher e, Matcher f)
type EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) = (Matcher a, Matcher b, Matcher c, Matcher d, Matcher e)
type EachMatcher (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* Nil)))) = (Matcher a, Matcher b, Matcher c, Matcher d)
type EachMatcher (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* Nil))) = (Matcher a, Matcher b, Matcher c)
type EachMatcher (a :* (b :* Nil)) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* Nil)) = (Matcher a, Matcher b)
type EachMatcher (a :* Nil) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* Nil) = Matcher a

data a :* b infixr 1 Source #

Tuple constructor

Constructors

a :* !b infixr 1 

Instances

Instances details
(Eq a, Eq b) => Eq (a :* b) Source # 
Instance details

Defined in Control.Method.Internal

Methods

(==) :: (a :* b) -> (a :* b) -> Bool #

(/=) :: (a :* b) -> (a :* b) -> Bool #

(Ord a, Ord b) => Ord (a :* b) Source # 
Instance details

Defined in Control.Method.Internal

Methods

compare :: (a :* b) -> (a :* b) -> Ordering #

(<) :: (a :* b) -> (a :* b) -> Bool #

(<=) :: (a :* b) -> (a :* b) -> Bool #

(>) :: (a :* b) -> (a :* b) -> Bool #

(>=) :: (a :* b) -> (a :* b) -> Bool #

max :: (a :* b) -> (a :* b) -> a :* b #

min :: (a :* b) -> (a :* b) -> a :* b #

(Show a, ShowTuple b) => Show (a :* b) Source # 
Instance details

Defined in Control.Method.Internal

Methods

showsPrec :: Int -> (a :* b) -> ShowS #

show :: (a :* b) -> String #

showList :: [a :* b] -> ShowS #

Generic (a :* b) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type Rep (a :* b) :: Type -> Type #

Methods

from :: (a :* b) -> Rep (a :* b) x #

to :: Rep (a :* b) x -> a :* b #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil)))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> a :* (b :* (c :* (d :* (e :* (f :* Nil))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) -> a :* (b :* (c :* (d :* (e :* Nil)))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* Nil))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

TupleLike (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* Nil)))) -> a :* (b :* (c :* (d :* Nil))) Source #

toTuple :: (a :* (b :* (c :* (d :* Nil)))) -> AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

TupleLike (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* Nil))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* Nil))) -> a :* (b :* (c :* Nil)) Source #

toTuple :: (a :* (b :* (c :* Nil))) -> AsTuple (a :* (b :* (c :* Nil))) Source #

TupleLike (a :* (b :* Nil)) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* Nil)) Source #

Methods

fromTuple :: AsTuple (a :* (b :* Nil)) -> a :* (b :* Nil) Source #

toTuple :: (a :* (b :* Nil)) -> AsTuple (a :* (b :* Nil)) Source #

TupleLike (a :* Nil) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* Nil) Source #

Methods

fromTuple :: AsTuple (a :* Nil) -> a :* Nil Source #

toTuple :: (a :* Nil) -> AsTuple (a :* Nil) Source #

ArgsMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> Matcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

ArgsMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> Matcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

ArgsMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) -> Matcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

ArgsMatcher (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* (d :* Nil)))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* (d :* Nil)))) -> Matcher (a :* (b :* (c :* (d :* Nil)))) Source #

ArgsMatcher (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* (c :* Nil))) Source #

Methods

args :: EachMatcher (a :* (b :* (c :* Nil))) -> Matcher (a :* (b :* (c :* Nil))) Source #

ArgsMatcher (a :* (b :* Nil)) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* (b :* Nil)) Source #

Methods

args :: EachMatcher (a :* (b :* Nil)) -> Matcher (a :* (b :* Nil)) Source #

ArgsMatcher (a :* Nil) Source # 
Instance details

Defined in Test.Method.Matcher

Associated Types

type EachMatcher (a :* Nil) Source #

Methods

args :: EachMatcher (a :* Nil) -> Matcher (a :* Nil) 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 #

(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 #

type Rep (a :* b) Source # 
Instance details

Defined in Control.Method.Internal

type Rep (a :* b) = D1 ('MetaData ":*" "Control.Method.Internal" "method-0.4.0.0-KoA3vlXutX8LfnLeoDArbl" 'False) (C1 ('MetaCons ":*" ('InfixI 'RightAssociative 1) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))
type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) = (a, b, c, d, e, f, g)
type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) = (a, b, c, d, e, f)
type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) = (a, b, c, d, e)
type AsTuple (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* (d :* Nil)))) = (a, b, c, d)
type AsTuple (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* (c :* Nil))) = (a, b, c)
type AsTuple (a :* (b :* Nil)) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* (b :* Nil)) = (a, b)
type AsTuple (a :* Nil) Source # 
Instance details

Defined in Control.Method.Internal

type AsTuple (a :* Nil) = a
type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) = (Matcher a, Matcher b, Matcher c, Matcher d, Matcher e, Matcher f, Matcher g)
type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) = (Matcher a, Matcher b, Matcher c, Matcher d, Matcher e, Matcher f)
type EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* (e :* Nil))))) = (Matcher a, Matcher b, Matcher c, Matcher d, Matcher e)
type EachMatcher (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* (d :* Nil)))) = (Matcher a, Matcher b, Matcher c, Matcher d)
type EachMatcher (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* (c :* Nil))) = (Matcher a, Matcher b, Matcher c)
type EachMatcher (a :* (b :* Nil)) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* (b :* Nil)) = (Matcher a, Matcher b)
type EachMatcher (a :* Nil) Source # 
Instance details

Defined in Test.Method.Matcher

type EachMatcher (a :* Nil) = Matcher a