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

Test.Method.Label

Description

 
Synopsis

Documentation

class Typeable f => Label (f :: Type -> Type) where Source #

Type class that represents f denotes the type of field names of InterfaceOf f

Minimal complete definition

toInterface, showLabel

Associated Types

type InterfaceOf f Source #

Interface type corrensponding to f

Methods

toInterface :: (forall m. (Typeable m, Method m, MonadIO (Base m), Show (Args m)) => f m -> m) -> InterfaceOf f Source #

Construct a interface from polymorphic function that returns each field of the interface.

showLabel :: f m -> String Source #

compareLabel :: f m1 -> f m2 -> Ordering Source #

Instances

Instances details
(Label f, Label g) => Label (f :|: g) Source # 
Instance details

Defined in Test.Method.Label

Associated Types

type InterfaceOf (f :|: g) Source #

Methods

toInterface :: (forall m. (Typeable m, Method m, MonadIO (Base m), Show (Args m)) => (f :|: g) m -> m) -> InterfaceOf (f :|: g) Source #

showLabel :: (f :|: g) m -> String Source #

compareLabel :: (f :|: g) m1 -> (f :|: g) m2 -> Ordering Source #

data (f :|: g) a Source #

f :|: g is the disjoint union of label f and label g. Use this type when you want to specify a protocol for multiple interfaces.

Example

data FooService = FooService {
  foo :: Int -> IO Bool,
  ...
  }
data BarService = BarService {
  bar :: String -> IO (),
  ...
  }
deriveLabel ''FooService
deriveLabel ''BarService

proto :: ProtocolM (FooServiceLabel :|: BarServiceLabel) ()
proto = do
  i1 <- decl $ whenArgs (L Foo) (==1) `thenReturn` True
  void $ decl $ whenArgs (R Bar) (=="bar") `thenReturn` () `dependsOn` [i1]

main :: IO ()
main = withProtocol proto $ \(fooService, barService) -> do
  ...

Constructors

L (f a) 
R (g a) 

Instances

Instances details
(Label f, Label g) => Label (f :|: g) Source # 
Instance details

Defined in Test.Method.Label

Associated Types

type InterfaceOf (f :|: g) Source #

Methods

toInterface :: (forall m. (Typeable m, Method m, MonadIO (Base m), Show (Args m)) => (f :|: g) m -> m) -> InterfaceOf (f :|: g) Source #

showLabel :: (f :|: g) m -> String Source #

compareLabel :: (f :|: g) m1 -> (f :|: g) m2 -> Ordering Source #

(Eq (f a), Eq (g a)) => Eq ((f :|: g) a) Source # 
Instance details

Defined in Test.Method.Label

Methods

(==) :: (f :|: g) a -> (f :|: g) a -> Bool #

(/=) :: (f :|: g) a -> (f :|: g) a -> Bool #

(Ord (f a), Ord (g a)) => Ord ((f :|: g) a) Source # 
Instance details

Defined in Test.Method.Label

Methods

compare :: (f :|: g) a -> (f :|: g) a -> Ordering #

(<) :: (f :|: g) a -> (f :|: g) a -> Bool #

(<=) :: (f :|: g) a -> (f :|: g) a -> Bool #

(>) :: (f :|: g) a -> (f :|: g) a -> Bool #

(>=) :: (f :|: g) a -> (f :|: g) a -> Bool #

max :: (f :|: g) a -> (f :|: g) a -> (f :|: g) a #

min :: (f :|: g) a -> (f :|: g) a -> (f :|: g) a #

(Show (f a), Show (g a)) => Show ((f :|: g) a) Source # 
Instance details

Defined in Test.Method.Label

Methods

showsPrec :: Int -> (f :|: g) a -> ShowS #

show :: (f :|: g) a -> String #

showList :: [(f :|: g) a] -> ShowS #

type InterfaceOf (f :|: g) Source # 
Instance details

Defined in Test.Method.Label

deriveLabel :: Name -> DecsQ Source #

Generate the label type from given interface type.

  • Define GADT XXXLabel m for interface XXX.

    • FieldX :: XXXLabel X for each field fieldX :: X where X is a standard type.
    • PolyFieldX :: XXXLabel ty[Dynamic/a] for each field of the form polyFieldX :: (forall a. Typeable a => ty)

      • Type variable a is substituted with DynamicShow if a is instances of Show and Typeable
      • Type variable a is substituted with Dynamic if a is an instance of Typeable but not Show
      • Report an error if type variable a is not an instance of Typeable
  • Define instance Label XXXLabel.

Example

data API env = API {
    _foo :: Int -> RIO env Int,
    _bar :: forall a. (Show a, Typeable a) => String -> RIO env (Maybe a),
    _baz :: forall b. (Typeable a) => b -> RIO env ()
  }

deriveLabel ''API will generate the following code.

data APILabel env m where
    Foo :: APILabel env (Int -> RIO env Int)
    Bar :: APILabel env (String -> RIO env (Maybe DynamicShow)) -- type variable `a` is replaced with DynamicShow
    Baz :: APILabel env (Dynamic -> RIO env ()) -- type variable 'b' is replaced with Dynamic

instance Label (APILabel env) where
    type InterfaceOf (APILabel env) = API env
    toInterface k = API (k Foo) (castMethod (k Bar)) (castMethod (k Baz))
    showLabel x = case x of
      Foo -> Foo
      Bar -> Bar
      Baz -> Baz