validity-0.4.0.1: Validity typeclass

Safe HaskellNone
LanguageHaskell2010

Data.Validity

Contents

Description

Validity is used to specify additional invariants upon values that are not enforced by the type system.

Let's take an example. Suppose we were to implement a type Prime that represents prime integers.

If you were to completely enforce the invariant that the represented number is a prime, then we could use Natural and only store the index of the given prime in the infinite sequence of prime numbers. This is very safe but also very expensive if we ever want to use the number, because we would have to calculcate all the prime numbers until that index.

Instead we choose to implement Prime by a newtype Prime = Prime Int. Now we have to maintain the invariant that the Int that we use to represent the prime is in fact positive and a prime.

The Validity typeclass allows us to specify this invariant (and enables testing via the genvalidity libraries: https://hackage.haskell.org/package/genvalidity ):

instance Validity Prime where
    validate (Prime n) = isPrime n <?@> "The 'Int' is prime."
    isValid (Prime n) = isPrime n

If certain typeclass invariants exist, you can make these explicit in the validity instance as well. For example, 'Fixed a' is only valid if a has an HasResolution instance, so the correct validity instance is HasResolution a => Validity (Fixed a).

Synopsis

Documentation

class Validity a where Source #

A class of types that have additional invariants defined upon them that aren't enforced by the type system

Purpose

validate checks whether a given value is a valid value and reports all reasons why the given value is not valid if that is the case.

isValid only checks whether a given value is a valid value of its type.

Instantiating Validity

To instantiate Validity, one has to implement both isValid and validate. Start by implementing validate. Use the helper functions below to define all the reasons why a given value would be a valid value of its type. Then define `isValid = isValidbyValidating' for now.

Example:

newtype Even = Even Int

instance Validity Even
    validate (Event i)
      even i <?@> "The contained 'Int' is even."
    isValid = isValidByValidating

If it turns out that, at this point, isValid is too slow for your taste, you can replace the implementation of isValid by a custom implementation. However, it is important that this isValid implementation has exactly the same semantics as isValidbyValidating.

Example:

newtype Even = Even Int

instance Validity Even
    validate (Event i)
      even i <?@> "The contained 'Int' is even."
    isValid (Event i) = even i

Semantics

isValid should be an underapproximation of actual validity.

This means that if isValid is not a perfect representation of actual validity, for safety reasons, it should never return True for invalid values, but it may return False for valid values.

For example:

isValid = const False

is a valid implementation for any type, because it never returns True for invalid values.

isValid (Even i) = i == 2

is a valid implementation for newtype Even = Even Int, but

isValid (Even i) = even i || i == 1

is not because it returns True for an invalid value: '1'.

Automatic instances with Generic

An instance of this class can be made automatically if the type in question has a Generic instance. This instance will try to use isValid to on all structural sub-parts of the value that is being checked for validity.

Example:

{-# LANGUAGE DeriveGeneric #-}

data MyType = MyType
    { myDouble :: Double
    { myString :: String
    } deriving (Show, Eq, Generic)

instance Validity MyType

generates something like:

instance Validity MyType where
    isValid (MyType d s)
        = isValid d && isValid s
    validate (MyType d s)
        = d <?!> "myDouble"
       <> s <?!> "myString"

Methods

validate :: a -> Validation Source #

validate :: (Generic a, GValidity (Rep a)) => a -> Validation Source #

isValid :: a -> Bool Source #

isValid :: (Generic a, GValidity (Rep a)) => a -> Bool Source #

Instances

Validity Bool Source #

Trivially valid

Validity Char Source #

Trivially valid

Validity Double Source #

NOT trivially valid:

  • NaN is not valid.
  • Infinite values are not valid.
Validity Float Source #

NOT trivially valid:

  • NaN is not valid.
  • Infinite values are not valid.
Validity Int Source #

Trivially valid

Validity Integer Source #

Trivially valid

Integer is not trivially valid under the hood, but instantiating Validity correctly would force validity to depend on a specific (big integer library integer-gmp versus integer-simple). This is rather impractical so for the time being we have opted for assuming that an Integer is always valid. Even though this is not technically sound, it is good enough for now.

Validity Ordering Source #

Trivially valid

Validity Rational Source #

Valid if the contained Integers are valid and the denominator is strictly positive.

Validity Word Source #

Trivially valid

Validity Word8 Source #

Trivially valid

Validity Word16 Source #

Trivially valid

Validity Word32 Source #

Trivially valid

Validity Word64 Source #

Trivially valid

Validity () Source #

Trivially valid

Methods

validate :: () -> Validation Source #

isValid :: () -> Bool Source #

Validity Natural Source #

Valid according to isValidNatural

Only available with base >= 4.8.

Validity Validation Source # 
Validity ValidationChain Source # 
Validity a => Validity [a] Source #

A list of things is valid if all of the things are valid.

This means that the empty list is considered valid. If the empty list should not be considered valid as part of your custom data type, make sure to write a custom Validity instance

Methods

validate :: [a] -> Validation Source #

isValid :: [a] -> Bool Source #

Validity a => Validity (Maybe a) Source #

A Maybe thing is valid if the thing inside is valid or it's nothing It makes sense to assume that Nothing is valid. If Nothing wasn't valid, you wouldn't have used a Maybe in the datastructure.

Validity a => Validity (NonEmpty a) Source #

A nonempty list is valid if all the elements are valid.

See the instance for 'Validity [a]' for more information.

HasResolution a => Validity (Fixed a) Source #

Valid according to the contained Integer.

(Validity a, Validity b) => Validity (Either a b) Source #

Any Either of things is valid if the contents are valid in either of the cases.

(Validity a, Validity b) => Validity (a, b) Source #

Any tuple of things is valid if both of its elements are valid

Methods

validate :: (a, b) -> Validation Source #

isValid :: (a, b) -> Bool Source #

(Validity a, Validity b, Validity c) => Validity (a, b, c) Source #

Any triple of things is valid if all three of its elements are valid

Methods

validate :: (a, b, c) -> Validation Source #

isValid :: (a, b, c) -> Bool Source #

(Validity a, Validity b, Validity c, Validity d) => Validity (a, b, c, d) Source #

Any quadruple of things is valid if all four of its elements are valid

Methods

validate :: (a, b, c, d) -> Validation Source #

isValid :: (a, b, c, d) -> Bool Source #

(Validity a, Validity b, Validity c, Validity d, Validity e) => Validity (a, b, c, d, e) Source #

Any quintuple of things is valid if all five of its elements are valid

Methods

validate :: (a, b, c, d, e) -> Validation Source #

isValid :: (a, b, c, d, e) -> Bool Source #

(Validity a, Validity b, Validity c, Validity d, Validity e, Validity f) => Validity (a, b, c, d, e, f) Source #

Any sextuple of things is valid if all six of its elements are valid

Methods

validate :: (a, b, c, d, e, f) -> Validation Source #

isValid :: (a, b, c, d, e, f) -> Bool Source #

Helper functions to define isValid

triviallyValid :: a -> Bool Source #

Declare any value to be valid.

triviallyValid a = seq a True

Helper functions to define validate

trivialValidation :: a -> Validation Source #

Declare any value to be valid in validation

trivialValidation a = seq a mempty

isValidByValidating :: Validity a => a -> Bool Source #

Implement isValid by using validate and checking that there are no reasons that the value is invalid.

check :: Bool -> String -> Validation Source #

Check that a given invariant holds.

The given string should describe the invariant, not the violation.

Example:

check (x < 5) "x is strictly smaller than 5"

instead of

check (x < 5) "x is greater than 5"

(<?!>) :: Validity a => a -> String -> Validation infixr 0 Source #

Infix operator for annotate

Example:

validate (a, b) =
    mconcat
        [ a <?!> "The first element of the tuple"
        , b <?!> "The second element of the tuple"
        ]

annotate :: Validity a => a -> String -> Validation Source #

Declare a sub-part as a necessary part for validation, and annotate it with a name.

Example:

validate (a, b) =
    mconcat
        [ annotate a "The first element of the tuple"
        , annotate b "The second element of the tuple"
        ]

(<?@>) :: Bool -> String -> Validation infixr 0 Source #

Infix operator for check

Example:

x < 5 <?@> "x is strictly smaller than 5"

validateByChecking :: Validity a => String -> a -> Validation Source #

Implement validate by using isValid and using the given string as the reason if the value is invalid.

validateByCheckingName :: Validity a => String -> a -> Validation Source #

Implement validate by using isValid and using the given name to define the reason if the value is invalid.

validateByCheckingName name = validateByChecking $ unwords ["The", name, "valid."]

validateByCheckingDefault :: Validity a => a -> Validation Source #

Implement validate by using isValid and using a default reason if the value is invalid.

validateByCheckingDefault = validateByChecking "The value is valid."

Utilities

Utilities for validity checking

isInvalid :: Validity a => a -> Bool Source #

Check whether isInvalid is not valid.

isInvalid = not . isValid

constructValid :: Validity a => a -> Maybe a Source #

Construct a valid element from an unchecked element

constructValidUnsafe :: (Show a, Validity a) => a -> a Source #

Construct a valid element from an unchecked element, throwing error on invalid elements.

Utilities for validation

checkValidity :: Validity a => a -> Either [ValidationChain] a Source #

validate a given value.

This function returns either all the reasons why the given value is invalid, in the form of a list of ValidationChains, or it returns Right with the input value, as evidence that it is valid.

Note: You map want to use prettyValidation instead, if you want to display these ValidationChains to a user.

prettyValidation :: Validity a => a -> Either String a Source #

validate a given value, and return a nice error if the value is invalid.

Re-exports

class Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

mconcat :: [a] -> a #

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid Validation # 
Monoid [a] 

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a) 

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a) 

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a) 

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b) 

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #