hspec-expectations-lens-0.4.0: Hspec expectations for the lens stuff

Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Hspec.Expectations.Lens

Contents

Description

Hspec expectations for the lens stuff

Synopsis

Expectations

shouldHave :: Show s => s -> Getting Any s a -> Expectation infixl 1 Source

s `shouldHave` l sets the expectation that Fold l has non-zero number of targets in the structure s

s `shouldBe` t ≡ s `shouldHave` only t
shouldHave :: Show s => s -> Getter     s a -> Expectation
shouldHave :: Show s => s -> Fold       s a -> Expectation
shouldHave :: Show s => s -> Iso'       s a -> Expectation
shouldHave :: Show s => s -> Lens'      s a -> Expectation
shouldHave :: Show s => s -> Traversal' s a -> Expectation
shouldHave :: Show s => s -> Prism'     s a -> Expectation

shouldNotHave :: Show s => s -> Getting All s a -> Expectation infixl 1 Source

s `shouldNotHave` l sets the expectation that Fold l has exactly zero targets in the structue s

shouldNotHave :: Show s => s -> Getter     s a -> Expectation
shouldNotHave :: Show s => s -> Fold       s a -> Expectation
shouldNotHave :: Show s => s -> Iso'       s a -> Expectation
shouldNotHave :: Show s => s -> Lens'      s a -> Expectation
shouldNotHave :: Show s => s -> Traversal' s a -> Expectation
shouldNotHave :: Show s => s -> Prism'     s a -> Expectation

shouldView :: (Show s, Show a, Eq a) => s -> a -> Getting a s a -> Expectation infixl 1 Source

s `shouldView` t `through` l sets the expectation that you can see target t in the structure s though a Getter l

shouldView ::           (Show s, Show a, Eq a) => s -> a -> Getter     s a -> Expectation
shouldView :: (Monoid m, Show s, Show a, Eq a) => s -> a -> Fold       s m -> Expectation
shouldView ::           (Show s, Show a, Eq a) => s -> a -> Iso'       s a -> Expectation
shouldView ::           (Show s, Show a, Eq a) => s -> a -> Lens'      s a -> Expectation
shouldView :: (Monoid m, Show s, Show a, Eq a) => s -> a -> Traversal' s m -> Expectation
shouldView :: (Monoid m, Show s, Show a, Eq a) => s -> a -> Prism'     s m -> Expectation

shouldPreview :: (Show s, Show a, Eq a) => s -> a -> Getting (First a) s a -> Expectation infixl 1 Source

s `shouldPreview` t `through` l sets the expectation that you y is the first target of the Fold l in s

shouldPreview :: (Show s, Show a, Eq a) => s -> a -> Getter     s a -> Expectation
shouldPreview :: (Show s, Show a, Eq a) => s -> a -> Fold       s a -> Expectation
shouldPreview :: (Show s, Show a, Eq a) => s -> a -> Lens'      s a -> Expectation
shouldPreview :: (Show s, Show a, Eq a) => s -> a -> Iso'       s a -> Expectation
shouldPreview :: (Show s, Show a, Eq a) => s -> a -> Traversal' s a -> Expectation
shouldPreview :: (Show s, Show a, Eq a) => s -> a -> Prism'     s a -> Expectation

shouldList :: (Show s, Show a, Eq a) => s -> [a] -> Getting (Endo [a]) s a -> Expectation infixl 1 Source

s `shouldList` ts `through` l sets the expectation that ts is a list of the Fold l targets in x

shouldList :: (Show s, Show a, Eq a) => s -> [a] -> Getter     s a -> Expectation
shouldList :: (Show s, Show a, Eq a) => s -> [a] -> Fold       s a -> Expectation
shouldList :: (Show s, Show a, Eq a) => s -> [a] -> Lens'      s a -> Expectation
shouldList :: (Show s, Show a, Eq a) => s -> [a] -> Iso'       s a -> Expectation
shouldList :: (Show s, Show a, Eq a) => s -> [a] -> Traversal' s a -> Expectation
shouldList :: (Show s, Show a, Eq a) => s -> [a] -> Prism'     s a -> Expectation

shouldThrow :: IO a -> Getting (First b) SomeException b -> Expectation infixl 1 Source

a `shouldThrow` l sets the expectation that a throws an exception that Fold l can catch

Test.Hspec exports shouldThrow too; it only allows e -> Bool selectors, which is less general and often less convenient

shouldThrow :: IO a -> Getter     SomeException b -> Expectation
shouldThrow :: IO a -> Fold       SomeException b -> Expectation
shouldThrow :: IO a -> Lens'      SomeException b -> Expectation
shouldThrow :: IO a -> Iso'       SomeException b -> Expectation
shouldThrow :: IO a -> Traversal' SomeException b -> Expectation
shouldThrow :: IO a -> Prism'     SomeException b -> Expectation

through :: a -> a infixl 1 Source

through fights parentheses

through ≡ id
through :: Int -> Int
through :: Char -> Char