profunctor-optics-0.0.0.3: An optics library compatible with the typeclasses in 'profunctors'.

Safe HaskellNone
LanguageHaskell2010

Control.Exception.Optic

Contents

Synopsis

Common optics

non' :: Prism' a () -> Iso' (Maybe a) a Source #

Generate an isomorphism between Maybe (a | isnt p a) and a.

non' p generalizes non (p # ()) to take any unit Prism

unlifted :: MonadUnliftIO m => Grate (m a) (m b) (IO a) (IO b) Source #

Unlift an action into an IO context.

liftIOcoview unlifted
>>> let catchA = catch @ArithException
>>> zipsWith unlifted (flip catchA . const) (throwIO Overflow) (print "caught")
"caught" 

exmapped :: Exception e1 => Exception e2 => Setter s s e1 e2 Source #

Map one exception into another as proposed in the paper "A semantics for imprecise exceptions".

>>> handles (only Overflow) (\_ -> return "caught") $ assert False (return "uncaught") & (exmapped ..~ \ (AssertionFailed _) -> Overflow)
"caught"
exmapped :: Exception e => Setter s s SomeException e

exception :: Exception e => Prism' SomeException e Source #

Focus on whether a given exception has occurred.

pattern Exception :: forall a. Exception a => a -> SomeException Source #

Derived operators

throws :: MonadIO m => Exception e => AReview e b -> b -> m r Source #

Throw an exception described by an optic.

throws o e `seq` x  ≡ throws o e

throws_ :: MonadIO m => Exception e => AReview e () -> m r Source #

Variant of throws for error constructors with no arguments.

throwsTo :: MonadIO m => Exception e => ThreadId -> AReview e b -> b -> m () Source #

Raise an Exception specified by an optic in the target thread.

throwsTo thread o ≡ throwTo thread . review o

tries :: MonadUnliftIO m => Exception ex => AOption e ex e -> m a -> m (Either e a) Source #

Test for synchronous exceptions that match a given optic.

In the style of 'safe-exceptions' this function rethrows async exceptions synchronously in order to preserve async behavior,

tries :: MonadUnliftIO m => AOption e SomeException e -> m a -> m (Either e a)
tries exception :: MonadUnliftIO m => Exception e => m a -> m (Either e a)

tries_ :: MonadUnliftIO m => Exception ex => AOption e ex e -> m a -> m (Maybe a) Source #

A variant of tries that returns synchronous exceptions.

catches :: MonadUnliftIO m => Exception ex => AOption e ex e -> m a -> (e -> m a) -> m a Source #

Catch synchronous exceptions that match a given optic.

Rethrows async exceptions synchronously in order to preserve async behavior.

catches :: MonadUnliftIO m => AOption e SomeException e -> m a -> (e -> m a) -> m a
catches exception :: MonadUnliftIO m => Exception e => m a -> (e -> m a) -> m a
>>> catches (only Overflow) (throwIO Overflow) (\_ -> return "caught")
"caught"

catches_ :: MonadUnliftIO m => Exception ex => AOption e ex e -> m a -> m a -> m a Source #

Catch synchronous exceptions that match a given optic, discarding the match.

>>> catches_ (only Overflow) (throwIO Overflow) (return "caught")
"caught"

handles :: MonadUnliftIO m => Exception ex => AOption e ex e -> (e -> m a) -> m a -> m a Source #

Flipped variant of catches.

>>> handles (only Overflow) (\_ -> return "caught") $ throwIO Overflow
"caught"

handles_ :: MonadUnliftIO m => Exception ex => AOption e ex e -> m a -> m a -> m a Source #

Flipped variant of catches_.

>>> handles_ (only Overflow) (return "caught") $ throwIO Overflow
"caught"

ioException :: Prism' SomeException IOException Source #

Exceptions that occur in the IO Monad.

An IOException records a more specific error type, a descriptive string and possibly the handle that was used when the error was flagged.

IO Error Fields

ioeLocation :: Lens' IOException String Source #

Where the error happened.

ioeDescription :: Lens' IOException String Source #

Error type specific information.

ioeHandle :: Lens' IOException (Maybe Handle) Source #

The handle used by the action flagging this error.

ioeFileName :: Lens' IOException (Maybe FilePath) Source #

fileName the error is related to.

ioeErrno :: Lens' IOException (Maybe CInt) Source #

errno leading to this error, if any.

IO Error Types

noSuchThing :: Prism' IOErrorType () Source #

TODO: Document

resourceBusy :: Prism' IOErrorType () Source #

TODO: Document

eof :: Prism' IOErrorType () Source #

TODO: Document

userError :: Prism' IOErrorType () Source #

TODO: Document

systemError :: Prism' IOErrorType () Source #

TODO: Document

otherError :: Prism' IOErrorType () Source #

TODO: Document

Async Exceptions

sync :: Exception e => Prism' e e Source #

Focus on whether an exception is synchronous.

async :: Exception e => Prism' e e Source #

Focus on whether an exception is asynchronous.

asyncException :: Exception e => Prism' SomeException e Source #

Focus on whether a given asynchronous exception has occurred.

pattern AsyncException :: forall a. Exception a => a -> SomeException Source #

timeExpired :: Prism' IOErrorType () Source #

TODO: Document

interrupted :: Prism' IOErrorType () Source #

TODO: Document

stackOverflow :: Prism' AsyncException () Source #

The current thread's stack exceeded its limit. Since an Exception has been raised, the thread's stack will certainly be below its limit again, but the programmer should take remedial action immediately.

heapOverflow :: Prism' AsyncException () Source #

The program's heap usage has exceeded its limit.

See Exception for more information.

threadKilled :: Prism' AsyncException () Source #

This Exception is raised by another thread calling killThread, or by the system if it needs to terminate the thread for some reason.

userInterrupt :: Prism' AsyncException () Source #

This Exception is raised by default in the main thread of the program when the user requests to terminate the program via the usual mechanism(s) (e.g. Control-C in the console).

Arithmetic exceptions

overflow :: Prism' ArithException () Source #

Detect arithmetic overflow.

underflow :: Prism' ArithException () Source #

Detect arithmetic underflow.

lossOfPrecision :: Prism' ArithException () Source #

Detect arithmetic loss of precision.

divideByZero :: Prism' ArithException () Source #

Detect division by zero.

denormal :: Prism' ArithException () Source #

Detect whether a FLOP was performed on a subnormal number.

ratioZeroDenominator :: Prism' ArithException () Source #

Detect zero denominators.

Array Exceptions

indexOutOfBounds :: Prism' ArrayException String Source #

Detect attempts to index an array outside its declared bounds.

undefinedElement :: Prism' ArrayException String Source #

Detect attempts to evaluate an element of an array that has not been initialized.

Miscellaneous Exceptions

illegal :: Profunctor p => t -> Optic' p t () Source #

nonTermination :: Prism' NonTermination () Source #

Thrown when the runtime system detects that the computation is guaranteed not to terminate. Note that there is no guarantee that the runtime system will notice whether any given computation is guaranteed to terminate or not.

nestedAtomically :: Prism' NestedAtomically () Source #

Thrown when the program attempts to call atomically, from the STM package, inside another call to atomically.

blockedIndefinitelyOnMVar :: Prism' BlockedIndefinitelyOnMVar () Source #

The thread is blocked on an MVar, but there are no other references to the MVar so it can't ever continue.

blockedIndefinitelyOnSTM :: Prism' BlockedIndefinitelyOnSTM () Source #

The thread is waiting to retry an STM transaction, but there are no other references to any TVars involved, so it can't ever continue.

deadlock :: Prism' Deadlock () Source #

There are no runnable threads, so the program is deadlocked. The Deadlock Exception is raised in the main thread only.

noMethodError :: Prism' NoMethodError String Source #

A class method without a definition (neither a default definition, nor a definition in the appropriate instance) was called.

recConError :: Prism' RecConError String Source #

An uninitialised record field was used.

recSelError :: Prism' RecSelError String Source #

A record selector was applied to a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another.

recUpdError :: Prism' RecUpdError String Source #

A record update was performed on a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another.

errorCall :: Prism' ErrorCall String Source #

Thrown when the user calls error.

allocationLimitExceeded :: Prism' AllocationLimitExceeded () Source #

This thread has exceeded its allocation limit.