cabal-doctest-1.0.7: A Setup.hs helper for doctests running

Safe HaskellNone
LanguageHaskell2010

Distribution.Extra.Doctest

Description

The provided generateBuildModule generates Build_doctests module. That module exports enough configuration, so your doctests could be simply

module Main where

import Build_doctests (flags, pkgs, module_sources)
import Data.Foldable (traverse_)
import Test.Doctest (doctest)

main :: IO ()
main = do
    traverse_ putStrLn args -- optionally print arguments
    doctest args
  where
    args = flags ++ pkgs ++ module_sources

To use this library in the Setup.hs, you should specify a custom-setup section in the cabal file, for example:

custom-setup
 setup-depends:
   base >= 4 && <5,
   cabal-doctest >= 1 && <1.1

Note: you don't need to depend on Cabal if you use only defaultMainWithDoctests in the Setup.hs.

Synopsis

Documentation

defaultMainWithDoctests Source #

Arguments

:: String

doctests test-suite name

-> IO () 

A default main with doctests:

import Distribution.Extra.Doctest
       (defaultMainWithDoctests)

main :: IO ()
main = defaultMainWithDoctests "doctests"

defaultMainAutoconfWithDoctests Source #

Arguments

:: String

doctests test-suite name

-> IO () 

Like defaultMainWithDoctests, for 'build-type: Configure' packages.

Since: 1.0.2

doctestsUserHooks Source #

Arguments

:: String

doctests test-suite name

-> UserHooks 

generateBuildModule Source #

Arguments

:: 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
    }