test for fast (not TH).
This commit is contained in:
parent
b35d19beec
commit
0556ec330c
2
Debug.hs
2
Debug.hs
@ -1,4 +1,4 @@
|
||||
module Debug (debugInfo) where
|
||||
module Debug (debugInfo, debug) where
|
||||
|
||||
import CabalApi
|
||||
import Control.Applicative
|
||||
|
@ -80,6 +80,7 @@ Test-Suite spec
|
||||
BrowseSpec
|
||||
CabalApiSpec
|
||||
CheckSpec
|
||||
DebugSpec
|
||||
FlagSpec
|
||||
InfoSpec
|
||||
LangSpec
|
||||
|
23
test/DebugSpec.hs
Normal file
23
test/DebugSpec.hs
Normal file
@ -0,0 +1,23 @@
|
||||
module DebugSpec where
|
||||
|
||||
import CabalApi
|
||||
import Cradle
|
||||
import Debug
|
||||
import Expectation
|
||||
import Test.Hspec
|
||||
import Types
|
||||
|
||||
checkFast :: String -> String -> IO ()
|
||||
checkFast file ans = withDirectory_ "test/data" $ do
|
||||
(strVer,_) <- getGHCVersion
|
||||
cradle <- findCradle Nothing strVer
|
||||
res <- debug defaultOptions cradle strVer file
|
||||
res `shouldContain` ans
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "debug" $ do
|
||||
it "can check TH" $ do
|
||||
checkFast "Main.hs" "Fast check: No"
|
||||
checkFast "Foo.hs" "Fast check: Yes"
|
||||
checkFast "Bar.hs" "Fast check: No"
|
5
test/data/Bar.hs
Normal file
5
test/data/Bar.hs
Normal file
@ -0,0 +1,5 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module Bar (bar) where
|
||||
import Foo (foo)
|
||||
|
||||
bar = $foo ++ "bar"
|
5
test/data/Foo.hs
Normal file
5
test/data/Foo.hs
Normal file
@ -0,0 +1,5 @@
|
||||
module Foo (foo) where
|
||||
import Language.Haskell.TH
|
||||
|
||||
foo :: ExpQ
|
||||
foo = stringE "foo"
|
3
test/data/Main.hs
Normal file
3
test/data/Main.hs
Normal file
@ -0,0 +1,3 @@
|
||||
import Bar (bar)
|
||||
|
||||
main = putStrLn bar
|
Loading…
Reference in New Issue
Block a user