MetaObject-0.0.3: A meta-object system for Haskell based on Perl 6ContentsIndex
MO.Base
Synopsis
class Monad m => Codeable m c where
run :: c -> Arguments m -> m (Invocant m)
newtype NoCode m = NoCode (Invocant m)
newtype PureCode = PureCode (forall m. (Typeable1 m, Monad m) => Arguments m -> Invocant m)
newtype Monad m => HsCode m = HsCode (Arguments m -> m (Invocant m))
type Arguments m = Capt (Invocant m)
withInvocant :: (Typeable1 m, Monad m) => Arguments m -> Invocant m -> Arguments m
getInvocant :: (Typeable1 m, Monad m) => Arguments m -> Maybe (Invocant m)
namedArg :: (Typeable1 m, Monad m) => Arguments m -> Atom -> Maybe (Invocant m)
data (Typeable1 m, Monad m) => Invocant m
stubInvocant :: (Typeable1 m, Monad m) => Invocant m
Documentation
class Monad m => Codeable m c where
open type to represent Code
Methods
run :: c -> Arguments m -> m (Invocant m)
show/hide Instances
newtype NoCode m
stub code which always return the same
Constructors
NoCode (Invocant m)
show/hide Instances
newtype PureCode
Pure code that works with any monad.
Constructors
PureCode (forall m. (Typeable1 m, Monad m) => Arguments m -> Invocant m)
show/hide Instances
newtype Monad m => HsCode m
Real monadic primitive code.
Constructors
HsCode (Arguments m -> m (Invocant m))
show/hide Instances
type Arguments m = Capt (Invocant m)
withInvocant :: (Typeable1 m, Monad m) => Arguments m -> Invocant m -> Arguments m
getInvocant :: (Typeable1 m, Monad m) => Arguments m -> Maybe (Invocant m)
namedArg :: (Typeable1 m, Monad m) => Arguments m -> Atom -> Maybe (Invocant m)
data (Typeable1 m, Monad m) => Invocant m
show/hide Instances
stubInvocant :: (Typeable1 m, Monad m) => Invocant m
Produced by Haddock version 2.1.0