lens-errors-0.2.0.0: Error handling in lens chains

Safe HaskellSafe
LanguageHaskell2010

Control.Lens.Error

Contents

Synopsis

Actions

examine :: Monoid e => Getting (e, a) s a -> s -> (e, a) Source #

See also ^&.

View the focus of a lens or traversal over a monoid. Returns the element and the monoidal sum of any errors encountered. Analogous to ^. with error collection.

>>> examine (_2 . traversed . fizzleWithWhen (\n -> [show n]) even . to (:[])) ("hi", [1, 2, 3, 4])
(["2","4"],[1,3])

examineList :: Monoid e => Getting (e, [a]) s a -> s -> (e, [a]) Source #

See also ^&..

View the focuses of a traversal as a list. Returns the elements and the monoidal sum of any errors encountered. Analogous to ^.. with error collection.

>>> examineList ((_2 . traversed . fizzleWithWhen (\n -> [show n]) even)) ("hi", [1, 2, 3, 4])
(["2","4"],[1,3])

tryModify :: LensLike (Validation e) s t a b -> (a -> b) -> s -> Validation e t Source #

See also %&~

Modify the focus of a lens/traversal. Returns a monoidal summary of failures or the altered structure.

>>> tryModify  (_2 . traversed . fizzleWhen ["shouldn't fail"] (const False)) (*100) ("hi", [1, 2, 3, 4])
Success ("hi",[100,200,300,400])
>>> tryModify  (_2 . traversed . fizzleWithWhen (\n -> [n]) even) (*100) ("hi", [1, 2, 3, 4])
Failure [2,4]

tryModify' :: LensLike (Validation e) s t a b -> (a -> Validation e b) -> s -> Validation e t Source #

See also %%&~

Modify the focus of a lens/traversal with a function which may fail. Returns a monoidal summary of failures or the altered structure.

>>> tryModify' (_2 . traversed . fizzleWithWhen (\n -> [n]) even) (Success . (*100)) ("hi", [1, 2, 3, 4])
Failure [2,4]
>>> tryModify' (_2 . traversed) (\n -> Failure [show n <> " failed"]) ("hi", [1, 2, 3, 4])
Failure ["1 failed","2 failed","3 failed","4 failed"]

preexamine :: Monoid e => Getting (e, First a) s a -> s -> Validation e a Source #

See also ^&?

Find the first element of a traversal; or return all errors found along the way.

>>> preexamine (traversed . fizzleWhen ["odd"] odd) [1, 2, 3, 4]
Success 2
>>> preexamine (traversed . fizzleWithWhen (\s -> [show s <> " is too small"]) (<10)) [1, 2, 3, 4]
Failure ["1 is too small","2 is too small","3 is too small","4 is too small"]

Operators

(^&.) :: Monoid e => s -> Getting (e, a) s a -> (e, a) infixl 8 Source #

Operator alias of examine

View the focus of a lens or traversal over a monoid. Returns the element and the monoidal sum of any errors encountered. Analogous to ^. with error collection.

>>> ("hi", [1, 2, 3, 4]) ^&. _2 . traversed . fizzleWithWhen (\n -> [show n]) even . to (:[])
(["2","4"],[1,3])

(^&..) :: Monoid e => s -> Getting (e, [a]) s a -> (e, [a]) infixl 8 Source #

Operator alias of examineList

View the focuses of a traversal as a list. Returns the elements and the monoidal sum of any errors encountered. Analogous to ^.. with error collection.

>>> ("hi", [1, 2, 3, 4]) ^&..  (_2 . traversed . fizzleWithWhen (\n -> [show n]) even)
(["2","4"],[1,3])

(^&?) :: Monoid e => s -> Getting (e, First a) s a -> Validation e a infixl 8 Source #

Operator alias of preexamine

Find the first element of a traversal; or return all errors found along the way.

>>> [1, 2, 3, 4] ^&? traversed . fizzleWhen ["odd"] odd
Success 2
>>> [1, 2, 3, 4] ^&? traversed . fizzleWithWhen (\s -> [show s <> " is too small"]) (<10)
Failure ["1 is too small","2 is too small","3 is too small","4 is too small"]

(%&~) :: LensLike (Validation e) s t a b -> (a -> b) -> s -> Validation e t infixl 8 Source #

Operator alias of tryModify

Modify the focus of a lens/traversal. Returns a monoidal summary of failures or the altered structure.

>>> ("hi", [1, 2, 3, 4]) & _2 . traversed . fizzleWhen ["shouldn't fail"] (const False) %&~ (*100)
Success ("hi",[100,200,300,400])
>>> ("hi", [1, 2, 3, 4]) & _2 . traversed . fizzleWithWhen (\n -> [n]) even %&~ (*100)
Failure [2,4]

(%%&~) :: LensLike (Validation e) s t a b -> (a -> Validation e b) -> s -> Validation e t infixl 8 Source #

Operator alias of tryModify'

Modify the focus of a lens/traversal with a function which may fail. Returns a monoidal summary of failures or the altered structure.

The definition of this function is actually just:

(%%&~) = (%%~)

But this combinator is provided for discoverability, completeness, and hoogle-ability.

>>> ("hi", [1, 2, 3, 4]) & _2 . traversed . fizzleWithWhen (\n -> [n]) even %%&~ Success . (*100)
Failure [2,4]
>>> ("hi", [1, 2, 3, 4]) & _2 . traversed %%&~ (\n -> Failure [show n <> " failed"])
Failure ["1 failed","2 failed","3 failed","4 failed"]

Failing

fizzleWhen :: LensFail e f => e -> (s -> Bool) -> LensLike' f s s Source #

Cause the current traversal to fizzle with a failure when the focus matches a predicate

>>> ("hi", [1, 2, 3, 4]) ^&.. _2 . traversed . fizzleWhen ["failure"] even :: ([String], [Int])
(["failure","failure"],[1,3])

fizzleUnless :: LensFail e f => e -> (s -> Bool) -> LensLike' f s s Source #

Cause the current traversal to fizzle with a failure when the focus fails a predicate

>>> ("hi", [1, 2, 3, 4]) ^&.. _2 . traversed . fizzleUnless ["failure"] even
(["failure","failure"],[2,4])

fizzleWith :: LensFail e f => (s -> e) -> LensLike f s t a b Source #

Always fizzle with the given error builder >>> let p x = [show x] >>> ("hi", [1, 2, 3, 4]) ^&.. _2 . traversed . fizzleWith p (["1","2","3","4"],[])

fizzleWithWhen :: LensFail e f => (s -> e) -> (s -> Bool) -> LensLike' f s s Source #

Fizzle using the given error builder when the focus matches a predicate

>>> let p x = [show x <> " was even"]
>>> ("hi", [1, 2, 3, 4]) ^&.. _2 . traversed . fizzleWithWhen p even
(["2 was even","4 was even"],[1,3])

fizzleWithUnless :: LensFail e f => (s -> e) -> (s -> Bool) -> LensLike' f s s Source #

Fizzle using the given error builder when the focus fails a predicate

>>> let p x = [show x <> " was even"]
>>> ("hi", [1, 2, 3, 4]) ^&.. _2 . traversed . fizzleWithUnless p odd
(["2 was even","4 was even"],[1,3])

maybeFizzleWith :: LensFail e f => (s -> Maybe e) -> LensLike' f s s Source #

Given a function which might produce an error, fizzle on Just, pass through on Nothing

>>> let p x
>>> | even x    = Just [show x <> " was even"]
>>> | otherwise = Nothing
>>> ("hi", [1, 2, 3, 4]) ^&.. _2 . traversed . maybeFizzleWith p
(["2 was even","4 was even"],[1,3])

orFizzle :: (LensFail e f, Applicative f) => Traversing (->) f s t a b -> e -> LensLike f s t a b Source #

Fail with the given error when the provided traversal produces no elements.

>>> ("hi", [1, 2, 3, 4]) ^&.. (_2 . traversed . filtered (> 10)) `orFizzle` ["nothing over 10"]
(["nothing over 10"],[])

orFizzleWith :: (LensFail e f, Applicative f) => Traversing (->) f s t a b -> (s -> e) -> LensLike f s t a b Source #

Fail using the given error builder when the provided traversal produces no elements.

>>> ("hi", [1, 2, 3, 4]) ^&.. (_2 . traversed . filtered (> 10)) `orFizzleWith` (\(_, xs) -> ["searched " <> show (length xs) <> " elements, no luck"])
(["searched 4 elements, no luck"],[])

Adjusting Errors

adjustingErrors :: LensFail e f => (e -> e) -> LensLike' f s s Source #

Adjust any errors which occur in the following branch. Note that we can't change the error type, but this can be helpful for adding context to errors if they occur at a position without enough context.

This is does nothing when no errors occur.

>>> [1, 2, 3, 4 :: Int] ^&.. traversed . fizzleWhen ["got 4"] (== 4) . adjustingErrors (fmap (<> "!")) . fizzleWhen ["got 3"] (== 3)
(["got 3!","got 4"],[1,2])

adjustingErrorsWith :: LensFail e f => (s -> e -> e) -> LensLike' f s s Source #

Adjust any errors which occur in the following branch, using the value available at the current position to add context.. Note that we can't change the error type, but this can be helpful for adding context to errors if they occur at a position without enough context.

This is does nothing when no errors occur.

>>> [1, 2, 3, 4 :: Int] ^&.. traversed . fizzleWhen ["got 4"] (== 4) . adjustingErrorsWith (\n -> fmap (\e -> show n <> ": " <> e)) . fizzleWhen ["fail"] (== 3)
(["3: fail","got 4"],[1,2])

Classes

class LensFail e f | f -> e where Source #

Methods

fizzle :: e -> f a Source #

alterErrors :: (e -> e) -> f a -> f a Source #

Instances
LensFail e (Validation e) Source # 
Instance details

Defined in Control.Lens.Error.Internal.LensFail

Methods

fizzle :: e -> Validation e a Source #

alterErrors :: (e -> e) -> Validation e a -> Validation e a Source #

LensFail e (Either e) Source # 
Instance details

Defined in Control.Lens.Error.Internal.LensFail

Methods

fizzle :: e -> Either e a Source #

alterErrors :: (e -> e) -> Either e a -> Either e a Source #

LensFail e (Const (Validation e a) :: Type -> Type) Source # 
Instance details

Defined in Control.Lens.Error.Internal.LensFail

Methods

fizzle :: e -> Const (Validation e a) a0 Source #

alterErrors :: (e -> e) -> Const (Validation e a) a0 -> Const (Validation e a) a0 Source #

LensFail e (Const (Either e a) :: Type -> Type) Source # 
Instance details

Defined in Control.Lens.Error.Internal.LensFail

Methods

fizzle :: e -> Const (Either e a) a0 Source #

alterErrors :: (e -> e) -> Const (Either e a) a0 -> Const (Either e a) a0 Source #

Monoid a => LensFail e (Const (e, a) :: Type -> Type) Source # 
Instance details

Defined in Control.Lens.Error.Internal.LensFail

Methods

fizzle :: e -> Const (e, a) a0 Source #

alterErrors :: (e -> e) -> Const (e, a) a0 -> Const (e, a) a0 Source #

Re-exports