File: ExampleSpec.hs

package info (click to toggle)
haskell-doctest-parallel 0.3.1.1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 652 kB
  • sloc: haskell: 3,241; makefile: 6; ansic: 4
file content (163 lines) | stat: -rw-r--r-- 5,739 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
{-# LANGUAGE OverloadedStrings #-}
module Runner.ExampleSpec (main, spec) where

import           Prelude ()
import           Prelude.Compat

import           Data.String
import           Test.Hspec
import           Test.Hspec.Core.QuickCheck (modifyMaxSize)
import           Test.QuickCheck

import           Test.DocTest.Internal.Parse
import           Test.DocTest.Internal.Runner.Example

main :: IO ()
main = hspec spec

data Line = PlainLine String | WildCardLines [String]
  deriving (Show, Eq)

instance Arbitrary Line where
    arbitrary = frequency [ (2, PlainLine <$> arbitrary)
                          , (1, WildCardLines . getNonEmpty <$> arbitrary)
                          ]

lineToExpected :: [Line] -> ExpectedResult
lineToExpected = map $ \x -> case x of
                                 PlainLine str -> fromString str
                                 WildCardLines _ -> WildCardLine

lineToActual :: [Line] -> [String]
lineToActual = concatMap $ \x -> case x of
                               PlainLine str -> [str]
                               WildCardLines xs -> xs

spec :: Spec
spec = do
  describe "mkResult" $ do
    it "returns Equal when output matches" $ do
      property $ \xs -> do
        mkResult (map fromString xs) xs `shouldBe` Equal

    it "ignores trailing whitespace" $ do
      mkResult ["foo\t"] ["foo  "] `shouldBe` Equal

    context "with WildCardLine" $ do
      it "matches zero lines" $ do
        mkResult ["foo", WildCardLine, "bar"] ["foo", "bar"]
            `shouldBe` Equal

      it "matches first zero line" $ do
        mkResult [WildCardLine, "foo", "bar"] ["foo", "bar"]
            `shouldBe` Equal

      it "matches final zero line" $ do
        mkResult ["foo", "bar", WildCardLine] ["foo", "bar"]
            `shouldBe` Equal

      it "matches an arbitrary number of lines" $ do
        mkResult ["foo", WildCardLine, "bar"] ["foo", "baz", "bazoom", "bar"]
            `shouldBe` Equal

      -- See https://github.com/sol/doctest/issues/259
      modifyMaxSize (const 8) $
        it "matches an arbitrary number of lines (quickcheck)" $ do
          property $ \xs -> mkResult (lineToExpected xs) (lineToActual xs)
              `shouldBe` Equal

    context "with WildCardChunk" $ do
      it "matches an arbitrary line chunk" $ do
        mkResult [ExpectedLine ["foo", WildCardChunk, "bar"]] ["foo baz bar"]
            `shouldBe` Equal

      it "matches an arbitrary line chunk at end" $ do
        mkResult [ExpectedLine ["foo", WildCardChunk]] ["foo baz bar"]
            `shouldBe` Equal

      it "does not match at end" $ do
        mkResult [ExpectedLine [WildCardChunk, "baz"]] ["foo baz bar"]
            `shouldBe` NotEqual [
                 "expected: ...baz"
               , " but got: foo baz bar"
               , "                 ^"
               ]

      it "does not match at start" $ do
        mkResult [ExpectedLine ["fuu", WildCardChunk]] ["foo baz bar"]
            `shouldBe` NotEqual [
                 "expected: fuu..."
               , " but got: foo baz bar"
               , "           ^"
               ]

    context "when output does not match" $ do
      it "constructs failure message" $ do
        mkResult ["foo"] ["bar"] `shouldBe` NotEqual [
            "expected: foo"
          , " but got: bar"
          , "          ^"
          ]

      it "constructs failure message for multi-line output" $ do
        mkResult ["foo", "bar"] ["foo", "baz"] `shouldBe` NotEqual [
            "expected: foo"
          , "          bar"
          , " but got: foo"
          , "          baz"
          , "            ^"
          ]

      context "when any output line contains \"unsafe\" characters" $ do
        it "uses show to format output lines" $ do
          mkResult ["foo\160bar"] ["foo bar"] `shouldBe` NotEqual [
              "expected: foo\\160bar"
            , " but got: foo bar"
            , "             ^"
            ]

      it "insert caret after last matching character on different lengths" $ do
        mkResult ["foo"] ["fo"] `shouldBe` NotEqual [
            "expected: foo"
          , " but got: fo"
          , "            ^"
          ]

      it "insert caret after mismatching line for multi-line output" $ do
        mkResult ["foo", "bar", "bat"] ["foo", "baz", "bax"] `shouldBe` NotEqual [
            "expected: foo"
          , "          bar"
          , "          bat"
          , " but got: foo"
          , "          baz"
          , "            ^"
          , "          bax"
          ]

      it "insert caret after mismatching line with the longest match for multi-line wildcard pattern" $ do
        mkResult ["foo", WildCardLine, "bar", "bat"] ["foo", "xxx", "yyy", "baz", "bxx"] `shouldBe` NotEqual [
            "expected: foo"
          , "          ..."
          , "          bar"
          , "          bat"
          , " but got: foo"
          , "          xxx"
          , "          yyy"
          , "          baz"
          , "            ^"
          , "          bxx"
          ]

      it "insert caret after longest match for wildcard" $ do
        mkResult [ExpectedLine ["foo ", WildCardChunk, " bar bat"]] ["foo xxx yyy baz bxx"] `shouldBe` NotEqual [
            "expected: foo ... bar bat"
          , " but got: foo xxx yyy baz bxx"
          , "                        ^"
          ]

      it "show expanded pattern for long matches" $ do
        mkResult [ExpectedLine ["foo ", WildCardChunk, " bar bat"]] ["foo 123456789 123456789 xxx yyy baz bxx"] `shouldBe` NotEqual [
            "expected: foo ... bar bat"
          , " but got: foo 123456789 123456789 xxx yyy baz bxx"
          , "          foo ........................... ba^"
          ]