File: RunSpec.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 (93 lines) | stat: -rw-r--r-- 3,360 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
{-# LANGUAGE CPP #-}
module RunSpec (main, spec) where

import           Prelude ()
import           Prelude.Compat

import           Test.Hspec
import           System.Exit

import qualified Control.Exception as E
import           Data.List.Compat

import           System.IO.Silently
import           System.IO (stderr)
import qualified Test.DocTest as DocTest
import           Test.DocTest.Helpers (findCabalPackage, extractSpecificCabalLibrary)
import qualified Test.DocTest.Internal.Options as Options

doctest :: HasCallStack => [String] -> IO ()
doctest args = do
  pkg <- findCabalPackage "doctest-parallel"
  lib <- extractSpecificCabalLibrary (Just "spectests-modules") pkg
  DocTest.mainFromLibrary lib args

main :: IO ()
main = hspec spec

spec :: Spec
spec = do
  describe "doctest" $ do
    it "exits with ExitFailure if at least one test case fails" $ do
      hSilence [stderr] (doctest ["Failing.Foo"]) `shouldThrow` (== ExitFailure 1)

    it "prints help on --help" $ do
      (r, ()) <- capture (doctest ["--help"])
      r `shouldBe` Options.usage

    it "prints version on --version" $ do
      (r, ()) <- capture (doctest ["--version"])
      lines r `shouldSatisfy` any (isPrefixOf "doctest version ")

    it "prints error message on invalid option" $ do
      (r, e) <- hCapture [stderr] . E.try $ doctest ["--foo", "test/integration/test-options/Foo.hs"]
      e `shouldBe` Left (ExitFailure 1)
      r `shouldBe` unlines [
          "doctest: Unknown command line argument: --foo"
        , "Try `doctest --help' for more information."
        ]

    -- The commented tests fail, but only because `doctest-parallel` prints
    -- absolute paths.
    --
    -- TODO: Fix

    -- it "prints verbose description of a specification" $ do
    --   (r, ()) <- hCapture [stderr] $ doctest ["--verbose", "TestSimple.Fib"]
    --   r `shouldBe` unlines [
    --       "### Started execution at test/integration/TestSimple/Fib.hs:5."
    --     , "### example:"
    --     , "fib 10"
    --     , "### Successful `test/integration/TestSimple/Fib.hs:5'!"
    --     , ""
    --     , "# Final summary:"
    --     , "Examples: 1  Tried: 1  Errors: 0  Unexpected output: 0"
    --     ]

    -- it "prints verbose description of a property" $ do
    --   (r, ()) <- hCapture [stderr] $ doctest ["--verbose", "PropertyBool.Foo"]
    --   r `shouldBe` unlines [
    --       "### Started execution at test/integration/PropertyBool/Foo.hs:4."
    --     , "### property:"
    --     , "True"
    --     , "### Successful `test/integration/PropertyBool/Foo.hs:4'!"
    --     , ""
    --     , "# Final summary:"
    --     , "Examples: 1  Tried: 1  Errors: 0  Unexpected output: 0"
    --     ]

    -- it "prints verbose error" $ do
    --   (r, e) <- hCapture [stderr] . E.try $ doctest ["--verbose", "Failing.Foo"]
    --   e `shouldBe` Left (ExitFailure 1)
    --   r `shouldBe` unlines [
    --           "### Started execution at test/integration/Failing/Foo.hs:5."
    --         , "### example:"
    --         , "23"
    --         , "test/integration/Failing/Foo.hs:5: failure in expression `23'"
    --         , "expected: 42"
    --         , " but got: 23"
    --         , "          ^"
    --         , ""
    --         , "# Final summary:"
    --         , "Examples: 1  Tried: 1  Errors: 0  Unexpected output: 1"
    --     ]