Merge pull request #115 from eagletmt/quasi-quotes

Fix fast check about QuasiQuotes
This commit is contained in:
Kazu Yamamoto 2013-04-01 17:54:48 -07:00
commit 71d3017ec9
6 changed files with 30 additions and 6 deletions

View File

@ -25,8 +25,7 @@ debug opt cradle ver fileName = do
[fast] <- withGHC fileName $ do [fast] <- withGHC fileName $ do
void $ initializeFlagsWithCradle opt cradle gopts True void $ initializeFlagsWithCradle opt cradle gopts True
setTargetFile fileName setTargetFile fileName
slow <- needsTemplateHaskell <$> depanal [] False pure . canCheckFast <$> depanal [] False
return [not slow]
return [ return [
"GHC version: " ++ ver "GHC version: " ++ ver
, "Current directory: " ++ currentDir , "Current directory: " ++ currentDir

View File

@ -7,6 +7,7 @@ module GHCApi (
, getDynamicFlags , getDynamicFlags
, setSlowDynFlags , setSlowDynFlags
, checkSlowAndSet , checkSlowAndSet
, canCheckFast
) where ) where
import CabalApi import CabalApi
@ -128,8 +129,8 @@ setSlowDynFlags = (flip setFastOrNot Slow <$> getSessionDynFlags)
-- So, this is necessary redundancy. -- So, this is necessary redundancy.
checkSlowAndSet :: Ghc () checkSlowAndSet :: Ghc ()
checkSlowAndSet = do checkSlowAndSet = do
slow <- needsTemplateHaskell <$> depanal [] False fast <- canCheckFast <$> depanal [] False
when slow setSlowDynFlags unless fast setSlowDynFlags
---------------------------------------------------------------- ----------------------------------------------------------------
@ -150,3 +151,9 @@ setTargetFile file = do
getDynamicFlags :: IO DynFlags getDynamicFlags :: IO DynFlags
getDynamicFlags = runGhc (Just libdir) getSessionDynFlags getDynamicFlags = runGhc (Just libdir) getSessionDynFlags
canCheckFast :: ModuleGraph -> Bool
canCheckFast = not . any (hasTHorQQ . ms_hspp_opts)
where
hasTHorQQ :: DynFlags -> Bool
hasTHorQQ dflags = any (\opt -> xopt opt dflags) [Opt_TemplateHaskell, Opt_QuasiQuotes]

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