genvalidity-sydtest-lens-0.0.0.0: Standard spec's for lens for sydtest
Safe HaskellNone
LanguageHaskell2010

Test.Syd.Validity.Lens

Description

Standard test Specs for optics

Synopsis

Documentation

lensSpecOnValid :: forall s b. (Show b, Eq b, GenValid b, Show s, Eq s, GenValid s) => Lens s s b b -> Spec Source #

Standard test spec for properties lenses for valid values

Example usage:

lensSpecOnValid ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational)

lensSpec :: forall s b. (Show b, Eq b, GenUnchecked b, Validity b, Show s, Eq s, GenUnchecked s, Validity s) => Lens s s b b -> Spec Source #

Standard test spec for properties lenses for unchecked values

Example usage:

lensSpec ((_2) :: Lens (Int, Int) (Int, Int) Int Int)

lensSpecOnArbitrary :: forall s b. (Show b, Eq b, Arbitrary b, Validity b, Show s, Eq s, Arbitrary s, Validity s) => Lens s s b b -> Spec Source #

Standard test spec for properties lenses for arbitrary values

Example usage:

lensSpecOnArbitrary ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational)

lensSpecOnGen :: (Show b, Eq b, Validity b, Show s, Eq s, Validity s) => Lens s s b b -> Gen b -> String -> (b -> [b]) -> Gen s -> String -> (s -> [s]) -> Spec Source #

Standard test spec for properties lenses for values generated by given generators

Example usage:

lensSpecOnGen
     ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational)
     (abs <$> genValid)
     "positive valid doubles"
     (filter (0.0 >=) . shrinkValid)
     ((,) <$> (negate . abs <$> genValid) <*> (negate . abs <$> genValid))
     "tuples of negative valid doubles"
     (const [])

lensLaw1 :: (Show b, Eq b, Show s) => Lens s s b b -> Gen b -> (b -> [b]) -> Gen s -> (s -> [s]) -> Property Source #

A property combinator for the first lens law:

view l (set l v s)  ≡ v

Example usage:

lensLaw1 ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational) genValid shrinkValid genValid shrinkValid

lensLaw2 :: (Show s, Eq s) => Lens s s b b -> Gen s -> (s -> [s]) -> Property Source #

A property combinator for the second lens law:

set l (view l s) s  ≡ s

Example usage:

lensLaw2 ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational) genValid shrinkValid

lensLaw3 :: (Show b, Show s, Eq s) => Lens s s a b -> Gen b -> (b -> [b]) -> Gen s -> (s -> [s]) -> Property Source #

A property combinator for the third lens law:

set l v' (set l v s) ≡ set l v' s

Example usage:

lensLaw3 ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational) genValid shrinkValid genValid shrinkValid

lensGettingProducesValidOnValid :: (Show s, GenValid s, Show b, GenValid b) => Lens s s b b -> Property Source #

A property combinator to test whether getting values via a lens on valid values produces valid values.

Example Usage:

lensGettingProducesValidOnValid ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational)

lensGettingProducesValid :: (Show s, GenUnchecked s, Show b, Validity b) => Lens s s b b -> Property Source #

A property combinator to test whether getting values via a lens on unchecked values produces valid values.

Example Usage:

lensGettingProducesValid ((_2) :: Lens (Int, Int) (Int, Int) Int Int)

lensGettingProducesValidOnArbitrary :: (Show s, Arbitrary s, Show b, Validity b) => Lens s s b b -> Property Source #

A property combinator to test whether getting values via a lens on arbitrary values produces valid values.

Example Usage:

lensGettingProducesValidOnArbitrary ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational)

lensGettingProducesValidOnGen :: (Validity b, Show b, Show s) => Lens s s b b -> Gen s -> (s -> [s]) -> Property Source #

A property combinator to test whether getting values generated by given a generator via a lens on values generated by a given generator produces valid values.

isValid (view l s)

Example Usage:

lensGettingProducesValidOnGen ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational) genValid shrinkValid

lensSettingProducesValidOnValid :: (Show s, GenValid s, Show b, GenValid b, Show t, Validity t) => Lens s t a b -> Property Source #

A property combinator to test whether setting valid values via a lens on valid values produces valid values.

Example usage:

lensSettingProducesValidOnValid ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational)

lensSettingProducesValid :: (Show s, GenUnchecked s, Show b, GenUnchecked b, Show t, Validity t) => Lens s t a b -> Property Source #

A property combinator to test whether setting unchecked values via a lens on unchecked values produces valid values.

Example usage:

lensSettingProducesValid ((_2) :: Lens (Int, Int) (Int, Int) Int Int)

lensSettingProducesValidOnArbitrary :: (Show s, Arbitrary s, Show b, Arbitrary b, Show t, Validity t) => Lens s t a b -> Property Source #

A property combinator to test whether setting arbitrary values via a lens on arbitrary values produces valid values.

Example usage:

lensSettingProducesValidOnArbitrary ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational)

lensSettingProducesValidOnGen :: (Show s, Show b, Show t, Validity t) => Lens s t a b -> Gen b -> (b -> [b]) -> Gen s -> (s -> [s]) -> Property Source #

A property combinator to test whether setting values generated by given a generator via a lens on values generated by a given generator produces valid values.

isValid (set l b s)

Example usage:

lensSettingProducesValidOnGen ((_2) :: Lens (Rational, Rational) (Rational, Rational) Rational Rational) genValid shrinkValid genValid shrinkValid