module Test.Tasty.TH
( testGroupGenerator
, defaultMainGenerator
, testGroupGeneratorFor
, defaultMainGeneratorFor
, extractTestFunctions
, locationModule
) where
import Control.Monad (join)
import Control.Applicative
import Language.Haskell.Exts (parseFileContentsWithMode)
import Language.Haskell.Exts.Parser (ParseResult(..), defaultParseMode, parseFilename)
import qualified Language.Haskell.Exts.Syntax as S
import Language.Haskell.TH
import Data.Maybe
import Data.Data (gmapQ, Data)
import Data.Typeable (cast)
import Data.List (nub, isPrefixOf, find)
import qualified Data.Foldable as F
import Test.Tasty
import Prelude
defaultMainGenerator :: ExpQ
defaultMainGenerator = [| defaultMain $(testGroupGenerator) |]
testGroupGenerator :: ExpQ
testGroupGenerator = join $ testGroupGeneratorFor <$> fmap loc_module location <*> testFunctions
where
testFunctions = location >>= runIO . extractTestFunctions . loc_filename
extractTestFunctions :: FilePath -> IO [String]
extractTestFunctions filePath = do
file <- readFile filePath
let functions = fromMaybe (lexed file) (parsed file)
filtered pat = filter (pat `isPrefixOf`) functions
return . nub $ concat [filtered "prop_", filtered "case_", filtered "test_"]
where
lexed = map fst . concatMap lex . lines
parsed file = case parseFileContentsWithMode (defaultParseMode { parseFilename = filePath }) file of
ParseOk parsedModule -> Just (declarations parsedModule)
ParseFailed _ _ -> Nothing
declarations (S.Module _ _ _ _ decls) = concatMap testFunName decls
declarations _ = []
testFunName (S.PatBind _ pat _ _) = patternVariables pat
testFunName (S.FunBind _ clauses) = nub (map clauseName clauses)
testFunName _ = []
clauseName (S.Match _ name _ _ _) = nameString name
clauseName (S.InfixMatch _ _ name _ _ _) = nameString name
nameString :: S.Name l -> String
nameString (S.Ident _ n) = n
nameString (S.Symbol _ n) = n
patternVariables :: Data l => S.Pat l -> [String]
patternVariables = go
where
go (S.PVar _ name) = [nameString name]
go pat = concat $ gmapQ (F.foldMap go . cast) pat
locationModule :: ExpQ
locationModule = do
loc <- location
return $ LitE $ StringL $ loc_module loc
testGroupGeneratorFor
:: String
-> [String]
-> ExpQ
testGroupGeneratorFor name functionNames = [| testGroup name $(listE (mapMaybe test functionNames)) |]
where
testFunctions = [("prop_", "testProperty"), ("case_", "testCase"), ("test_", "testGroup")]
getTestFunction fname = snd <$> find ((`isPrefixOf` fname) . fst) testFunctions
test fname = do
fn <- getTestFunction fname
return $ appE (appE (varE $ mkName fn) (stringE (fixName fname))) (varE (mkName fname))
defaultMainGeneratorFor
:: String
-> [String]
-> ExpQ
defaultMainGeneratorFor name fns = [| defaultMain $(testGroupGeneratorFor name fns) |]
fixName :: String -> String
fixName = replace '_' ' ' . tail . dropWhile (/= '_')
replace :: Eq a => a -> a -> [a] -> [a]
replace b v = map (\i -> if b == i then v else i)