{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} -- | Standard test `Spec`s for optics -- -- You will need @TypeApplications@ to use these. module Test.Validity.Optics ( lensSpecOnValid , lensSpec , lensSpecOnArbitrary , lensSpecOnGen , lensLaw1 , lensLaw2 , lensLaw3 ) where import Lens.Micro import Lens.Micro.Extras import Data.GenValidity import Test.Hspec import Test.QuickCheck import Test.Validity.Utils -- | Standard test spec for properties lenses for valid values -- -- Example usage: -- -- lensSpecOnValid ((_2) :: Lens (Double, Double) (Double, Double) Double Double) lensSpecOnValid :: forall s b. (Show b, Eq b, GenValid b, Show s, Eq s, GenValid s) => Lens s s b b -> Spec lensSpecOnValid l = lensSpecOnGen l (genValid @b) "valid values" shrinkValid (genValid @s) "valid values" shrinkValid -- | Standard test spec for properties lenses for unchecked values -- -- Example usage: -- -- lensSpec ((_2) :: Lens (Int, Int) (Int, Int) Int Int) lensSpec :: forall s b. (Show b, Eq b, GenUnchecked b, Show s, Eq s, GenUnchecked s) => Lens s s b b -> Spec lensSpec l = lensSpecOnGen l (genUnchecked @b) "unchecked values" shrinkUnchecked (genUnchecked @s) "unchecked values" shrinkUnchecked -- | Standard test spec for properties lenses for arbitrary values -- -- Example usage: -- -- lensSpecOnArbitrary ((_2) :: Lens (Double, Double) (Double, Double) Double Double) lensSpecOnArbitrary :: forall s b. (Show b, Eq b, Arbitrary b, Show s, Eq s, Arbitrary s) => Lens s s b b -> Spec lensSpecOnArbitrary l = lensSpecOnGen l (arbitrary @b) "arbitrary values" shrink (arbitrary @s) "arbitrary values" shrink -- | Standard test spec for properties lenses for values generated by given generators -- -- Example usage: -- -- > lensSpecOnGen -- > ((_2) :: Lens (Double, Double) (Double, Double) Double Double) -- > (abs <$> genValid) -- > "positive valid doubles" -- > (filter (0.0 >=) . shrinkValid) -- > ((,) <$> (negate . abs <$> genValid) <*> (negate . abs <$> genValid)) -- > "tuples of negative valid doubles" -- > (const []) lensSpecOnGen :: (Show b, Eq b, Show s, Eq s) => Lens s s b b -> Gen b -> String -> (b -> [b]) -> Gen s -> String -> (s -> [s]) -> Spec lensSpecOnGen l genB genBName shrinkB genS genSName shrinkS = do parallel $ do it (unwords ["satisfies the first lens law for", genBName, "and", genSName]) $ lensLaw1 l genB shrinkB genS shrinkS it (unwords ["satisfies the second lens law for", genSName]) $ lensLaw2 l genS shrinkS it (unwords ["satisfies the third lens law for", genBName, "and", genSName]) $ lensLaw3 l genB shrinkB genS shrinkS -- | A property combinator for the first lens law: -- -- > view l (set l v s) ≡ v -- -- prop> lensLaw1 ((_2) :: Lens (Double, Double) (Double, Double) Double Double) genValid shrinkValid genValid shrinkValid lensLaw1 :: (Show b, Eq b, Show s) => Lens s s b b -> Gen b -> (b -> [b]) -> Gen s -> (s -> [s]) -> Property lensLaw1 l genB shrinkB genS shrinkS = forAllShrink genB shrinkB $ \b -> forAllShrink genS shrinkS $ \s -> view l (set l b s) `shouldBe` b -- | A property combinator for the second lens law: -- -- > set l (view l s) s ≡ s -- -- prop> lensLaw2 ((_2) :: Lens (Double, Double) (Double, Double) Double Double) genValid shrinkValid lensLaw2 :: (Show s, Eq s) => Lens s s b b -> Gen s -> (s -> [s]) -> Property lensLaw2 l genS shrinkS = forAllShrink genS shrinkS $ \s -> set l (view l s) s `shouldBe` s -- | A property combinator for the third lens law: -- -- > set l v' (set l v s) ≡ set l v' s -- -- prop> lensLaw3 ((_2) :: Lens (Double, Double) (Double, Double) Double Double) genValid shrinkValid genValid shrinkValid lensLaw3 :: (Show b, Eq b, Show s, Eq s) => Lens s s a b -> Gen b -> (b -> [b]) -> Gen s -> (s -> [s]) -> Property lensLaw3 l genB shrinkB genS shrinkS = forAllShrink genB shrinkB $ \b -> forAllShrink genB shrinkB $ \b' -> forAllShrink genS shrinkS $ \s -> set l b' (set l b s) `shouldBe` set l b' s