Class.hs 4.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148
  1. {-# LANGUAGE TypeFamilies #-}
  2. module Control.Monad.Trans.Interruptible.Class (
  3. Interruptible(..),
  4. -- * Instance accessors
  5. inEitherTCtx, peelEitherTCtx,
  6. inStateTCtx, peelStateTCtx,
  7. inWriterTCtx, peelWriterTCtx,
  8. inReaderTCtx, peelReaderTCtx,
  9. inRWSTCtx, peelRWSTCtx,
  10. -- * Resumers for stacks of interruptibles
  11. resume2,
  12. resume3,
  13. resume4,
  14. resume5
  15. )where
  16. import Control.Monad.Trans.Class
  17. import Control.Monad.Trans.State
  18. import Control.Monad.Trans.Either
  19. import Control.Monad.Trans.Reader
  20. import Control.Monad.Trans.Writer
  21. import Control.Monad.Trans.RWS
  22. {- |
  23. Interruptible monad transformers.
  24. A monad transformer can be interrupted if it returns its
  25. final context from its type creator, and if it is possible
  26. to hoist this context again into the monad at the begining
  27. of its execution.
  28. For example, @StateT@ can be interrupted because
  29. @runStateT@ returns its final state, and because its state
  30. can be set at the type creation. Error can not be hoisted,
  31. thus is can not be interrupted.
  32. Interruptible transformers can be stacked so that their
  33. execution is resumed by composition of their @resume@
  34. functions, and their data by the composition of their data
  35. constructors at the inverse order. That is, in the stack:
  36. > (Monad m, Interruptible i, Interruptible j) => i j m
  37. Both i and j can be resumed by the function @resume . resume@,
  38. and given @initI :: a -> RSt i a@ and @initJ :: a -> RSt j a@,
  39. the total context is given by @initJ . initI@.
  40. The context data constructors vary with each Interruptible,
  41. as well as its signature.
  42. -}
  43. class MonadTrans t => Interruptible t where
  44. -- | Context data of the transformer
  45. type RSt t a :: *
  46. -- | Resumes the execution of an interruptible transformer
  47. resume :: Monad m => (a -> t m b) -> RSt t a -> m (RSt t b)
  48. instance Interruptible (EitherT e) where
  49. -- | The context of @EitherT e a@ is @Either e a@.
  50. type RSt (EitherT e) a = Either e a
  51. resume f st = runEitherT (hoistEither st >>= f)
  52. -- | Cretes an interrupted EitherT context
  53. inEitherTCtx :: a -> RSt (EitherT e) a
  54. inEitherTCtx = Right
  55. -- | Unwraps an interrupted EitherT context
  56. peelEitherTCtx :: RSt (EitherT e) a -> Either e a
  57. peelEitherTCtx = id
  58. instance Interruptible (StateT st) where
  59. -- | The context of @StateT st a@ is @(a, st)@
  60. type RSt (StateT st) a = (a, st)
  61. resume f (a, st) = runStateT (f a) st
  62. -- | Creates an interrupted StateT context
  63. inStateTCtx :: st -> a -> RSt (StateT st) a
  64. inStateTCtx st a = (a, st)
  65. -- | Unwraps an interrupted StateT context
  66. peelStateTCtx :: RSt (StateT st) a -> (a, st)
  67. peelStateTCtx = id
  68. instance Monoid w => Interruptible (WriterT w) where
  69. type RSt (WriterT w) a = (a, w)
  70. resume f (a, w) = do
  71. (a', w') <- runWriterT (f a)
  72. return (a', mappend w w')
  73. -- | Creates an interrupted WriterT context
  74. inWriterTCtx :: Monoid w => a -> RSt (WriterT w) a
  75. inWriterTCtx a = (a, mempty)
  76. -- | Unwraps an interrupted WriterT context
  77. peelWriterTCtx :: RSt (WriterT w) a -> (a, w)
  78. peelWriterTCtx = id
  79. instance Interruptible (ReaderT r) where
  80. type RSt (ReaderT r) a = (a, r)
  81. resume f (a, r) = do
  82. a' <- runReaderT (f a) r
  83. return (a', r)
  84. -- | Creates an interrupted ReaderT context
  85. inReaderTCtx :: r -> a -> RSt (ReaderT r) a
  86. inReaderTCtx r a = (a, r)
  87. -- | Unwraps an interrupted WriterT context
  88. peelReaderTCtx :: RSt (ReaderT r) a -> a
  89. peelReaderTCtx (a, _) = a
  90. instance Monoid w => Interruptible (RWST r w s) where
  91. type RSt (RWST r w s) a = (a, r, w, s)
  92. resume f (a, r, w, s) = do
  93. (a', s', w') <- runRWST (f a) r s
  94. return (a', r, w', s')
  95. -- | Creates an interrupted RWST context
  96. inRWSTCtx :: Monoid w => r -> s -> a -> RSt (RWST r w s) a
  97. inRWSTCtx r s a = (a, r, mempty, s)
  98. -- | Unwraps an interrupted RWST context
  99. peelRWSTCtx :: RSt (RWST r w s) a -> (a, w, s)
  100. peelRWSTCtx (a, r, w, s) = (a, w, s)
  101. resume2 :: (Monad m, Interruptible t, Monad (t m), Interruptible u) =>
  102. (a -> u (t m) b) -> RSt t (RSt u a) -> m (RSt t (RSt u b))
  103. resume2 = resume.resume
  104. resume3 :: (Monad m, Interruptible t0, Monad (t0 m), Interruptible t1,
  105. Monad (t1 (t0 m)), Interruptible t2) =>
  106. (a -> t2 (t1 (t0 m)) b) -> RSt t0 (RSt t1 (RSt t2 a)) ->
  107. m (RSt t0 (RSt t1 (RSt t2 b)))
  108. resume3 = resume2.resume
  109. resume4 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2,
  110. Interruptible t3, Monad (t0 m), Monad (t1 (t0 m)), Monad (t2 (t1 (t0 m)))) =>
  111. (a -> t3 (t2 (t1 (t0 m))) b) -> RSt t0 (RSt t1 (RSt t2 (RSt t3 a))) ->
  112. m (RSt t0 (RSt t1 (RSt t2 (RSt t3 b))))
  113. resume4 = resume3.resume
  114. resume5 :: (Monad m, Interruptible t0, Interruptible t1, Interruptible t2,
  115. Interruptible t3, Interruptible t4, Monad (t0 m), Monad (t1 (t0 m)),
  116. Monad (t2 (t1 (t0 m))), Monad (t3 (t2 (t1 (t0 m))))) =>
  117. (a -> t4 (t3 (t2 (t1 (t0 m)))) b) -> RSt t0 (RSt t1 (RSt t2 (RSt t3 (RSt t4 a)))) ->
  118. m (RSt t0 (RSt t1 (RSt t2 (RSt t3 (RSt t4 b)))))
  119. resume5 = resume4.resume