module Control.Monad.Static where
import Control.Applicative.Static
import Control.Distributed.Closure
import Data.Functor.Static
import Data.Typeable (Typeable)
class StaticApply m => StaticBind m where
staticBind :: (Typeable a, Typeable b) => m a -> Closure (a -> m b) -> m b
staticBind m k = staticJoin (staticMap k m)
staticJoin :: Typeable a => m (m a) -> m a
staticJoin m = m `staticBind` static id
class (StaticApplicative m, StaticBind m) => StaticMonad m
instance (StaticApplicative m, StaticBind m) => StaticMonad m
staticReturn :: (StaticApplicative m, Typeable a) => a -> m a
staticReturn = staticPure
instance StaticBind Closure where
staticBind m k = unclosure k (unclosure m)