[Haskell-cafe] Monad-control rant

Mikhail Vorozhtsov mikhail.vorozhtsov at gmail.com
Mon Nov 14 07:25:34 CET 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