Safe Haskell | None |
---|---|
Language | Haskell2010 |
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) = check (isPrime n) "The 'Int' is prime."
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
- class Validity a where
- validate :: a -> Validation
- trivialValidation :: a -> Validation
- genericValidate :: (Generic a, GValidity (Rep a)) => a -> Validation
- check :: Bool -> String -> Validation
- declare :: String -> Bool -> Validation
- annotate :: Validity a => a -> String -> Validation
- delve :: Validity a => String -> a -> Validation
- decorate :: String -> Validation -> Validation
- decorateList :: [a] -> (a -> Validation) -> Validation
- invalid :: String -> Validation
- valid :: Validation
- validateCharNotUtf16SurrogateCodePoint :: Char -> Validation
- isUtf16SurrogateCodePoint :: Char -> Bool
- validateCharNotLineSeparator :: Char -> Validation
- isLineSeparator :: Char -> Bool
- validateStringSingleLine :: String -> Validation
- isSingleLine :: String -> Bool
- validateNotNaN :: RealFloat a => a -> Validation
- validateNotInfinite :: RealFloat a => a -> Validation
- validateRatioNotNaN :: Integral a => Ratio a -> Validation
- validateRatioNotInfinite :: Integral a => Ratio a -> Validation
- validateRatioNormalised :: Integral a => Ratio a -> Validation
- isValid :: Validity a => a -> Bool
- isInvalid :: Validity a => a -> Bool
- constructValid :: Validity a => a -> Maybe a
- constructValidUnsafe :: (Show a, Validity a) => a -> a
- newtype Validation = Validation {}
- data ValidationChain
- checkValidity :: Validity a => a -> Either [ValidationChain] a
- validationIsValid :: Validation -> Bool
- prettyValidate :: Validity a => a -> Either String a
- prettyValidation :: Validation -> Maybe String
- class Semigroup a => Monoid a where
- class Semigroup a where
- (<>) :: a -> a -> a
Documentation
class Validity a where Source #
A class of types that have additional invariants defined upon them
Nothing
validate :: a -> Validation Source #
Instances
Validity Bool Source # | Trivially valid |
Defined in Data.Validity validate :: Bool -> Validation Source # | |
Validity Char Source # | Trivially valid |
Defined in Data.Validity validate :: Char -> Validation Source # | |
Validity Double Source # | Trivially valid: |
Defined in Data.Validity validate :: Double -> Validation Source # | |
Validity Float Source # | Trivially valid: |
Defined in Data.Validity validate :: Float -> Validation Source # | |
Validity Int Source # | Trivially valid |
Defined in Data.Validity validate :: Int -> Validation Source # | |
Validity Int8 Source # | NOT trivially valid on GHC because small number types are represented using a 64bit structure underneath. |
Defined in Data.Validity validate :: Int8 -> Validation Source # | |
Validity Int16 Source # | NOT trivially valid on GHC because small number types are represented using a 64bit structure underneath. |
Defined in Data.Validity validate :: Int16 -> Validation Source # | |
Validity Int32 Source # | NOT trivially valid on GHC because small number types are represented using a 64bit structure underneath. |
Defined in Data.Validity validate :: Int32 -> Validation Source # | |
Validity Int64 Source # | Trivially valid |
Defined in Data.Validity validate :: Int64 -> Validation Source # | |
Validity Integer Source # | Trivially valid Integer is not trivially valid under the hood, but instantiating
|
Defined in Data.Validity validate :: Integer -> Validation Source # | |
Validity Natural Source # | Valid according to |
Defined in Data.Validity validate :: Natural -> Validation Source # | |
Validity Ordering Source # | Trivially valid |
Defined in Data.Validity validate :: Ordering -> Validation Source # | |
Validity Word Source # | Trivially valid |
Defined in Data.Validity validate :: Word -> Validation Source # | |
Validity Word8 Source # | NOT trivially valid on GHC because small number types are represented using a 64bit structure underneath. |
Defined in Data.Validity validate :: Word8 -> Validation Source # | |
Validity Word16 Source # | NOT trivially valid on GHC because small number types are represented using a 64bit structure underneath. |
Defined in Data.Validity validate :: Word16 -> Validation Source # | |
Validity Word32 Source # | NOT trivially valid on GHC because small number types are represented using a 64bit structure underneath. |
Defined in Data.Validity validate :: Word32 -> Validation Source # | |
Validity Word64 Source # | Trivially valid |
Defined in Data.Validity validate :: Word64 -> Validation Source # | |
Validity () Source # | Trivially valid |
Defined in Data.Validity validate :: () -> Validation Source # | |
Validity ValidationChain Source # | |
Defined in Data.Validity validate :: ValidationChain -> Validation 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 |
Defined in Data.Validity validate :: [a] -> Validation 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 |
Defined in Data.Validity validate :: Maybe a -> Validation Source # | |
(Validity a, Ord a, Num a, Integral a) => Validity (Ratio a) Source # | Valid if the contained numbers are valid and the denominator is strictly positive. |
Defined in Data.Validity validate :: Ratio a -> Validation Source # | |
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. |
Defined in Data.Validity validate :: NonEmpty a -> Validation Source # | |
(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. |
Defined in Data.Validity validate :: Either a b -> Validation Source # | |
(Validity a, Validity b) => Validity (a, b) Source # | Any tuple of things is valid if both of its elements are valid |
Defined in Data.Validity validate :: (a, b) -> Validation Source # | |
HasResolution a => Validity (Fixed a) Source # | Valid according to the contained |
Defined in Data.Validity validate :: Fixed a -> Validation 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 |
Defined in Data.Validity validate :: (a, b, c) -> Validation 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 |
Defined in Data.Validity validate :: (a, b, c, d) -> Validation 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 |
Defined in Data.Validity validate :: (a, b, c, d, e) -> Validation 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 |
Defined in Data.Validity validate :: (a, b, c, d, e, f) -> Validation Source # |
Helper functions to define validate
trivialValidation :: a -> Validation Source #
Declare any value to be valid in validation
trivialValidation a = seq a mempty
genericValidate :: (Generic a, GValidity (Rep a)) => a -> Validation Source #
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"
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" ]
decorate :: String -> Validation -> Validation Source #
Decorate a validation with a location
decorateList :: [a] -> (a -> Validation) -> Validation Source #
Decorate a piecewise validation of a list with their location in the list
invalid :: String -> Validation Source #
Construct a trivially invalid Validation
Example:
data Wrong = Wrong | Fine deriving (Show, Eq) instance Validity Wrong where validate w = case w of Wrong -> invalid "Wrong" Fine -> valid
valid :: Validation Source #
Helpers for specific types
Char
isUtf16SurrogateCodePoint :: Char -> Bool Source #
isLineSeparator :: Char -> Bool Source #
isSingleLine :: String -> Bool Source #
RealFloat (Double)
validateNotNaN :: RealFloat a => a -> Validation Source #
validateNotInfinite :: RealFloat a => a -> Validation Source #
Ratio
validateRatioNotNaN :: Integral a => Ratio a -> Validation Source #
validateRatioNotInfinite :: Integral a => Ratio a -> Validation Source #
validateRatioNormalised :: Integral a => Ratio a -> Validation Source #
Utilities
Utilities for validity checking
isInvalid :: Validity a => a -> Bool Source #
Check whether a value 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
newtype Validation Source #
The result of validating a value.
mempty
means the value was valid.
This type intentionally doesn't have a Validity
instance to make sure
you can never accidentally use annotate
or delve
twice.
Instances
data ValidationChain Source #
Instances
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 ValidationChain
s, or it returns Right
with the
input value, as evidence that it is valid.
Note: You may want to use prettyValidation
instead, if you want to
display these ValidationChain
s to a user.
validationIsValid :: Validation -> Bool Source #
Check if a Validation
concerns a valid value.
prettyValidate :: Validity a => a -> Either String a Source #
Validate a given value
This function will return a nice error if the value is invalid.
It will return the original value in Right
if it was valid,
as evidence that it has been validated.
prettyValidation :: Validation -> Maybe String Source #
Render a Validation
in a somewhat pretty way.
This function will return Nothing
if the Validation
concerned a valid value.
Re-exports
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:
- Right identity
x
<>
mempty
= x- Left identity
mempty
<>
x = x- Associativity
x
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)- Concatenation
mconcat
=foldr
(<>
)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 newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Identity of mappend
>>>
"Hello world" <> mempty
"Hello world"
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
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.
>>>
mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"
Instances
Monoid Ordering | Since: base-2.1 |
Monoid () | Since: base-2.1 |
Monoid All | Since: base-2.1 |
Monoid Any | Since: base-2.1 |
Monoid Validation Source # | |
Defined in Data.Validity mempty :: Validation # mappend :: Validation -> Validation -> Validation # mconcat :: [Validation] -> Validation # | |
Monoid [a] | Since: base-2.1 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
Monoid p => Monoid (Par1 p) | Since: base-4.12.0.0 |
Monoid a => Monoid (Identity a) | Since: base-4.9.0.0 |
Monoid (First a) | Since: base-2.1 |
Monoid (Last a) | Since: base-2.1 |
Monoid a => Monoid (Dual a) | Since: base-2.1 |
Monoid (Endo a) | Since: base-2.1 |
Num a => Monoid (Sum a) | Since: base-2.1 |
Num a => Monoid (Product a) | Since: base-2.1 |
Monoid a => Monoid (Down a) | Since: base-4.11.0.0 |
Monoid b => Monoid (a -> b) | Since: base-2.1 |
Monoid (U1 p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Monoid (f p) => Monoid (Rec1 f p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 |
Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
Monoid c => Monoid (K1 i c p) | Since: base-4.12.0.0 |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: base-2.1 |
Monoid (f p) => Monoid (M1 i c f p) | Since: base-4.12.0.0 |
Monoid (f (g p)) => Monoid ((f :.: g) p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: base-2.1 |
The class of semigroups (types with an associative binary operation).
Instances should satisfy the following:
Since: base-4.9.0.0
Instances
Semigroup Ordering | Since: base-4.9.0.0 |
Semigroup () | Since: base-4.9.0.0 |
Semigroup All | Since: base-4.9.0.0 |
Semigroup Any | Since: base-4.9.0.0 |
Semigroup Validation Source # | |
Defined in Data.Validity (<>) :: Validation -> Validation -> Validation # sconcat :: NonEmpty Validation -> Validation # stimes :: Integral b => b -> Validation -> Validation # | |
Semigroup [a] | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (IO a) | Since: base-4.10.0.0 |
Semigroup p => Semigroup (Par1 p) | Since: base-4.12.0.0 |
Semigroup a => Semigroup (Identity a) | Since: base-4.9.0.0 |
Semigroup (First a) | Since: base-4.9.0.0 |
Semigroup (Last a) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 |
Semigroup (Endo a) | Since: base-4.9.0.0 |
Num a => Semigroup (Sum a) | Since: base-4.9.0.0 |
Num a => Semigroup (Product a) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Down a) | Since: base-4.11.0.0 |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
Semigroup b => Semigroup (a -> b) | Since: base-4.9.0.0 |
Semigroup (Either a b) | Since: base-4.9.0.0 |
Semigroup (V1 p) | Since: base-4.12.0.0 |
Semigroup (U1 p) | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b) => Semigroup (a, b) | Since: base-4.9.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Semigroup (f p) => Semigroup (Rec1 f p) | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Semigroup a) => Semigroup (Ap f a) | Since: base-4.12.0.0 |
Alternative f => Semigroup (Alt f a) | Since: base-4.9.0.0 |
Semigroup c => Semigroup (K1 i c p) | Since: base-4.12.0.0 |
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) | Since: base-4.9.0.0 |
Semigroup (f p) => Semigroup (M1 i c f p) | Since: base-4.12.0.0 |
Semigroup (f (g p)) => Semigroup ((f :.: g) p) | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) | Since: base-4.9.0.0 |