Coder Social home page Coder Social logo

doctest's Introduction

Doctest: Test interactive Haskell examples

doctest is a tool that checks examples and properties in Haddock comments. It is similar in spirit to the popular Python module with the same name.

Getting started

Installation

doctest is available from Hackage. Install it with:

cabal update && cabal install doctest

Make sure that Cabal's bindir is on your PATH.

On Linux:

export PATH="$HOME/.cabal/bin:$PATH"

On Mac OS X:

export PATH="$HOME/Library/Haskell/bin:$PATH"

On Windows:

set PATH="%AppData%\cabal\bin\;%PATH%"

A basic example

Below is a small Haskell module. The module contains a Haddock comment with some examples of interaction. The examples demonstrate how the module is supposed to be used.

-- src/Fib.hs
module Fib where

-- | Compute Fibonacci numbers
--
-- Examples:
--
-- >>> fib 10
-- 55
--
-- >>> fib 5
-- 5
fib :: Int -> Int
fib 0 = 0
fib 1 = 1
fib n = fib (n - 1) + fib (n - 2)

(A comment line starting with >>> denotes an expression. All comment lines following an expression denote the result of that expression. Result is defined by what a REPL (e.g. ghci) prints to stdout and stderr when evaluating that expression.)

With doctest you can check whether the implementation satisfies the given examples:

doctest src/Fib.hs

Running doctest for a Cabal package

The easiest way to run doctest for a Cabal package is via cabal repl --with-ghc=doctest.

This doesn't make a big difference for a simple package, but in more involved situations cabal will make sure that all dependencies are available and it will pass any required GHC options to doctest.

A simple .cabal file for Fib looks like this:

-- fib.cabal
cabal-version: 1.12

name:           fib
version:        0.0.0
build-type:     Simple

library
  build-depends: base == 4.*
  hs-source-dirs: src
  exposed-modules: Fib
  default-language: Haskell2010

With a .cabal file in place, it is possible to run doctest via cabal repl:

$ cabal repl --with-ghc=doctest
...
Examples: 2  Tried: 2  Errors: 0  Failures: 0

Notes:

  • If you use properties you need to pass --build-depends=QuickCheck and --build-depends=template-haskell to cabal repl.

  • You likely want to reset the warning strategy for cabal repl with --repl-options='-w -Wdefault'.

  • doctest always uses the version of GHC it was compiled with. Reinstalling doctest with cabal install doctest --overwrite-policy=always before each invocation ensures that it uses the same version of GHC as is on the PATH.

  • Technically, cabal build is not necessary. cabal repl --with-ghc=doctest will build any dependencies as needed. However, it's more robust to run cabal build first (specifically it is not a good idea to build ghc-paths with --with-ghc=doctest).

So a more robust way to call doctest is as follows:

cabal install doctest --overwrite-policy=always && cabal build && cabal repl --build-depends=QuickCheck --build-depends=template-haskell --with-ghc=doctest --repl-options='-w -Wdefault'

(This is what you want to use on CI.)

Passing doctest options to cabal repl

You can pass doctest options like --fast, --preserve-it and --verbose to cabal repl via --repl-options.

Example:

$ cabal repl --with-ghc=doctest --repl-options=--verbose
### Started execution at src/Fib.hs:7.
### example:
fib 10
### Successful!

### Started execution at src/Fib.hs:10.
### example:
fib 5
### Successful!

# Final summary:
Examples: 2  Tried: 2  Errors: 0  Failures: 0

Writing examples and properties

Example groups

Examples from a single Haddock comment are grouped together and share the same scope. E.g. the following works:

-- |
-- >>> let x = 23
-- >>> x + 42
-- 65

If an example fails, subsequent examples from the same group are skipped. E.g. for

-- |
-- >>> let x = 23
-- >>> let n = x + y
-- >>> print n

print n is skipped, because let n = x + y fails (as y is not in scope).

A note on performance

By default, doctest calls :reload between each group to clear GHCi's scope of any local definitions. This ensures that previous examples cannot influence later ones. However, it can lead to performance penalties if you are using doctest in a project with many modules. One possible remedy is to pass the --fast flag to doctest, which disables calling :reload between groups. If doctests are running too slowly, you might consider using --fast. (With the caveat that the order in which groups appear now matters!)

However, note that due to a bug on GHC 8.2.1 or later, the performance of --fast suffers significantly when combined with the --preserve-it flag (which keeps the value of GHCi's it value between examples).

Setup code

You can put setup code in a named chunk with the name $setup. The setup code is run before each example group. If the setup code produces any errors/failures, all tests from that module are skipped.

Here is an example:

module Foo where

import Bar.Baz

-- $setup
-- >>> let x = 23 :: Int

-- |
-- >>> foo + x
-- 65
foo :: Int
foo = 42

Note that you should not place setup code inbetween the module header (module ... where) and import declarations. GHC will not be able to parse it (issue #167). It is best to place setup code right after import declarations, but due to its declarative nature you can place it anywhere inbetween top level declarations as well.

Multi-line input

GHCi supports commands which span multiple lines, and the same syntax works for doctest:

-- |
-- >>> :{
--  let
--    x = 1
--    y = 2
--  in x + y + multiline
-- :}
-- 6
multiline = 3

Note that >>> can be left off for the lines following the first: this is so that haddock does not strip leading whitespace. The expected output has whitespace stripped relative to the :}.

Some peculiarities on the ghci side mean that whitespace at the very start is lost. This breaks the example broken, since the x and y aren't aligned from ghci's perspective. A workaround is to avoid leading space, or add a newline such that the indentation does not matter:

{- | >>> :{
let x = 1
    y = 2
  in x + y + works
:}
6
-}
works = 3

{- | >>> :{
 let x = 1
     y = 2
  in x + y + broken
:}
3
-}
broken = 3

Multi-line output

If there are no blank lines in the output, multiple lines are handled automatically.

-- | >>> putStr "Hello\nWorld!"
-- Hello
-- World!

If however the output contains blank lines, they must be noted explicitly with <BLANKLINE>. For example,

import Data.List ( intercalate )

-- | Double-space a paragraph.
--
--   Examples:
--
--   >>> let s1 = "\"Every one of whom?\""
--   >>> let s2 = "\"Every one of whom do you think?\""
--   >>> let s3 = "\"I haven't any idea.\""
--   >>> let paragraph = unlines [s1,s2,s3]
--   >>> putStrLn $ doubleSpace paragraph
--   "Every one of whom?"
--   <BLANKLINE>
--   "Every one of whom do you think?"
--   <BLANKLINE>
--   "I haven't any idea."
--
doubleSpace :: String -> String
doubleSpace = (intercalate "\n\n") . lines

Matching arbitrary output

Any lines containing only three dots (...) will match one or more lines with arbitrary content. For instance,

-- |
-- >>> putStrLn "foo\nbar\nbaz"
-- foo
-- ...
-- baz

If a line contains three dots and additional content, the three dots will match anything within that line:

-- |
-- >>> putStrLn "foo bar baz"
-- foo ... baz

QuickCheck properties

Haddock has markup support for properties. Doctest can verify properties with QuickCheck. A simple property looks like this:

-- |
-- prop> \xs -> sort xs == (sort . sort) (xs :: [Int])

The lambda abstraction is optional and can be omitted:

-- |
-- prop> sort xs == (sort . sort) (xs :: [Int])

A complete example that uses setup code is below:

module Fib where

-- $setup
-- >>> import Control.Applicative
-- >>> import Test.QuickCheck
-- >>> newtype Small = Small Int deriving Show
-- >>> instance Arbitrary Small where arbitrary = Small . (`mod` 10) <$> arbitrary

-- | Compute Fibonacci numbers
--
-- The following property holds:
--
-- prop> \(Small n) -> fib n == fib (n + 2) - fib (n + 1)
fib :: Int -> Int
fib 0 = 0
fib 1 = 1
fib n = fib (n - 1) + fib (n - 2)

If you see an error like the following, ensure that QuickCheck is visible to doctest (e.g. by passing --build-depends=QuickCheck to cabal repl).

<interactive>:39:3:
    Not in scope: polyQuickCheck
    In the splice: $(polyQuickCheck (mkName "doctest_prop"))

<interactive>:39:3:
    GHC stage restriction:
      polyQuickCheck is used in a top-level splice or annotation,
      and must be imported, not defined locally
    In the expression: polyQuickCheck (mkName "doctest_prop")
    In the splice: $(polyQuickCheck (mkName "doctest_prop"))

Hiding examples from Haddock

You can put examples into named chunks, and not refer to them in the export list. That way they will not be part of the generated Haddock documentation, but Doctest will still find them.

-- $
-- >>> 1 + 1
-- 2

Using GHC extensions

There's two sets of GHC extensions involved when running Doctest:

  1. The set of GHC extensions that are active when compiling the module code (excluding the doctest examples). The easiest way to specify these extensions is through LANGUAGE pragmas in your source files.

  2. The set of GHC extensions that are active when executing the Doctest examples. (These are not influenced by the LANGUAGE pragmas in the file.) The recommended way to enable extensions for Doctest examples is to switch them on like this:

-- |
-- >>> :seti -XTupleSections
-- >>> fst' $ (1,) 2
-- 1
fst' :: (a, b) -> a
fst' = fst

Alternatively you can pass any GHC options to Doctest, e.g.:

doctest -XCPP Foo.hs

These options will affect both the loading of the module and the execution of the Doctest examples.

If you want to omit the information which language extensions are enabled from the Doctest examples you can use the method described in Hiding examples from Haddock, e.g.:

-- $
-- >>> :seti -XTupleSections

Limitations

  • Doctests only works on platforms that have support for GHC's --interactive mode (ghci).

  • Due to a GHC bug, running :set -XTemplateHaskell within ghci may unload any modules that were specified on the command-line.

    To address this doctest >= 0.19.0 does two things:

    1. Doctest always enables -XTemplateHaskell. So it is safe to use Template Haskell in examples without enabling the extension explicitly.
    2. Doctest filters out -XTemplateHaskell from single-line :set-statements. So it is still safe to include :set -XTemplateHaskell in examples for documentation purposes. It may just not work as intended in ghci due to that GHC bug.

    Doctest does not filter out -XTemplateHaskell from multi-line :set-statements. So if you e.g. use

    >>> :{
    :set -XTemplateHaskell
    :}
    

    then you are on your own.

    Note that all platforms that support --interactive also support -XTemplateHaskell. So this approach does not reduce Doctest's platform support.

  • Modules that are rejected by haddock will not work with doctest. This can mean that doctest fails on input that is accepted by GHC (e.g. #251).

  • Doctest works best with UTF-8. If your locale is e.g. LC_ALL=C, you may want to invoke doctest with LC_ALL=C.UTF-8.

Doctest in the wild

You can find real world examples of Doctest being used below:

Development

Discuss your ideas first, ideally by opening an issue on GitHub.

Add tests for new features, and make sure that the test suite passes with your changes.

cabal build --enable-tests && cabal exec -- cabal test --test-show-details=direct

Contributors

  • Adam Vogt
  • Alan Zimmerman
  • Alexander Bernauer
  • Alexandre Esteves
  • Anders Persson
  • Andreas Abel
  • Ankit Ahuja
  • Artyom Kazak
  • Edward Kmett
  • Gabor Greif
  • Hiroki Hattori
  • Ignat Insarov
  • Jens Petersen
  • Joachim Breitner
  • John Chee
  • João Cristóvão
  • Julian Arni
  • Kazu Yamamoto
  • Leon Schoorl
  • Levent Erkok
  • Luke Murphy
  • Matvey Aksenov
  • Michael Orlitzky
  • Michael Snoyman
  • Mitchell Rosen
  • Nick Smallbone
  • Nikos Baxevanis
  • Oleg Grenrus
  • quasicomputational
  • Ryan Scott
  • Sakari Jokinen
  • Simon Hengel
  • Sönke Hahn
  • Takano Akio
  • Tamar Christina
  • Veronika Romashkina

For up-to-date list, query

git shortlog -s

doctest's People

Contributors

aavogt avatar andreasabel avatar cheecheeo avatar decentral1se avatar eddiejessup avatar ekmett avatar g357r6kc avatar jcristovao avatar jkarni avatar juhp avatar kazu-yamamoto avatar kindaro avatar leonschoorl avatar leventerkok avatar mistuke avatar mitchellwrosen avatar moodmosaic avatar nick8325 avatar nomeata avatar orlitzky avatar phadej avatar quasicomputational avatar ryanglscott avatar sakari avatar snoyberg avatar soenkehahn avatar sol avatar supki avatar takano-akio avatar vrom911 avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

doctest's Issues

interaction between hint and doctest

Looks like issue #11 is back. I see in that thread that the root cause was in ghc, maybe I should report it there instead? Anyway, on to the actual bug report.

In a file called Main.hs:

import Test.DocTest
import Language.Haskell.Interpreter

-- |
-- >>> True
-- True
main :: IO ()
main = do
    _ <- runInterpreter $ interpret "()" (as :: ())
    doctest ["Main.hs"]
    return ()

The program fails with Main.hs: Too late for parseStaticFlags: call it before newSession. But there is an easy workaround: if I swap the calls to runInterpreter and doctest, I get Examples: 1 Tried: 1 Errors: 0 Failures: 0, as expected.

(By the way, doctest is my favorite testing framework ever! And it makes so much more sense to use that strategy in Haskell than in python.)

parseStaticFlags of GHC 7.7

Doctest complied with GHC 7.7 cannot handle >>> doctest <something>. This is one test case of "cabal doctests".

This is probably because the behavior of parseStaticFlags change. Reseting v_opt_C_ready explicitly passes the test. But this workaound is not proper, I believe.

Integration with test frameworks

It would be great if doctest could be easily run from existing test frameworks. Based on our email discussion[1], it sounds like the best way to do this would be to provide a function:

getDocTests :: [Flag] -> [FilePath] -> IO [Test]

I'm assuming that "Test" here would be from HUnit. Two additional features I would like to ask for are:

  • Automatically adding GHC options based on LANGUAGE pragmas on files.
  • Determining the [FilePath] argument based on the .cabal file.

Thanks

[1] http://www.haskell.org/pipermail/haskell-cafe/2011-April/090827.html

Run doctest against X.hs works, but against Y.hs, which runs against X.hs fails

This gist contains two files Link.hs and Person.hs. If I run doctest against Link.hs, the test passes just fine. However, if I run doctest against Person.hs, which then runs Link.hs, the test fails with a strange error message:

### Failure in ./Test/Link.hs:13: expression `fmap (unpickleDoc' xpLinkElem) . runLA xread $ "<link/>"'
expected: [Right Link]
but got: [Left "xpElem: got element name \"link\", but expected \"link\"\ncontext: element \"/\""]
Examples: 2 Tried: 2 Errors: 0 Failures: 1

Running with

  • ghc-7.6.3
  • hxt-9.3.1.1
  • doctest-0.9.9

Script to reproduce

#!/bin/sh

cabal sandbox init
cabal install hxt-9.3.1.1
cabal install doctest-0.9.9
mkdir Test
wget https://gist.github.com/tonymorris/7095376/raw/c2bb6d107ae97e52c89807877baa04db56153084/Link.hs -O Test/Link.hs -q
wget https://gist.github.com/tonymorris/7095376/raw/cbc4aa4bbbbca38979e18cb8620c5fb7748cc28b/Person.hs -O Test/Person.hs -q
ghc -e "fmap (unpickleDoc' xpLinkElem) . runLA xread $ \"<link/>\"" Test/Link.hs
ghc -e "fmap (unpickleDoc' xpLinkElem) . runLA xread $ \"<link/>\"" Test/Person.hs
ghc -e "fmap (unpickleDoc' xpAuthorElem) . runLA xread $ \"<author><link/></author>\"" Test/Person.hs
./.cabal-sandbox/bin/doctest Test/Link.hs
./.cabal-sandbox/bin/doctest Test/Person.hs

Please support newline as CR+LF environment

commit 37ef9a54c1cb0adaaa107ea4ce6d861b41d1b500
Author: Hiroki Hattori <[email protected]>
Date:   Sat Apr 28 13:23:10 2012 +0900

    Support newline as CR+LF

diff --git a/src/Parse.hs b/src/Parse.hs
index 27a32d7..fa11f4b 100644
--- a/src/Parse.hs
+++ b/src/Parse.hs
@@ -42,7 +42,7 @@ parseModule (Module name docs) = (Module name . map Example . filter (not . null

 -- | Extract all interactions from given Haddock documentation.
 parse :: Located String -> [Located Interaction]
-parse (Located loc input) = go $ zipWith Located (enumerate loc) (lines input)
+parse (Located loc input) = go $ zipWith Located (enumerate loc) (map (reverse . dropWhile ((==) '\r') . reverse) $ lines input)
   where
     isPrompt :: Located String -> Bool
     isPrompt = isPrefixOf ">>>" . dropWhile isSpace . unLoc

More operators from and an argument to QuickCheck?

Currently, Property.hs imports quickCheck and ==> only. I guess we need to consider what kind of functions/operators should be imported more.

Also, users might want to pass Args to quickCheckWith to increase the number of random tests.

What do you think?

A new version

Would you release the new version? I need it to build ghc-mod with GHC 7.7.

Add support for junit XML result output

I use test-framework's support for dumping test results into a junit-compatible XML file in my continuous integration setup.

Since doctest produces no output in this format, I have no handy stats on how many doctest tests I have. This would be very useful to have.

screen shot 2014-04-19 at 23 28 55

useUnicodeQuotes in GHC 7.7

I noticed that DynFlags of GHC 7.7 has useUnicodeQuotes. I will see if we can remove quote hack if we set it False.

chokes on non-ASCII characters

With lens 3.7.1.2, building in the C locale:

Error in src/Data/Complex/Lens.hs:35: expression `let { a doctests: : hPutChar: invalid argument (invalid character)

customized comparisons for output

I use doctest to check that some types can be properly inferred. I would like some way to customize the comparison so that the following tests would be accepted:

This fails because a isn't b... though they mean exactly the same thing:

{- |
>>>  let p = (+) :: Num b => b -> b -> b
>>> :t p
p :: Num a => a -> a -> a
-}

This fails because of whitespace.... sometimes ghc breaks type signatures
into different lines

{- |
>>>  let p = (+) :: Num b => b -> b -> b
>>> :t p
p :: Num a =>
             a -> a -> a
-}

As far as I know, there is no way to get a String in ghci out of :type, so I can't even do something confusing like:

{- |
>>> let x = show (1 + 1) ++ " next"
>>> let canonicalize = filter (/=' ')
>>> let expectedX = "2next"
>>> canonicalize x == canonicalize expectedX
True
-}

One idea might be to make the comparison happen in the ghci session using whatever == is in scope (or some other/better function name). In other words,

{- |
>>> let (==) a b = canonicalize a Prelude.== canonicalize b
>>> 1+1
2
<BLANKLINE>
3
-}

will send two lines to ghci like:

let (==) a b  = canonicalize a Prelude.== canonicalize b
show (1+1) == "2\n3"

GHC 7.7's error

For GHC 7.7, doctest got the following failures against the tests.

2) Interpreter.eval shows exceptions (undefined)
expected: "*** Exception: Prelude.undefined\n"
  but got: ""

3) Interpreter.eval shows exceptions (ExitCode)
expected: "*** Exception: ExitFailure 10\n"
 but got: ""

After long investigation, I realized that GHC 7.7's error does not generate "\n" at the end. For instance,

% ghci src/Interpreter.hs
> withInterpreter [] $ \i -> eval i "1 `div` 0"
""
> withInterpreter [] $ \i -> eval i "1 `div` 0\n1+2\n"
"3\n*** Exception: divide by zero\n"

I guess this is a bug of GHC 7.7.

Dependency on `ghc` is causing trouble

The cabal2nix utility uses the doctest library to build a test program that verifies its own documentation. Now, a side-effect of this dependency is that our test program depends on ghc and several of its internal modules, such as bin-package-db, Cabal, and binary. As it happens cabal2nix uses some of those modules itself, too, but it requires newer versions that the ones shipped with the compiler. The result is that cabal configure produces a warning, saying:

Warning: This package indirectly depends on multiple versions of the same
package. This is highly likely to cause a compile failure.
package ghc-7.4.2 requires Cabal-1.14.0
package bin-package-db-0.0.0.0 requires Cabal-1.14.0
package hackage-db-1.7 requires Cabal-1.16.0.3
package cabal2nix-1.56 requires Cabal-1.16.0.3

In Nix, this warning aborts the build, because it's usually serious and shouldn't be ignored. See http://hydra.cryp.to/build/30779/nixlog/2/raw for a complete build log.

Now, how do I deal with this situation? I could tell the build to ignore the warning and proceed anyway, but that's really unsatisfactory, because then the build would succeed even if the warning changes to something really serious, and then we wouldn't notice. Is there any way to get rid of that particular warning, maybe?

Dynamic linking of GHCi 7.7

Here is the other failures for "spec":

1) Extract, extract (regression tests), works with a module that splices in an expression from an other module
uncaught exception: GhcException (test/extract/th/Foo.hs:8:9:
    cannot find normal object file ‛/var/folders/k0/548g5xg90jjfbrj5j09nvwv80000gq/T/.doctest-22631/Bar.dyn_o’
    while linking an interpreted expression)

4) Main, doctest (regression tests), template-haskell-bugfix
uncaught exception: GhcException (Main.hs:10:21:
    cannot find normal object file ‛/var/folders/k0/548g5xg90jjfbrj5j09nvwv80000gq/T/.doctest-22631/Printf.dyn_o’
    while linking an interpreted expression)

These are probably because GHCi now is using dynamic linking. I don't know workaround for these at this moment.

GHC 7.8 vs prop>

I'm testing whether or not GHC 7.8 RC2 commands set work correctly for "prop>". Unfortunately, I got the following error against "prop>":

% doctest Data/Set/Splay.hs 
### Failure in Data/Set/Splay.hs:104: expression `some is' ==> valid . snd . deleteMax . fromList $ is''

<interactive>:32:14: lexical error at character '\8216'
### Failure in Data/Set/Splay.hs:121: expression `insert 5 (fromList [5,3]) == fromList [3,5]'

If "prop>" is not used, this error does not occur. u8216 is not defined in Unicode. Is this error reported from the lexer of GHC?

doctest doesn't compile with GHC 7.7 snapshot

Building doctest-0.9.7...
Preprocessing library doctest-0.9.7...
[ 1 of 13] Compiling Paths_doctest    ( dist/build/autogen/Paths_doctest.hs, dist/build/Paths_doctest.o )
[ 2 of 13] Compiling Interpreter      ( src/Interpreter.hs, dist/build/Interpreter.o )
[ 3 of 13] Compiling Help             ( src/Help.hs, dist/build/Help.o )
[ 4 of 13] Compiling Util             ( src/Util.hs, dist/build/Util.o )
[ 5 of 13] Compiling Runner.Example   ( src/Runner/Example.hs, dist/build/Runner/Example.o )
[ 6 of 13] Compiling Location         ( src/Location.hs, dist/build/Location.o )
[ 7 of 13] Compiling GhcUtil          ( src/GhcUtil.hs, dist/build/GhcUtil.o )

src/GhcUtil.hs:8:25: Module `Panic' does not export `ghcError'

library of v0.7

How soon the library of v0.7 is available? Currenly the only executable can be compiled.

Doctest crashes on Groundhog example

I've narrowed this down to a fairly "simple" example, which is to say all of the evil occurs in the background. My source file:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}

module Main
where

import Database.Groundhog
import Database.Groundhog.TH

data Foo = Foo { bar :: Int }

mkPersist defaultCodegenConfig [groundhog|
- entity: Foo
|]

main = putStrLn "Boom."

When I run doctest on this file, it commits suicide:

$ doctest Main.hs 
Killed

Running in ghci is slightly more informative, but is still beyond my ability to debug:

Prelude> import Test.DocTest
Prelude Test.DocTest> doctest ["Main.hs"]
...
GHCi runtime linker: fatal error: I found a duplicate definition for symbol
   __stginit_transformerszm0zi3zi0zi0_ControlziApplicativeziBackwards
whilst processing object file
   /usr/lib64/transformers-0.3.0.0/ghc-7.6.3/libHStransformers-0.3.0.0.a
This could be caused by:
   * Loading two different object files which export the same symbol
   * Specifying the same object file twice on the GHCi command line
   * An incorrect `package.conf' entry, causing some object to be
     loaded twice.
GHCi cannot safely continue in this situation.  Exiting now.  Sorry.

ghc-pkg says everything on my system is happy.

A way to wrap long lines

Python allows long line wrapping with the tripple dot, like this:

# >>> SomeLongFunction(
# ... arg1, arg2, arg3)
# output

It would be really nice if haskell doctest could do this too.

7.9 support

Bumping the upper bound from 7.9 to 7.10 in the cabal file works but we get 2 failing tests

1) Main.doctest template-haskell
template-haskell ["Foo.hs"]
expected: Examples: 2  Tried: 2  Errors: 0  Failures: 0
 but got: Examples: 2  Tried: 2  Errors: 0  Failures: 1

2) Main, doctest (regression tests), template-haskell-bugfix
template-haskell-bugfix ["Main.hs"]
expected: Examples: 2  Tried: 2  Errors: 0  Failures: 0
 but got: Examples: 2  Tried: 2  Errors: 0  Failures: 1

Randomized with seed 4611685479519110675

Finished in 34.1091 seconds
142 examples, 2 failures
Test suite spec: FAIL

It'd be great if we could use doctest with 7.9. Perhaps this has to do with changes to the TH API in 7.9.

Allow trailing comments

A given term is enclosed with "(" and ")" when it is passed to quickCheck.
This does not allow trailing comments. For instance,

prop> some is ==> valid (delete (head is) (fromList is)) -- delete root
prop> some is ==> valid $ delete (last is) (fromList is) -- delete leaf
prop> some is ==> valid $ delete x (fromList is) -- delete non-member

(where "some" ensures non-empty list and "valid" ensures a tree is well-formed)

Using $ instead of () solves this problem. But it breaks a literal with type notation. For instance

prop> True :: Bool

But is this important? I guess typical properties have binary operators which can be parsed even if there are type notations.

Code that splices in TH does not work anymore

Steps to reproduce:

-- Main.hs
{-# LANGUAGE TemplateHaskell #-}
module Main where

-- Import our template "pr"
import Printf ( pr )

-- The splice operator $ takes the Haskell source code
-- generated at compile time by "pr" and splices it into
-- the argument of "putStrLn".
main = putStrLn ( $(pr "Hello") )
-- Printf.hs
{-# LANGUAGE TemplateHaskell #-}
--
-- derived from: http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.html#th-example
--
module Printf (pr) where

import Language.Haskell.TH

data Format = D | S | L String

parse :: String -> [Format]
parse s   = [ L s ]

gen :: [Format] -> Q Exp
gen [D]   = [| \n -> show n |]
gen [S]   = [| \s -> s |]
gen [L s] = stringE s

-- |
--
-- >>> 23
-- 23
pr :: String -> Q Exp
pr s = gen (parse s)
$ doctest Main.hs

Unexpected 'Overlapping instances' occurs on debian wheezy (ghc-7.4.1)

doctest this module

module TestTarget where

-- $setup
-- >>> import Test.QuickCheck
-- >>> instance Arbitrary T where arbitrary = return T

-- |
-- 
-- >>> T == T
-- True
-- 
-- prop> t == t
-- 
data T = T deriving Eq

by

$ doctest TestTarget.hs

causes

### Failure in TestTarget.hs:9: expression `T == T'
expected: True
 but got:
          <interactive>:32:3:
              Overlapping instances for Eq T
                arising from a use of `=='
              Matching instances:
                instance Eq T -- Defined at TestTarget.hs:14:21
                instance Eq T -- Defined at TestTarget.hs:14:21
              In the expression: T == T
              In an equation for `it': it = T == T
Examples: 4  Tried: 4  Errors: 0  Failures: 1

on debian wheezy with

/var/lib/ghc/package.conf.d
   Cabal-1.14.0
   array-0.4.0.0
   base-4.5.0.0
   bin-package-db-0.0.0.0
   binary-0.5.1.0
   bytestring-0.9.2.1
   containers-0.4.2.1
   deepseq-1.3.0.0
   directory-1.1.0.2
   extensible-exceptions-0.1.1.4
   filepath-1.3.0.0
   ghc-7.4.1
   ghc-prim-0.2.0.0
   haskell2010-1.1.0.1
   haskell98-2.0.0.1
   hoopl-3.8.7.3
   hpc-0.5.1.1
   integer-gmp-0.4.0.0
   old-locale-1.0.0.4
   old-time-1.1.0.0
   pretty-1.1.1.0
   process-1.1.0.1
   rts-1.0
   template-haskell-2.7.0.0
   time-1.4
   unix-2.5.1.0
/home/vagrant/work/doctest/.cabal-sandbox/x86_64-linux-ghc-7.4.1-packages.conf.d
   QuickCheck-2.6
   doctest-0.9.10
   ghc-paths-0.1.0.9
   random-1.0.1.1
   syb-0.4.1
   transformers-0.3.0.0

On the other hand, this problem is not reproduced on ghc-7.6.3 environment.

doctest vs *.o

I have one problem with doctest. In my package, there is cbits/foo.c. To load an HS file by GHCi, dist/build/cbits/foo.o" should also be specified:

% ghci dist/build/cbits/foo.o XXX/YYY.hs

But doctest rejects this arguments:

% doctest dist/build/cbits/foo.o XXX/YYY.hs
doctest: target `dist/build/cbits/foo.o' is not a module name or a source file

I tried to find the way to specify a target file as an option, but I could not found it. Do you know how to fix this?

Update README

  • Add documentation and examples for QuickCheck support

doctest leaves ghc running

Doctest (from 104caf3) sometimes leaves ghc running after finishing. For example executing tests/runtests.sh in a loop and then exiting with ^C can leave the ghc up and consuming nearly 100% of cpu. To get rid of it it needs to be killed with -9.

This is more noticeable when more than one interpreter is started. I first noticed this with test-framework-doctest as it currently uses a new interpreter for each doctest and test runs leave a ghc hanging pretty much every time the doctests are run.

Small typo in README

If an example fails, subsequent examples from the same group are skiped. => skipped

Doctests does not always use "right" GHC

On my machine, instead of using ghc, I need to use a wrapper script that adds additional package databases. This is the ghc in PATH, whereas doctests uses GHC.Paths.ghc (as seen in Interpreter.hs), which is in fact also a wrapper script on my machine but not the one I need.

My suggestion is using ghc from PATH by default, and/or giving me an environment variable to customize which GHC to use. It can still fall back to GHC.Paths.ghc, of course.

Specifics of my situation:

Nix using nixpkgs on OS X. I use nix' haskellPackages_ghc742.ghcWithPackages function to install a GHC complete with commonly used packages (i.e. the haskell platform and some others).

ghc in PATH is /nix/store/6s8zylpykahxwlxr3ar8bi1s6slpqbjx-haskell-env-ghc-7.4.2/bin/ghc with contents

#! /nix/store/pizqh1kn20szxsnvp2k2bpd7ar2jpzv5-bash-4.2-p24/bin/sh -e
exec /nix/store/2qa339vlijw9qyp771c194y9y1ki8p40-ghc-7.4.2/bin/ghc -B/nix/store/6s8zylpykahxwlxr3ar8bi1s6slpqbjx-haskell-env-ghc-7.4.2/lib "${extraFlagsArray[@]}" "$@"

GHC.Paths.ghc is /nix/store/xcsn1rgn9m94m66wakardg0fnr26pq0y-ghc-7.4.2-wrapper/bin/ghc with contents

#! /nix/store/pizqh1kn20szxsnvp2k2bpd7ar2jpzv5-bash-4.2-p24/bin/sh -e
exec /nix/store/2qa339vlijw9qyp771c194y9y1ki8p40-ghc-7.4.2/bin/ghc $(/nix/store/xcsn1rgn9m94m66wakardg0fnr26pq0y-ghc-7.4.2-wrapper/bin/ghc-get-packages.sh 7.4.2 "$(dirname $0)") "${extraFlagsArray[@]}" "$@"

Note that both GHC scripts actually use the same ghc binary, but add different package configurations.

Support for text files

I'd love to use this to test my README.md too (which Python's doctest supports). Running doctest with README.md currently gives me:

doctests: target `README.md' is not a module name or a source file

I assume this means text files aren't supported. If I'm wrong, please let me know, but if not, I'd love the feature to exist please!

7.4.1 compat

Recently upgraded to GHC 7.4.1; and I was unable to compile doctest. Likely due to haddock having 7.4.1 compilation issues as well. Tinkered a bit with the .cabal file constraints, no luck so far. It'd be nice if we can get doctest compiling with 7.4.1.

Add support for setup/teardown

The idea is to run all interactions from a named chunk $setup before each example (if a named chunk with that name exists). The documentation author can then decide whether he wants to include the setup code into the generated documentation by (not) referencing $setup.

use cabal repl to run the tests?

cabal-install HEAD (which will be tagged 1.18 in a few weeks), has cabal ghci / repl support, which seems like it would allow sandboxed running of doc tests.

Using the GHC API on Mac OS X with ghci or runhaskell causes a segmentation fault

If docTest is used with ghci or runghc, it causes segfault:

*Main> docTest ["../Data/RBTree.hs"] ["-i.."]
zsh: segmentation fault ghci Test2.hs

This is very inconvenient because "runghc Test.hs", for exmaple causes segfault, where
Test.hs contains test-framework-doctest.

Are there any work around on this?

I'm using GHC 7.0.4 on Mac.

doctest cant be sandboxed ?! (ie hsenv or cabal-dev)

I'm trying to use cabal-dev or hsenv to do sandboxed builds for github.com/analytics/analytics

the build process for the doctest suite doesn't seem to play nice with being sandboxed.

if doctest is creating its own shell session or something... maybe its somehow not inheriting the environment variables from the parent shell / process correct?

Output less clutter on failures

Let's look at an example.

module Foo where

-- | A failing example
--
-- >>> 23
-- 42
foo :: a
foo = undefined

-- | An other failing example
--
-- >>> putStrLn "foo\nbar"
-- foo
-- baz
bar :: a
bar = undefined

Running doctest Foo.hs produces the following output.

There are 2 tests, with 2 total interactions.
### Failure in Foo.hs:5: expression `23'
expected: ["42"]
 but got: ["23"]
### Failure in Foo.hs:12: expression `putStrLn "foo\nbar"'
expected: ["foo","baz"]
 but got: ["foo","bar"]
Examples: 2  Tried: 2  Errors: 0  Failures: 2

And I think it would be nice to get this instead.

There are 2 tests, with 2 total interactions.
### Failure in Foo.hs:5: expression `23'
expected: 42
 but got: 23
### Failure in Foo.hs:12: expression `putStrLn "foo\nbar"'
expected: foo
          baz
 but got: foo
          bar
Examples: 2  Tried: 2  Errors: 0  Failures: 2

If any line contains any trailing whitespace, we would still need to print quotes.

tests fails with GHC 7.8

Now cabal test on doctest-haskell got the following error:

17) Property.runProperty reports the values for which a property that takes multiple arguments fails
expected: ["False","0","\"\""]
 but got: ["<interactive>:24:66:","    \8216doctest_prop\8217 is not in the type environment at a reify","    In the splice: $(polyQuickCheck 'doctest_prop)"]

This is relating to src/Property.hs:

  where
    quickCheck term vars =
      "let doctest_prop " ++ unwords vars ++ " = " ++ term ++
      " in $(polyQuickCheck 'doctest_prop)"

It seems to me that the behavior of Template Haskell changed. I don't know how to fix this.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.