[Haskell-cafe] Monad-control rant

Edward Z. Yang ezyang at MIT.EDU
Mon Jan 9 18:17:09 CET 2012


Hello Mikhail,

(Apologies for reviving a two month old thread). Have you put some thought into
whether or not these extra classes generalize in a way that is not /quite/ as
general as MonadBaseControl (so as to give you the power you need) but still
allow you to implement the functionality you are looking for? I'm not sure but
it seems something along the lines of unwind-protect ala Scheme might be
sufficient.

Edward

Excerpts from Mikhail Vorozhtsov's message of Mon Nov 14 01:25:34 -0500 2011:
> On 11/14/2011 06:55 AM, Bas van Dijk wrote:
> > Hi Mikhail,
> >
> > your type class:
> >
> > class MonadAbort e μ ⇒ MonadRecover e μ | μ → e where
> >    recover ∷ μ α → (e → μ α) → μ α
> >
> > looks a lot like the MonadCatchIO type class from MonadCatchIO-transformers:
> >
> > class MonadIO m =>  MonadCatchIO m where
> >    catch   :: E.Exception e =>  m a ->  (e ->  m a) ->  m a
> >
> > I haven't looked at your code in detail but are you sure your
> > continuation based AIO monad doesn't suffer from the same unexpected
> > behavior as the ContT monad transformer with regard to catching and
> > handling exceptions?
> Yes, I'm sure. The reason why it works is because finally/bracket/etc 
> are not implemented on top of 'recover' (i.e. they don't assume that 
> throwing an exception is the only reason control can escape). The 
> following class takes care of it:
> 
> class (Applicative μ, Monad μ) ⇒ MonadFinally μ where
>    finally' ∷ μ α → (Maybe α → μ β) → μ (α, β)
>    finally ∷ μ α → μ β → μ α
>    finally m = fmap fst . finally' m . const
> 
> Finalizers have type 'Maybe α → μ β' so we can
> 
> (a) Thread transformer side effects properly:
> 
> instance MonadFinally μ ⇒ MonadFinally (L.StateT s μ) where
>    finally' m f = L.StateT $ \s → do
>      ~(~(mr, _), ~(fr, s'')) ← finally' (L.runStateT m s) $ \mbr → do
>        let ~(a, s') = case mbr of
>               Just ~(x, t) → (Just x, t)
>               Nothing → (Nothing, s)
>        L.runStateT (f a) s'
>      return ((mr, fr), s'')
> 
> (b) Detect that control escaped computation before producing a result 
> (finalizer will be called with 'Nothing' in that case).
> 
> instance (MonadFinally μ, Error e) ⇒ MonadFinally (ErrorT e μ) where
>    finally' m f = ErrorT $ do
>      ~(mr, fr) ← finally' (runErrorT m) $ \mbr →
>        runErrorT $ f $ case mbr of
>          Just (Right a) → Just a
>          _ → Nothing
>      return $ (,) <$> mr <*> fr
> 
> That of course does not mean that I can use 'finally' and friends with 
> ContT, but I can use them with monads which are carefully /implemented/ 
> on top of ContT but do not expose it's full power to the users.
> 



More information about the Haskell-Cafe mailing list