valor-1.0.0.0: Simple and powerful data validation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Valor.Internal

Description

Guts of valor.

Synopsis

Documentation

newtype Valid a Source #

Simple wrapper holding a Valid value that has successfully passed the validation. It's not supposed to be mapped over, parsed, read, coerced etc. (so as to not modify / spoil the Valid value). The only way to construct it is by passing an input throug a validator using validateP or validateM.

Constructors

Valid a 

Instances

Instances details
Eq a => Eq (Valid a) Source # 
Instance details

Defined in Data.Valor.Internal

Methods

(==) :: Valid a -> Valid a -> Bool #

(/=) :: Valid a -> Valid a -> Bool #

Show a => Show (Valid a) Source # 
Instance details

Defined in Data.Valor.Internal

Methods

showsPrec :: Int -> Valid a -> ShowS #

show :: Valid a -> String #

showList :: [Valid a] -> ShowS #

unValid :: Valid a -> a Source #

Extract a value from the Valid wrapper for further use / processing.

newtype Valor i m e Source #

Valor (VALidatOR) is the centerpiece of this validation library. You can think of it as a function from an input to a possible error.

Because Valor is essentially just an alias for a function of type i -> m (Wrong e) we can think of operations on Valor as operations on the resulting Wrong once i has been applied.

Here's a useful table detailing the behavior of each operation on Wrong (and consequently Valor):

con / <>app / <*>altacc
Inert a × Inert bInert $ a <> bInert $ a bInert aInert a
Inert a × Wrong bWrong $ a <> bWrong $ a bInert aInert a
Wrong a × Inert bWrong $ a <> bWrong $ a bInert bInert b
Wrong a × Wrong bWrong $ a <> bWrong $ a bWrong bWrong $ a <> b

NOTE: You can not directly interact with Wrong as it is only used internally in Valor.

Constructors

Valor 

Fields

Instances

Instances details
Monad m => Monad (Valor i m) Source #

Evaluates the "input" Valor. If the result is Inert e it takes the e and binds it to get the next Valor, however, if the result is Wrong e it will "remember" that and if the next Valor is Inert it'll be converted to Wrong. This will essentially make the whole Monadic computation result in Wrong.

Instance details

Defined in Data.Valor.Internal

Methods

(>>=) :: Valor i m a -> (a -> Valor i m b) -> Valor i m b #

(>>) :: Valor i m a -> Valor i m b -> Valor i m b #

return :: a -> Valor i m a #

Monad m => Functor (Valor i m) Source #

Evaluates the Valor and fmaps the f over the resulting Wrong.

Instance details

Defined in Data.Valor.Internal

Methods

fmap :: (a -> b) -> Valor i m a -> Valor i m b #

(<$) :: a -> Valor i m b -> Valor i m a #

Monad m => Applicative (Valor i m) Source #

Evaluates both Valor operands and then does the <*> operation on the resulting Wrongs.

Instance details

Defined in Data.Valor.Internal

Methods

pure :: a -> Valor i m a #

(<*>) :: Valor i m (a -> b) -> Valor i m a -> Valor i m b #

liftA2 :: (a -> b -> c) -> Valor i m a -> Valor i m b -> Valor i m c #

(*>) :: Valor i m a -> Valor i m b -> Valor i m b #

(<*) :: Valor i m a -> Valor i m b -> Valor i m a #

(Monad m, Semigroup e) => Semigroup (Valor i m e) Source #

Implemented using the Wrong <>. Think of it as evaluating the Valor and then mappending the resulting Wrongs.

Instance details

Defined in Data.Valor.Internal

Methods

(<>) :: Valor i m e -> Valor i m e -> Valor i m e #

sconcat :: NonEmpty (Valor i m e) -> Valor i m e #

stimes :: Integral b => b -> Valor i m e -> Valor i m e #

(Monad m, Monoid e) => Monoid (Valor i m e) Source #

Implemented using the Wrong mempty wrapped in Valor.

Instance details

Defined in Data.Valor.Internal

Methods

mempty :: Valor i m e #

mappend :: Valor i m e -> Valor i m e -> Valor i m e #

mconcat :: [Valor i m e] -> Valor i m e #

data Wrong e Source #

The internal data type used to accumulate errors and keep track of the error state (if there was an actual error or not).

Constructors

Inert e 
Wrong e 

Instances

Instances details
Functor Wrong Source #

Just a simple Functor instance which applies the function to the value within.

Instance details

Defined in Data.Valor.Internal

Methods

fmap :: (a -> b) -> Wrong a -> Wrong b #

(<$) :: a -> Wrong b -> Wrong a #

Applicative Wrong Source #

Applicatives pure is implemented as Inert. If Wrong is encountered in any of the operands then the result will also be Wrong.

Instance details

Defined in Data.Valor.Internal

Methods

pure :: a -> Wrong a #

(<*>) :: Wrong (a -> b) -> Wrong a -> Wrong b #

liftA2 :: (a -> b -> c) -> Wrong a -> Wrong b -> Wrong c #

(*>) :: Wrong a -> Wrong b -> Wrong b #

(<*) :: Wrong a -> Wrong b -> Wrong a #

Eq e => Eq (Wrong e) Source # 
Instance details

Defined in Data.Valor.Internal

Methods

(==) :: Wrong e -> Wrong e -> Bool #

(/=) :: Wrong e -> Wrong e -> Bool #

Semigroup e => Semigroup (Wrong e) Source #

Inert operands are ignored and Wrong operands are mappended. If both operands are Inert then the first one is ignored. If Wrong is one of the operands then the resulting value is also Wrong.

Instance details

Defined in Data.Valor.Internal

Methods

(<>) :: Wrong e -> Wrong e -> Wrong e #

sconcat :: NonEmpty (Wrong e) -> Wrong e #

stimes :: Integral b => b -> Wrong e -> Wrong e #

Monoid e => Monoid (Wrong e) Source #

The Monoids mempty is implemented as Inert mempty.

Instance details

Defined in Data.Valor.Internal

Methods

mempty :: Wrong e #

mappend :: Wrong e -> Wrong e -> Wrong e #

mconcat :: [Wrong e] -> Wrong e #

conW :: Semigroup e => Wrong e -> Wrong e -> Wrong e Source #

An alias for the mappend (<>).

appW :: Wrong (a -> b) -> Wrong a -> Wrong b Source #

An alias for the <*>.

altW :: Wrong e -> Wrong e -> Wrong e Source #

Non accumulating Alternative. As long as there's one Inert value the resulting value will be Inert. However, if there are two Wrongs then only the second one will be returned as a resulting value. If there are two Inerts then only the first one is returned.

accW :: Semigroup e => Wrong e -> Wrong e -> Wrong e Source #

Accumulating Alternative. Almost the same as altW except if there are two Wrongs they are mappended together.

valW :: Wrong e -> e Source #

Extracts the value contained within the Wrong regardless if the "internal" state is Inert or Wrong.

wrong :: (e -> a) -> (e -> a) -> Wrong e -> a Source #

If the given value is Wrong, the first function will be applied, if the value is Inert then the second function will be applied.

isInert :: Wrong e -> Bool Source #

Checks if the value is Inert.

isWrong :: Wrong e -> Bool Source #

Checks if the value is Wrong.