validity-0.3.0.4: Validity typeclass

Safe HaskellSafe
LanguageHaskell2010

Data.Validity

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 Numeric.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
    isValid (Prime n) = isPrime n

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

Minimal complete definition

isValid

Methods

isValid :: a -> Bool Source #

Check whether a given value is a valid value.

Instances

Validity Bool Source #

Trivially valid

Methods

isValid :: Bool -> Bool Source #

Validity Char Source #

Trivially valid

Methods

isValid :: Char -> Bool Source #

Validity Double Source #

NOT trivially valid:

  • NaN is not valid.
  • Infinite values are not valid.

Methods

isValid :: Double -> Bool Source #

Validity Float Source #

NOT trivially valid:

  • NaN is not valid.
  • Infinite values are not valid.

Methods

isValid :: Float -> Bool Source #

Validity Int Source #

Trivially valid

Methods

isValid :: Int -> Bool Source #

Validity Integer Source #

Trivially valid

Methods

isValid :: Integer -> Bool Source #

Validity Ordering Source #

Trivially valid

Validity Word Source #

Trivially valid

Methods

isValid :: Word -> Bool Source #

Validity () Source #

Trivially valid

Methods

isValid :: () -> Bool 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

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.

Methods

isValid :: Maybe a -> Bool Source #

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

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

Methods

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

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

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

Methods

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

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.