Workaround for #340

This commit is contained in:
Daniel Gröber 2014-09-12 03:48:22 +02:00
parent b728294d3d
commit 615c6c4543
2 changed files with 14 additions and 5 deletions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
module Language.Haskell.GhcMod.Target ( module Language.Haskell.GhcMod.Target (
setTargetFiles setTargetFiles
) where ) where
@ -5,7 +6,7 @@ module Language.Haskell.GhcMod.Target (
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Control.Monad (forM, void, (>=>)) import Control.Monad (forM, void, (>=>))
import DynFlags (ExtensionFlag(..), xopt) import DynFlags (ExtensionFlag(..), xopt)
import GHC (DynFlags(..), LoadHowMuch(..)) import GHC (LoadHowMuch(..))
import qualified GHC as G import qualified GHC as G
import Language.Haskell.GhcMod.DynFlags import Language.Haskell.GhcMod.DynFlags
import Language.Haskell.GhcMod.Monad import Language.Haskell.GhcMod.Monad
@ -50,7 +51,10 @@ setTargetFiles files = do
setCompilerMode Intelligent setCompilerMode Intelligent
needsFallback :: G.ModuleGraph -> Bool needsFallback :: G.ModuleGraph -> Bool
needsFallback = any (hasTHorQQ . G.ms_hspp_opts) needsFallback = any $ \ms ->
where let df = G.ms_hspp_opts ms in
hasTHorQQ :: DynFlags -> Bool Opt_TemplateHaskell `xopt` df
hasTHorQQ dflags = any (`xopt` dflags) [Opt_TemplateHaskell, Opt_QuasiQuotes] || Opt_QuasiQuotes `xopt` df
#if __GLASGOW_HASKELL__ >= 708
|| (Opt_PatternSynonyms `xopt` df)
#endif

View File

@ -31,6 +31,11 @@ spec = do
res <- runID $ checkSyntax ["Baz.hs"] res <- runID $ checkSyntax ["Baz.hs"]
res `shouldSatisfy` ("Baz.hs:5:1:Warning:" `isPrefixOf`) res `shouldSatisfy` ("Baz.hs:5:1:Warning:" `isPrefixOf`)
it "works with modules using PatternSynonyms" $ do
withDirectory_ "test/data/pattern-synonyms" $ do
res <- runID $ checkSyntax ["B.hs"]
res `shouldSatisfy` ("B.hs:6:9:Warning:" `isPrefixOf`)
it "works with foreign exports" $ do it "works with foreign exports" $ do
withDirectory_ "test/data" $ do withDirectory_ "test/data" $ do
res <- runID $ checkSyntax ["ForeignExport.hs"] res <- runID $ checkSyntax ["ForeignExport.hs"]