ghc-mod/GhcMod/Exe/Test.hs

58 lines
1.5 KiB
Haskell
Raw Permalink Normal View History

2017-08-19 21:27:08 +00:00
{-# LANGUAGE CPP #-}
module GhcMod.Exe.Test where
2015-12-16 20:45:16 +00:00
import Control.Applicative
import Data.List
import System.FilePath
import System.Directory
2015-12-16 20:45:16 +00:00
import Prelude
import GhcMod.Types
import GhcMod.Monad
import GhcMod.DynFlags
2015-12-16 20:45:16 +00:00
import GHC
import GHC.Exception
import OccName
test :: IOish m
=> FilePath -> GhcModT m String
2015-12-28 12:59:59 +00:00
test f = runGmlT' [Left f] (fmap setHscInterpreted . deferErrors) $ do
mg <- getModuleGraph
root <- cradleRootDir <$> cradle
f' <- makeRelative root <$> liftIO (canonicalizePath f)
let Just ms = find ((==Just f') . ml_hs_file . ms_location) mg
mdl = ms_mod ms
mn = moduleName mdl
Just mi <- getModuleInfo mdl
let exs = map (occNameString . getOccName) $ modInfoExports mi
cqs = filter ("prop_" `isPrefixOf`) exs
setContext [ IIDecl $ simpleImportDecl mn
, IIDecl $ simpleImportDecl $ mkModuleName "Test.QuickCheck"
]
_res <- mapM runTest cqs
return ""
2017-08-19 21:27:08 +00:00
#if __GLASGOW_HASKELL__ >= 802
runTest :: GhcMonad m => String -> m (Maybe SomeException)
runTest fn = do
res <- execStmt ("quickCheck " ++ fn) execOptions
return $ case res of
ExecComplete (Right _) _ -> Nothing
ExecComplete (Left se) _ -> Just se
_ -> error "runTest"
#else
runTest :: GhcMonad m => String -> m (Maybe SomeException)
runTest fn = do
res <- runStmt ("quickCheck " ++ fn) RunToCompletion
return $ case res of
RunOk [] -> Nothing
RunException se -> Just se
_ -> error "runTest"
2017-08-19 21:27:08 +00:00
#endif