Skip to content

Commit

Permalink
Control.Exception.Lens.mappedException ∷ (Exception e, Exception e') …
Browse files Browse the repository at this point in the history
…⇒ Setter s s e e'
  • Loading branch information
liyang committed Apr 6, 2013
1 parent 5206e14 commit a4e6135
Showing 1 changed file with 35 additions and 0 deletions.
35 changes: 35 additions & 0 deletions src/Control/Exception/Lens.hs
Expand Up @@ -44,6 +44,8 @@ module Control.Exception.Lens
, throwing
, throwingM
, throwingTo
-- * Mapping
, mappedException, mappedException'
-- * Exceptions
, exception
-- * Exception Handlers
Expand Down Expand Up @@ -318,6 +320,39 @@ throwingTo :: MonadIO m => ThreadId -> AReview s SomeException a b -> b -> m ()
throwingTo tid l = reviews l (liftIO . throwTo tid)
{-# INLINE throwingTo #-}

----------------------------------------------------------------------------
-- Mapping
----------------------------------------------------------------------------

-- | This 'Setter' can be used to purely map over the 'Exception's an
-- arbitrary expression might throw; it is a variant of 'mapException' in
-- the same way that 'mapped' is a variant of 'fmap'.
--
-- > 'mapException' ≡ 'over' 'mappedException'
--
-- This view that every Haskell expression can be regarded as carrying a bag
-- of 'Exception's is detailed in “A Semantics for Imprecise Exceptions” by
-- Peyton Jones & al. at PLDI ’99.
--
-- The following maps failed assertions to arithmetic overflow:
--
-- >>> handling _Overflow (\_ -> return "caught") $ assert False (return "uncaught") & mappedException %~ \ (AssertionFailed _) -> Overflow
-- "caught"
mappedException :: (Exception e, Exception e') => Setter s s e e'
mappedException = sets mapException
{-# INLINE mappedException #-}

-- | This is a type restricted version of 'mappedException', which avoids
-- the type ambiguity in the input 'Exception' when using 'set'.
--
-- The following maps any exception to arithmetic overflow:
--
-- >>> handling _Overflow (\_ -> return "caught") $ assert False (return "uncaught") & mappedException' .~ Overflow
-- "caught"
mappedException' :: (Exception e') => Setter s s SomeException e'
mappedException' = mappedException
{-# INLINE mappedException' #-}

----------------------------------------------------------------------------
-- IOException
----------------------------------------------------------------------------
Expand Down

0 comments on commit a4e6135

Please sign in to comment.