Add a test case for checking QuasiQuotes module
This commit is contained in:
parent
c56b625501
commit
4b77af102b
@ -3,7 +3,7 @@ module CheckSpec where
|
||||
import CabalApi
|
||||
import Check
|
||||
import Cradle
|
||||
import Data.List (isSuffixOf, isInfixOf)
|
||||
import Data.List (isSuffixOf, isInfixOf, isPrefixOf)
|
||||
import Expectation
|
||||
import Test.Hspec
|
||||
import Types
|
||||
@ -31,3 +31,9 @@ spec = do
|
||||
cradle <- findCradle Nothing strVer
|
||||
res <- checkSyntax defaultOptions cradle "Mutual1.hs"
|
||||
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`)
|
||||
|
@ -21,3 +21,6 @@ spec = do
|
||||
checkFast "Main.hs" "Fast check: No"
|
||||
checkFast "Foo.hs" "Fast check: Yes"
|
||||
checkFast "Bar.hs" "Fast check: No"
|
||||
|
||||
it "can check QuasiQuotes" $ do
|
||||
checkFast "Baz.hs" "Fast check: No"
|
||||
|
5
test/data/Baz.hs
Normal file
5
test/data/Baz.hs
Normal file
@ -0,0 +1,5 @@
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
module Baz (baz) where
|
||||
import Foo (fooQ)
|
||||
|
||||
baz = [fooQ| foo bar baz |]
|
@ -1,5 +1,9 @@
|
||||
module Foo (foo) where
|
||||
module Foo (foo, fooQ) where
|
||||
import Language.Haskell.TH
|
||||
import Language.Haskell.TH.Quote (QuasiQuoter(..))
|
||||
|
||||
foo :: ExpQ
|
||||
foo = stringE "foo"
|
||||
|
||||
fooQ :: QuasiQuoter
|
||||
fooQ = QuasiQuoter (litE . stringL) undefined undefined undefined
|
||||
|
Loading…
Reference in New Issue
Block a user