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

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Optic.Option

Contents

Synopsis

Option & Ixoption

type Option s a = forall p. (Choice p, Strong p, forall x. Contravariant (p x)) => Optic' p s a Source #

A Option combines at most one element, with no interactions.

option :: (s -> Maybe a) -> Option s a Source #

Obtain a Option directly.

option . preview ≡ id
option (view o) ≡ o . just
>>> preview (option . preview $ selected even) (2, "yes")
Just "yes"
>>> preview (option . preview $ selected even) (3, "no")
Nothing
>>> preview (option listToMaybe) "foo"
Just 'f'

ioption :: (s -> Maybe (i, a)) -> Ixoption i s a Source #

Obtain an Ixoption directly.

failing :: AOption a s a -> AOption a s a -> Option s a infixl 3 Source #

If the first Option has no focus then try the second one.

toOption :: View s (Maybe a) -> Option s a Source #

Obtain a Option from a View.

toOption o ≡ o . just
toOption o ≡ option (view o)

fromOption :: AOption a s a -> View s (Maybe a) Source #

Obtain a View from a Option

Optics

optioned :: Option (Maybe a) a Source #

The canonical Option.

>>> [Just 1, Nothing] ^.. folded . optioned
[1]

filtered :: (a -> Bool) -> Option a a Source #

Filter another optic.

>>> [1..10] ^.. folded . filtered even
[2,4,6,8,10]

Primitive operators

withOption :: Optic (OptionRep r) s t a b -> (a -> Maybe r) -> s -> Maybe r Source #

TODO: Document

withIxoption :: (Additive - Monoid) i => AIxoption r i s a -> (i -> a -> Maybe r) -> s -> Maybe r Source #

TODO: Document

Operators

(^?) :: s -> AOption a s a -> Maybe a infixl 8 Source #

An infix alias for preview'.

(^?) ≡ flip preview'

Perform a safe head of a Fold or Traversal or retrieve Just the result from a View or Lens.

When using a Traversal as a partial Lens, or a Fold as a partial View this can be a convenient way to extract the optional value.

>>> Left 4 ^? left'
Just 4
>>> Right 4 ^? left'
Nothing

preview :: MonadReader s m => AOption a s a -> m (Maybe a) Source #

TODO: Document

preuse :: MonadState s m => AOption a s a -> m (Maybe a) Source #

TODO: Document

is :: AOption a s a -> s -> Bool Source #

Check whether the optic is matched.

>>> is just Nothing
False

isnt :: AOption a s a -> s -> Bool Source #

Check whether the optic isn't matched.

>>> isnt just Nothing
True

Indexed operators

ipreview :: (Additive - Monoid) i => AIxoption (i, a) i s a -> s -> Maybe (i, a) Source #

TODO: Document

ipreviews :: (Additive - Monoid) i => AIxoption r i s a -> (i -> a -> r) -> s -> Maybe r Source #

TODO: Document

MonadUnliftIO

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"