import DynFlag only in Gap.
This commit is contained in:
parent
c8fbdcfa2f
commit
c1c0993b4a
@ -1,7 +1,6 @@
|
|||||||
module Language.Haskell.GhcMod.Doc where
|
module Language.Haskell.GhcMod.Doc where
|
||||||
|
|
||||||
import DynFlags (DynFlags)
|
import GHC (Ghc, DynFlags)
|
||||||
import GHC (Ghc)
|
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
import Language.Haskell.GhcMod.Gap (withStyle, showDocWith)
|
import Language.Haskell.GhcMod.Gap (withStyle, showDocWith)
|
||||||
import Outputable (SDoc, PprStyle, mkUserStyle, Depth(AllTheWay), neverQualify)
|
import Outputable (SDoc, PprStyle, mkUserStyle, Depth(AllTheWay), neverQualify)
|
||||||
|
@ -11,7 +11,6 @@ import Bag (Bag, bagToList)
|
|||||||
import Control.Applicative ((<$>))
|
import Control.Applicative ((<$>))
|
||||||
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
|
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import DynFlags (dopt)
|
|
||||||
import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo)
|
import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo)
|
||||||
import GHC (Ghc, DynFlags, SrcSpan, Severity(SevError))
|
import GHC (Ghc, DynFlags, SrcSpan, Severity(SevError))
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
@ -85,8 +84,8 @@ ppMsg spn sev dflag style msg = prefix ++ cts
|
|||||||
where
|
where
|
||||||
cts = showPage dflag style msg
|
cts = showPage dflag style msg
|
||||||
defaultPrefix
|
defaultPrefix
|
||||||
| dopt Gap.dumpSplicesFlag dflag = ""
|
| Gap.isDumpSplices dflag = ""
|
||||||
| otherwise = checkErrorPrefix
|
| otherwise = checkErrorPrefix
|
||||||
prefix = fromMaybe defaultPrefix $ do
|
prefix = fromMaybe defaultPrefix $ do
|
||||||
(line,col,_,_) <- Gap.getSrcSpan spn
|
(line,col,_,_) <- Gap.getSrcSpan spn
|
||||||
file <- normalise <$> Gap.getSrcFile spn
|
file <- normalise <$> Gap.getSrcFile spn
|
||||||
|
@ -21,7 +21,6 @@ import Control.Monad (forM, void)
|
|||||||
import CoreMonad (liftIO)
|
import CoreMonad (liftIO)
|
||||||
import Data.Maybe (isJust, fromJust)
|
import Data.Maybe (isJust, fromJust)
|
||||||
import Distribution.PackageDescription (PackageDescription)
|
import Distribution.PackageDescription (PackageDescription)
|
||||||
import DynFlags (dopt_set)
|
|
||||||
import Exception (ghandle, SomeException(..))
|
import Exception (ghandle, SomeException(..))
|
||||||
import GHC (Ghc, GhcMonad, DynFlags(..), GhcLink(..), HscTarget(..), LoadHowMuch(..))
|
import GHC (Ghc, GhcMonad, DynFlags(..), GhcLink(..), HscTarget(..), LoadHowMuch(..))
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
@ -146,8 +145,8 @@ setBuildEnv build = setHideAllPackages build . setCabalPackage build
|
|||||||
-- | Set option in 'DynFlags' to Expand template haskell if first argument is
|
-- | Set option in 'DynFlags' to Expand template haskell if first argument is
|
||||||
-- True
|
-- True
|
||||||
setSplice :: Bool -> DynFlags -> DynFlags
|
setSplice :: Bool -> DynFlags -> DynFlags
|
||||||
setSplice False df = df
|
setSplice False = id
|
||||||
setSplice True df = dopt_set df Gap.dumpSplicesFlag
|
setSplice True = Gap.setDumpSplices
|
||||||
|
|
||||||
-- At the moment with this option set ghc only prints different error messages,
|
-- At the moment with this option set ghc only prints different error messages,
|
||||||
-- suggesting the user to add a hidden package to the build-depends in his cabal
|
-- suggesting the user to add a hidden package to the build-depends in his cabal
|
||||||
|
@ -15,6 +15,9 @@ module Language.Haskell.GhcMod.Gap (
|
|||||||
, setCabalPkg
|
, setCabalPkg
|
||||||
, setHideAllPackages
|
, setHideAllPackages
|
||||||
, addPackageFlags
|
, addPackageFlags
|
||||||
|
, setDeferTypeErrors
|
||||||
|
, setDumpSplices
|
||||||
|
, isDumpSplices
|
||||||
, filterOutChildren
|
, filterOutChildren
|
||||||
, infoThing
|
, infoThing
|
||||||
, pprInfo
|
, pprInfo
|
||||||
@ -29,8 +32,6 @@ module Language.Haskell.GhcMod.Gap (
|
|||||||
, showDocWith
|
, showDocWith
|
||||||
, GapThing(..)
|
, GapThing(..)
|
||||||
, fromTyThing
|
, fromTyThing
|
||||||
, dumpSplicesFlag
|
|
||||||
, setDeferTypeErrors
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Applicative hiding (empty)
|
import Control.Applicative hiding (empty)
|
||||||
@ -235,12 +236,10 @@ setCabalPkg dflag = dopt_set dflag Opt_BuildingCabalPackage
|
|||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
setHideAllPackages :: DynFlags -> DynFlags
|
setHideAllPackages :: DynFlags -> DynFlags
|
||||||
setHideAllPackages df = df'
|
|
||||||
where
|
|
||||||
#if __GLASGOW_HASKELL__ >= 707
|
#if __GLASGOW_HASKELL__ >= 707
|
||||||
df' = gopt_set df Opt_HideAllPackages
|
setHideAllPackages df = gopt_set df Opt_HideAllPackages
|
||||||
#else
|
#else
|
||||||
df' = dopt_set df Opt_HideAllPackages
|
setHideAllPackages df = dopt_set df Opt_HideAllPackages
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
addPackageFlags :: [Package] -> DynFlags -> DynFlags
|
addPackageFlags :: [Package] -> DynFlags -> DynFlags
|
||||||
@ -249,6 +248,26 @@ addPackageFlags pkgs df =
|
|||||||
where
|
where
|
||||||
expose pkg = ExposePackageId $ showPkgId pkg
|
expose pkg = ExposePackageId $ showPkgId pkg
|
||||||
|
|
||||||
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
setDumpSplices :: DynFlags -> DynFlags
|
||||||
|
setDumpSplices dflag = dopt_set dflag Opt_D_dump_splices
|
||||||
|
|
||||||
|
isDumpSplices :: DynFlags -> Bool
|
||||||
|
isDumpSplices dflag = dopt Opt_D_dump_splices dflag
|
||||||
|
|
||||||
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
|
||||||
|
setDeferTypeErrors :: DynFlags -> DynFlags
|
||||||
|
#if __GLASGOW_HASKELL__ >= 707
|
||||||
|
setDeferTypeErrors dflag = gopt_set dflag Opt_DeferTypeErrors
|
||||||
|
#elif __GLASGOW_HASKELL__ >= 706
|
||||||
|
setDeferTypeErrors dflag = dopt_set dflag Opt_DeferTypeErrors
|
||||||
|
#else
|
||||||
|
setDeferTypeErrors = id
|
||||||
|
#endif
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
@ -355,21 +374,3 @@ fromTyThing (ADataCon d) = GtA $ dataConRepType d
|
|||||||
#endif
|
#endif
|
||||||
fromTyThing (ATyCon t) = GtT t
|
fromTyThing (ATyCon t) = GtT t
|
||||||
fromTyThing _ = GtN
|
fromTyThing _ = GtN
|
||||||
|
|
||||||
----------------------------------------------------------------
|
|
||||||
|
|
||||||
#if __GLASGOW_HASKELL__ >= 707
|
|
||||||
dumpSplicesFlag :: DumpFlag
|
|
||||||
#else
|
|
||||||
dumpSplicesFlag :: DynFlag
|
|
||||||
#endif
|
|
||||||
dumpSplicesFlag = Opt_D_dump_splices
|
|
||||||
|
|
||||||
setDeferTypeErrors :: DynFlags -> DynFlags
|
|
||||||
#if __GLASGOW_HASKELL__ >= 707
|
|
||||||
setDeferTypeErrors dflag = gopt_set dflag Opt_DeferTypeErrors
|
|
||||||
#elif __GLASGOW_HASKELL__ >= 706
|
|
||||||
setDeferTypeErrors dflag = dopt_set dflag Opt_DeferTypeErrors
|
|
||||||
#else
|
|
||||||
setDeferTypeErrors = id
|
|
||||||
#endif
|
|
||||||
|
Loading…
Reference in New Issue
Block a user