|
@@ -1,31 +1,77 @@
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
|
|
|
|
|
-module Control.Monad.Trans.Interruptible.Class where
|
|
|
+module Control.Monad.Trans.Interruptible.Class (
|
|
|
+ Interruptible(..),
|
|
|
+ -- * Resumers for stacks of interruptibles
|
|
|
+ resume2,
|
|
|
+ resume3,
|
|
|
+ resume4,
|
|
|
+ resume5
|
|
|
+ )where
|
|
|
|
|
|
import Control.Monad.Trans.Class
|
|
|
+import Control.Monad.Trans.State
|
|
|
import Control.Monad.Trans.Either
|
|
|
|
|
|
+{- |
|
|
|
+Interruptible monad transformers.
|
|
|
+
|
|
|
+A monad transformer can be interrupted if it returns its
|
|
|
+final context from its type creator, and if it is possible
|
|
|
+to hoist this context again into the monad at the begining
|
|
|
+of its execution.
|
|
|
+
|
|
|
+For example, @StateT@ can be interrupted because
|
|
|
+@runStateT@ returns its final state, and because its state
|
|
|
+can be set at the type creation. Error can not be hoisted,
|
|
|
+thus is can not be interrupted.
|
|
|
+
|
|
|
+Interruptible transformers can be stacked so that their
|
|
|
+execution is resumed by composition of their @resume@
|
|
|
+functions, and their data by the composition of their data
|
|
|
+constructors at the inverse order. That is, in the stack:
|
|
|
+
|
|
|
+> (Monad m, Interruptible i, Interruptible j) => i j m
|
|
|
+
|
|
|
+Both i and j can be resumed by the function @resume . resume@,
|
|
|
+and given @initI :: a -> RSt i a@ and @initJ :: a -> RSt j a@,
|
|
|
+the total context is given by @initJ . initI@.
|
|
|
+
|
|
|
+The context data constructors vary with each Interruptible,
|
|
|
+as well as its signature.
|
|
|
+-}
|
|
|
class MonadTrans t => Interruptible t where
|
|
|
- type RSt t :: * -> *
|
|
|
+ -- | Context data of the transformer
|
|
|
+ type RSt t a :: *
|
|
|
+ -- | Resumes the execution of an interruptible transformer
|
|
|
resume :: Monad m => (a -> t m b) -> RSt t a -> m (RSt t b)
|
|
|
|
|
|
instance Interruptible (EitherT e) where
|
|
|
- type RSt (EitherT e) = Either e
|
|
|
+ -- | The context of @EitherT e a@ is @Either e a@.
|
|
|
+ type RSt (EitherT e) a = Either e a
|
|
|
resume f st = runEitherT (hoistEither st >>= f)
|
|
|
|
|
|
+instance Interruptible (StateT st) where
|
|
|
+ -- | The context of @StateT st a@ is @(a, st)@
|
|
|
+ type RSt (StateT st) a = (a, st)
|
|
|
+ resume f (a, st) = runStateT (f a) st
|
|
|
+
|
|
|
resume2 :: (Monad m, Interruptible t, Monad (t m), Interruptible u) =>
|
|
|
(a -> u (t m) b) -> RSt t (RSt u a) -> m (RSt t (RSt u b))
|
|
|
resume2 = resume.resume
|
|
|
+
|
|
|
resume3 :: (Monad m, Interruptible t0, Monad (t0 m), Interruptible t1,
|
|
|
Monad (t1 (t0 m)), Interruptible t2) =>
|
|
|
(a -> t2 (t1 (t0 m)) b) -> RSt t0 (RSt t1 (RSt t2 a)) ->
|
|
|
m (RSt t0 (RSt t1 (RSt t2 b)))
|
|
|
resume3 = resume2.resume
|
|
|
+
|
|
|
resume4 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2,
|
|
|
Interruptible t3, Monad (t0 m), Monad (t1 (t0 m)), Monad (t2 (t1 (t0 m)))) =>
|
|
|
(a -> t3 (t2 (t1 (t0 m))) b) -> RSt t0 (RSt t1 (RSt t2 (RSt t3 a))) ->
|
|
|
m (RSt t0 (RSt t1 (RSt t2 (RSt t3 b))))
|
|
|
resume4 = resume3.resume
|
|
|
+
|
|
|
resume5 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2,
|
|
|
Interruptible t3, Interruptible t4, Monad (t0 m), Monad (t1 (t0 m)),
|
|
|
Monad (t2 (t1 (t0 m))), Monad (t3 (t2 (t1 (t0 m))))) =>
|