hledger/hledger-lib/Hledger.hs
Simon Michael b4c336c874 test/_test/it/_it helpers; refactor easytests
This makes skipping/unskipping tests easier, and improves readability
a bit.

Note it's also possible to just write the test name with no preceding
function, when the type is constrained (see Journal.hs).
2018-08-17 13:40:37 +01:00

33 lines
767 B
Haskell

{-# LANGUAGE OverloadedStrings #-}
module Hledger (
module X
,tests_Hledger
,Hledger.easytests
)
where
import Test.HUnit hiding (test)
import EasyTest
import Hledger.Data as X hiding (easytests)
import qualified Hledger.Data (easytests)
import Hledger.Read as X hiding (samplejournal, easytests)
import qualified Hledger.Read (easytests)
import Hledger.Reports as X
import Hledger.Query as X
import Hledger.Utils as X
tests_Hledger = TestList
[
tests_Hledger_Data
,tests_Hledger_Query
,tests_Hledger_Read
,tests_Hledger_Reports
,tests_Hledger_Utils
]
easytests = test "Hledger" $ tests [
Hledger.Data.easytests
,Hledger.Read.easytests
]