Add a test case for checking QuasiQuotes module

This commit is contained in:
eagletmt 2013-04-01 15:55:29 +09:00
parent c56b625501
commit 4b77af102b
4 changed files with 20 additions and 2 deletions

View File

@ -3,7 +3,7 @@ module CheckSpec where
import CabalApi import CabalApi
import Check import Check
import Cradle import Cradle
import Data.List (isSuffixOf, isInfixOf) import Data.List (isSuffixOf, isInfixOf, isPrefixOf)
import Expectation import Expectation
import Test.Hspec import Test.Hspec
import Types import Types
@ -31,3 +31,9 @@ spec = do
cradle <- findCradle Nothing strVer cradle <- findCradle Nothing strVer
res <- checkSyntax defaultOptions cradle "Mutual1.hs" res <- checkSyntax defaultOptions cradle "Mutual1.hs"
res `shouldSatisfy` ("Module imports form a cycle" `isInfixOf`) res `shouldSatisfy` ("Module imports form a cycle" `isInfixOf`)
it "can check a module using QuasiQuotes" $ do
withDirectory_ "test/data" $ do
cradle <- getGHCVersion >>= findCradle Nothing . fst
res <- checkSyntax defaultOptions cradle "Baz.hs"
res `shouldSatisfy` ("Baz.hs:5:1:Warning:" `isPrefixOf`)

View File

@ -21,3 +21,6 @@ spec = do
checkFast "Main.hs" "Fast check: No" checkFast "Main.hs" "Fast check: No"
checkFast "Foo.hs" "Fast check: Yes" checkFast "Foo.hs" "Fast check: Yes"
checkFast "Bar.hs" "Fast check: No" checkFast "Bar.hs" "Fast check: No"
it "can check QuasiQuotes" $ do
checkFast "Baz.hs" "Fast check: No"

5
test/data/Baz.hs Normal file
View File

@ -0,0 +1,5 @@
{-# LANGUAGE QuasiQuotes #-}
module Baz (baz) where
import Foo (fooQ)
baz = [fooQ| foo bar baz |]

View File

@ -1,5 +1,9 @@
module Foo (foo) where module Foo (foo, fooQ) where
import Language.Haskell.TH import Language.Haskell.TH
import Language.Haskell.TH.Quote (QuasiQuoter(..))
foo :: ExpQ foo :: ExpQ
foo = stringE "foo" foo = stringE "foo"
fooQ :: QuasiQuoter
fooQ = QuasiQuoter (litE . stringL) undefined undefined undefined