Show more relevant bindings in typed holes

This commit is contained in:
Alejandro Serrano 2014-07-06 09:45:02 +02:00
parent 75b838bab6
commit 72679c619c
2 changed files with 12 additions and 2 deletions

View File

@ -32,7 +32,7 @@ checkSyntax files = withErrorHandler sessionName $ do
check :: [FilePath] -- ^ The target files. check :: [FilePath] -- ^ The target files.
-> GhcMod (Either String String) -> GhcMod (Either String String)
check fileNames = do check fileNames = do
withLogger setAllWaringFlags $ do withLogger (setAllWaringFlags . setNoMaxRelevantBindings) $ do
setTargetFiles fileNames setTargetFiles fileNames
---------------------------------------------------------------- ----------------------------------------------------------------

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ScopedTypeVariables, RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables, RecordWildCards, CPP #-}
module Language.Haskell.GhcMod.GHCApi ( module Language.Haskell.GhcMod.GHCApi (
withGHC withGHC
@ -11,6 +11,7 @@ module Language.Haskell.GhcMod.GHCApi (
, withCmdFlags , withCmdFlags
, setNoWaringFlags , setNoWaringFlags
, setAllWaringFlags , setAllWaringFlags
, setNoMaxRelevantBindings
) where ) where
import Language.Haskell.GhcMod.CabalApi import Language.Haskell.GhcMod.CabalApi
@ -195,6 +196,15 @@ setNoWaringFlags df = df { warningFlags = Gap.emptyWarnFlags}
setAllWaringFlags :: DynFlags -> DynFlags setAllWaringFlags :: DynFlags -> DynFlags
setAllWaringFlags df = df { warningFlags = allWarningFlags } setAllWaringFlags df = df { warningFlags = allWarningFlags }
-- | Set 'DynFlags' equivalent to "-fno-max-relevant-bindings".
setNoMaxRelevantBindings :: DynFlags -> DynFlags
#if __GLASGOW_HASKELL__ >= 708
setNoMaxRelevantBindings df = df { maxRelevantBinds = Nothing }
#else
setNoMaxRelevantBindings = id
#endif
allWarningFlags :: Gap.WarnFlags allWarningFlags :: Gap.WarnFlags
allWarningFlags = unsafePerformIO $ do allWarningFlags = unsafePerformIO $ do
mlibdir <- getSystemLibDir mlibdir <- getSystemLibDir