MetaObject-0.0.3: A meta-object system for Haskell based on Perl 6ContentsIndex
MO.Run
Synopsis
data MethodInvocation m = MkMethodInvocation {
mi_name :: !MethodName
mi_arguments :: !Arguments m
}
class Monad m => ResponderInterface m a | a -> m where
fromMethodList :: [(MethodName, MethodCompiled m)] -> m a
dispatch :: a -> Invocant m -> MethodInvocation m -> m (Invocant m)
data Monad m => NoResponse m = NoResponse
emptyResponder :: (Typeable1 m, Monad m) => AnyResponder m
data MethodTable m = MkMethodTable {
mt_methods :: !AtomMap (MethodCompiled m)
}
data AnyResponder m = forall c . ResponderInterface m c => MkResponder !m c
data (Typeable1 m, Monad m) => Invocant m = forall a . (Show a, Eq a, Ord a, Typeable a) => MkInvocant a (AnyResponder m)
fromInvocant :: forall m b. (Typeable1 m, Monad m, Typeable b) => Arguments m -> m b
ivDispatch :: (Typeable1 m, Monad m) => Invocant m -> MethodInvocation m -> m (Invocant m)
__ :: (Typeable1 m, Monad m, Ord a, Show a, Typeable a) => a -> Invocant m
stubInvocant :: (Typeable1 m, Monad m) => Invocant m
mkArgs :: (Typeable1 m, Monad m) => [Invocant m] -> Arguments m
module MO.Base
Documentation
data MethodInvocation m
Constructors
MkMethodInvocation
mi_name :: !MethodName
mi_arguments :: !Arguments m
class Monad m => ResponderInterface m a | a -> m where
Methods
fromMethodList :: [(MethodName, MethodCompiled m)] -> m a
dispatch :: a -> Invocant m -> MethodInvocation m -> m (Invocant m)
show/hide Instances
data Monad m => NoResponse m
Constructors
NoResponse
show/hide Instances
emptyResponder :: (Typeable1 m, Monad m) => AnyResponder m
data MethodTable m
This is a static method table.
Constructors
MkMethodTable
mt_methods :: !AtomMap (MethodCompiled m)
show/hide Instances
data AnyResponder m
Constructors
forall c . ResponderInterface m c => MkResponder !m c
show/hide Instances
data (Typeable1 m, Monad m) => Invocant m
Constructors
forall a . (Show a, Eq a, Ord a, Typeable a) => MkInvocant a (AnyResponder m)
show/hide Instances
fromInvocant :: forall m b. (Typeable1 m, Monad m, Typeable b) => Arguments m -> m b
ivDispatch :: (Typeable1 m, Monad m) => Invocant m -> MethodInvocation m -> m (Invocant m)
__ :: (Typeable1 m, Monad m, Ord a, Show a, Typeable a) => a -> Invocant m
stubInvocant :: (Typeable1 m, Monad m) => Invocant m
mkArgs :: (Typeable1 m, Monad m) => [Invocant m] -> Arguments m
module MO.Base
Produced by Haddock version 2.1.0