Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
See cabal-doctest README for full-fledged recipes & caveats.
The provided generateBuildModule
generates a Build_{suffix}
module, with
caller-chosen suffix
that is usually "doctests"
-- module Build_doctests
.
That module exports just enough compiler flags, so that doctest could be simply
module Main where import Build_doctests (flags, pkgs, module_sources) import Test.Doctest (doctest) main :: IO () main = doctest args where args = flags ++ pkgs ++ module_sources
As this module-generation is done at build-time, generateBuildModule
must be
invoked from Setup.hs
, which also necessarily means build-type: Custom
.
Setup.hs
can use libraries, but they must be declared as dependencies in the
custom-setup
stanza of the user's cabal file. To use cabal-doctest
then:
custom-setup setup-depends: base >= 4 && <5, cabal-doctest >= 1 && <1.1
Finally, simple shortcuts are provided to avoid an explicit dependency on Cabal
from setup-depends
: defaultMainWithDoctests
and defaultMainAutoconfWithDoctests
.
Synopsis
- defaultMainWithDoctests :: String -> IO ()
- defaultMainAutoconfWithDoctests :: String -> IO ()
- addDoctestsUserHook :: String -> UserHooks -> UserHooks
- doctestsUserHooks :: String -> UserHooks
- generateBuildModule :: String -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
Documentation
defaultMainWithDoctests Source #
A default Setup.hs
main with doctests:
import Distribution.Extra.Doctest (defaultMainWithDoctests) main :: IO () main = defaultMainWithDoctests "doctests"
defaultMainAutoconfWithDoctests Source #
Like defaultMainWithDoctests
, but for packages with build-type: Configure
.
Since: 1.0.2
addDoctestsUserHook :: String -> UserHooks -> UserHooks Source #
Compose generateBuildModule
into Cabal's UserHooks
(prepending the action).
This is exported for advanced custom Setup-s.
Since: 1.0.2
simpleUserHooks
with generateBuildModule
already wired-in.
:: String | doctests test-suite name |
-> BuildFlags | |
-> PackageDescription | |
-> LocalBuildInfo | |
-> IO () |
Generate a build module for the test suite.
import Distribution.Simple (defaultMainWithHooks, UserHooks(..), simpleUserHooks) import Distribution.Extra.Doctest (generateBuildModule) main :: IO () main = defaultMainWithHooks simpleUserHooks { buildHook = pkg lbi hooks flags -> do generateBuildModule "doctests" flags pkg lbi buildHook simpleUserHooks pkg lbi hooks flags }