validation-selective-0.1.0.0: Lighweight pure data validation based on Applicative and Selective functors
Copyright(c) 2020 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Validation.Combinators

Description

Helpful combinators to work with Validation data type.

Synopsis

Documentation

validateAll :: forall e b a f. (Foldable f, Semigroup e) => f (a -> Validation e b) -> a -> Validation e a Source #

Validate all given checks in a Foldable. Returns the Success of the start element when all checks are successful.

A basic example of usage could look like this:

> let validatePassword = validateAll
        [ validateEmptyPassword
        , validateShortPassword
        ]

> validateAll "VeryStrongPassword"
Success "VeryStrongPassword"

> validateAll ""
Failure (EmptyPassword :| [ShortPassword])

When* functions

whenSuccess :: Applicative f => x -> Validation e a -> (a -> f x) -> f x Source #

Applies the given action to Validation if it is Success and returns the result. In case of Failure the default value is returned.

>>> whenSuccess "bar" (Failure "foo") (\a -> "success!" <$ print a)
"bar"
>>> whenSuccess "bar" (Success 42) (\a -> "success!" <$ print a)
42
"success!"

whenFailure :: Applicative f => x -> Validation e a -> (e -> f x) -> f x Source #

Applies the given action to Validation if it is Failure and returns the result. In case of Success the default value is returned.

>>> whenFailure "bar" (Failure 42) (\a -> "foo" <$ print a)
42
"foo"
>>> whenFailure "bar" (Success 42) (\a -> "foo" <$ print a)
"bar"

whenSuccess_ :: Applicative f => Validation e a -> (a -> f ()) -> f () Source #

Applies given action to the Validation content if it is Success.

Similar to whenSuccess but the default value is ().

>>> whenSuccess_ (Failure "foo") print
>>> whenSuccess_ (Success 42) print
42

whenFailure_ :: Applicative f => Validation e a -> (e -> f ()) -> f () Source #

Applies given action to the Validation content if it is Failure.

Similar to whenFailure but the default value is ().

>>> whenFailure_ (Success 42) putStrLn
>>> whenFailure_ (Failure "foo") putStrLn
foo

whenSuccessM :: Monad m => x -> m (Validation e a) -> (a -> m x) -> m x Source #

Monadic version of whenSuccess. Applies monadic action to the given Validation in case of Success. Returns the resulting value, or provided default.

>>> whenSuccessM "bar" (pure $ Failure "foo") (\a -> "success!" <$ print a)
"bar"
>>> whenSuccessM "bar" (pure $ Success 42) (\a -> "success!" <$ print a)
42
"success!"

whenFailureM :: Monad m => x -> m (Validation e a) -> (e -> m x) -> m x Source #

Monadic version of whenFailure. Applies monadic action to the given Validation in case of Failure. Returns the resulting value, or provided default.

>>> whenFailureM "bar" (pure $ Failure 42) (\a -> "foo" <$ print a)
42
"foo"
>>> whenFailureM "bar" (pure $ Success 42) (\a -> "foo" <$ print a)
"bar"

whenSuccessM_ :: Monad m => m (Validation e a) -> (a -> m ()) -> m () Source #

Monadic version of whenSuccess_. Applies monadic action to the given Validation in case of Success. Similar to whenSuccessM but the default is ().

>>> whenSuccessM_ (pure $ Failure "foo") print
>>> whenSuccessM_ (pure $ Success 42) print
42

whenFailureM_ :: Monad m => m (Validation e a) -> (e -> m ()) -> m () Source #

Monadic version of whenFailure_. Applies monadic action to the given Validation in case of Failure. Similar to whenFailureM but the default is ().

>>> whenFailureM_ (pure $ Success 42) putStrLn
>>> whenFailureM_ (pure $ Failure "foo") putStrLn
foo

Maybe conversion

failureToMaybe :: Validation e a -> Maybe e Source #

Maps Failure of Validation to Just.

>>> failureToMaybe (Failure True)
Just True
>>> failureToMaybe (Success "aba")
Nothing

successToMaybe :: Validation e a -> Maybe a Source #

Maps Success of Validation to Just.

>>> successToMaybe (Failure True)
Nothing
>>> successToMaybe (Success "aba")
Just "aba"

maybeToFailure :: a -> Maybe e -> Validation e a Source #

Maps Just to Failure In case of Nothing it wraps the given default value into Success.

>>> maybeToFailure True (Just "aba")
Failure "aba"
>>> maybeToFailure True Nothing
Success True

maybeToSuccess :: e -> Maybe a -> Validation e a Source #

Maps Just to Success. In case of Nothing it wraps the given default value into Failure

>>> maybeToSuccess True (Just "aba")
Success "aba"
>>> maybeToSuccess True Nothing
Failure True