
On 11/12/2011 07:34 AM, Bas van Dijk wrote:
Are you going to release a new version of monad-control right away
Not just yet. I've split `monad-control` into two packages:
* `monad-control`: just exports `Control.Monad.Trans.Control`. This part is finished. * `lifted-base`: wraps all modules of the `base` package which export `IO` computations and provides lifted version instead. For example we have `Control.Exception.Lifted`, `Control.Concurrent.Lifted`, etc.
As you can imagine the latter is a lot of boring work. Fortunately it's easy to do so will probably not take a lot of time. BTW if by any chance you want to help out, that will be much appreciated!
The repos can be found [here](https://github.com/basvandijk/lifted-base)
Maybe I should elaborate on why I stopped using monad-control and rolled out my own version of lifted Control.Exception in monad-abort-fd package. I'm CC-ing the Cafe just in case someone else might be interested in the matter of IO lifting. Imagine we have a monad for multiprogramming with shared state: -- ContT with a little twist. Both the constructor and runAIO -- are NOT exported. newtype AIO s α = AIO { runAIO ∷ ∀ β . (α → IO (Trace s β)) → IO (Trace s β) } runAIOs ∷ MonadBase IO μ ⇒ s -- The initial state → [AIO s α] -- The batch of programs to run. -- If one program exits normally (without using -- aioExit) or throws an exception, the whole batch -- is terminated. → μ (s, Maybe (Attempt α)) -- The final state and the result. -- "Nothing" means deadlock or that -- all the programs exited with -- aioExit. runAIOs = liftBase $ mask_ $ ... bloody evaluation ... data Trace s α where -- Finish the program (without finishing the batch). TraceExit ∷ Trace s α -- Lift a pure value. TraceDone ∷ α → Trace s α -- A primitive to execute and the continuation. TraceCont ∷ Prim s α → (α → IO (Trace s β)) → Trace s β -- Primitive operations data Prim s α where -- State retrieval/modification PrimGet ∷ Prim s s PrimSet ∷ s → Prim s () -- Scheduling point. The program is suspended until -- the specified event occurs. PrimEv ∷ Event e ⇒ e → Prim s (EventResult e) -- Scheduling point. The program is suspended until the state -- satisfies the predicate. PrimCond ∷ (s → Bool) → Prim s () -- Run computation guarded with finalizer. PrimFin ∷ IO (Trace s α) → (Maybe α → AIO s β) → Prim s (α, β) -- Run computation guarded with exception handler. PrimHand ∷ IO (Trace s α) → (SomeException → AIO s α) → Prim s α aioExit ∷ AIO s α aioExit = AIO $ const $ return TraceExit aioAfter ∷ (s → Bool) → AIO s () aioAfter cond = AIO $ return . TraceCont (PrimCond cond) aioAwait ∷ Event e ⇒ e → AIO s (EventResult e) aioAwait e = AIO $ return . TraceCont (PrimEv e) runAIOs slices the programs at scheduling points and enqueues the individual pieces for execution, taking care of saving/restoring the context (finalizers and exception handlers). The Functor/Applicative/Monad/MonadBase/etc instances are pretty trivial: instance Functor (AIO s) where fmap f (AIO g) = AIO $ \c → g (c . f) instance Applicative (AIO s) where pure a = AIO ($ a) (<*>) = ap instance Monad (AIO s) where return = pure AIO g >>= f = AIO $ \c → g (\a → runAIO (f a) c) instance MonadBase IO (AIO s) where liftBase io = AIO (io >>=) instance MonadState s (AIO s) where get = AIO $ return . TraceCont PrimGet put s = AIO $ return . TraceCont (PrimSet s) instance MonadAbort SomeException (AIO s) where abort = liftBase . throwIO trace ∷ AIO s α → IO (Trace s α) trace (AIO g) = g (return . TraceDone) instance MonadRecover SomeException (AIO s) where recover m h = AIO $ return . TraceCont (PrimHand (trace m) h) instance MonadFinally (AIO s) where finally' m f = AIO $ return . TraceCont (PrimFin (trace m) f) -- finally m = fmap fst . finally' m . const -- No async exceptions in AIO instance MonadMask () (AIO s) where getMaskingState = return () setMaskingState = const id Now we have a problem: we can throw/catch exceptions and install finalizers in AIO, but we can't use Control.Exception.Lifted because we can't declare a MonadBaseControl instance for our "ContT with limited interface". So now, instead of trying to wrap IO control operations uniformly, I just reimplement them in terms of the classes I mentioned above (MonadAbort+MonadRecover+MonadFinally+MonadMask), for example: bracket ∷ (MonadFinally μ, MonadMask m μ) ⇒ μ α → (α → μ β) → (α → μ γ) → μ γ bracket acq release m = mask $ \restore → do a ← acq finally (restore $ m a) (release a) It requires more typing (more classes => more instances), but it works for a broader class of monads and I get proper side affects in finalizers for a bonus. The code is on Hackage (monad-abort-fd) and on the GitHub (https://github.com/mvv/monad-abort-fd/blob/master/src/Control/Monad/Exceptio...)