diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index c1f15cfcc7..0d70f31bb7 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -14,7 +14,7 @@ homepage: https://github.com/haskell/haskell-language-server/tree/master/ghcide#readme bug-reports: https://github.com/haskell/haskell-language-server/issues -tested-with: GHC ==9.8.2 || ==9.6.4 || ==9.4.8 || ==9.2.8 +tested-with: GHC ==9.8.2 || ==9.6.5 || ==9.4.8 || ==9.2.8 extra-source-files: CHANGELOG.md README.md @@ -98,7 +98,6 @@ library , prettyprinter-ansi-terminal , random , regex-tdfa >=1.3.1.0 - , row-types , safe-exceptions , sorted-list , sqlite-simple @@ -272,25 +271,12 @@ library ghcide-test-utils visibility: public default-language: GHC2021 - hs-source-dirs: test/src test/cabal + hs-source-dirs: test/cabal exposed-modules: Development.IDE.Test.Runfiles build-depends: - aeson, - base > 4.9 && < 5, - containers, - data-default, - directory, - extra, - filepath, - ghcide, - lsp-types, - hls-plugin-api, - lens, - lsp-test ^>= 0.17, - tasty-hunit >= 0.10, - text, + base > 4.9 && < 5 default-extensions: LambdaCase diff --git a/ghcide/session-loader/Development/IDE/Session.hs b/ghcide/session-loader/Development/IDE/Session.hs index a0a5e9596e..71688afd1d 100644 --- a/ghcide/session-loader/Development/IDE/Session.hs +++ b/ghcide/session-loader/Development/IDE/Session.hs @@ -49,18 +49,19 @@ import qualified Data.Text as T import Data.Time.Clock import Data.Version import Development.IDE.Core.RuleTypes -import Development.IDE.Core.Shake hiding (Log, Priority, - knownTargets, withHieDb) +import Development.IDE.Core.Shake hiding (Log, knownTargets, + withHieDb) import qualified Development.IDE.GHC.Compat as Compat +import Development.IDE.GHC.Compat.CmdLine import Development.IDE.GHC.Compat.Core hiding (Target, TargetFile, TargetModule, Var, Warning, getOptions) import qualified Development.IDE.GHC.Compat.Core as GHC import Development.IDE.GHC.Compat.Env hiding (Logger) import Development.IDE.GHC.Compat.Units (UnitId) -import qualified Development.IDE.GHC.Compat.Util as Compat import Development.IDE.GHC.Util import Development.IDE.Graph (Action) +import qualified Development.IDE.Session.Implicit as GhcIde import Development.IDE.Session.VersionCheck import Development.IDE.Types.Diagnostics import Development.IDE.Types.Exports @@ -69,8 +70,8 @@ import Development.IDE.Types.HscEnvEq (HscEnvEq, newHscEnvEq, import Development.IDE.Types.Location import Development.IDE.Types.Options import GHC.Check +import GHC.ResponseFile import qualified HIE.Bios as HieBios -import qualified HIE.Bios.Cradle as HieBios import HIE.Bios.Environment hiding (getCacheDir) import HIE.Bios.Types hiding (Log) import qualified HIE.Bios.Types as HieBios @@ -113,27 +114,21 @@ import HieDb.Utils import qualified System.Random as Random import System.Random (RandomGen) -import qualified Development.IDE.Session.Implicit as GhcIde - -import Development.IDE.GHC.Compat.CmdLine - - -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if MIN_VERSION_ghc(9,3,0) import qualified Data.Set as OS +import qualified Development.IDE.GHC.Compat.Util as Compat +import GHC.Data.Graph.Directed import GHC.Data.Bag import GHC.Driver.Env (hsc_all_home_unit_ids) import GHC.Driver.Errors.Types -import GHC.Driver.Make (checkHomeUnitsClosed) import GHC.Types.Error (errMsgDiagnostic, singleMessage) import GHC.Unit.State #endif -import GHC.Data.Graph.Directed -import GHC.ResponseFile - data Log = LogSettingInitialDynFlags | LogGetInitialGhcLibDirDefaultCradleFail !CradleError !FilePath !(Maybe FilePath) !(Cradle Void) diff --git a/ghcide/src/Development/IDE/Core/Compile.hs b/ghcide/src/Development/IDE/Core/Compile.hs index 1c46362c19..f295e568c6 100644 --- a/ghcide/src/Development/IDE/Core/Compile.hs +++ b/ghcide/src/Development/IDE/Core/Compile.hs @@ -1,8 +1,8 @@ -- Copyright (c) 2019 The DAML Authors. All rights reserved. -- SPDX-License-Identifier: Apache-2.0 -{-# LANGUAGE CPP #-} -{-# LANGUAGE GADTs #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE GADTs #-} -- | Based on https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/API. -- Given a list of paths to find libraries, and a file to compile, produce a list of 'CoreModule' values. @@ -38,17 +38,14 @@ module Development.IDE.Core.Compile , shareUsages ) where -import Prelude hiding (mod) -import Control.Monad.IO.Class import Control.Concurrent.Extra import Control.Concurrent.STM.Stats hiding (orElse) -import Control.DeepSeq (NFData (..), force, - rnf) +import Control.DeepSeq (NFData (..), force, rnf) import Control.Exception (evaluate) import Control.Exception.Safe -import Control.Lens hiding (List, (<.>), pre) -import Control.Monad.Except +import Control.Lens hiding (List, pre, (<.>)) import Control.Monad.Extra +import Control.Monad.IO.Class import Control.Monad.Trans.Except import qualified Control.Monad.Trans.State.Strict as S import Data.Aeson (toJSON) @@ -65,8 +62,8 @@ import Data.IntMap (IntMap) import Data.IORef import Data.List.Extra import qualified Data.Map.Strict as Map -import Data.Proxy (Proxy(Proxy)) import Data.Maybe +import Data.Proxy (Proxy (Proxy)) import qualified Data.Text as T import Data.Time (UTCTime (..)) import Data.Tuple.Extra (dupe) @@ -97,33 +94,26 @@ import GHC (ForeignHValue, import qualified GHC.LanguageExtensions as LangExt import GHC.Serialized import HieDb hiding (withHieDb) +import qualified Language.LSP.Protocol.Message as LSP +import Language.LSP.Protocol.Types (DiagnosticTag (..)) +import qualified Language.LSP.Protocol.Types as LSP import qualified Language.LSP.Server as LSP -import Language.LSP.Protocol.Types (DiagnosticTag (..)) -import qualified Language.LSP.Protocol.Types as LSP -import qualified Language.LSP.Protocol.Message as LSP +import Prelude hiding (mod) import System.Directory import System.FilePath import System.IO.Extra (fixIO, newTempFileWithin) --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - -import GHC.Tc.Gen.Splice - - - import qualified GHC as G - -#if !MIN_VERSION_ghc(9,3,0) -import GHC (ModuleGraph) -#endif - +import GHC.Tc.Gen.Splice import GHC.Types.ForeignStubs import GHC.Types.HpcInfo import GHC.Types.TypeEnv +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if !MIN_VERSION_ghc(9,3,0) import Data.Map (Map) -import GHC (GhcException (..)) +import GHC.Unit.Module.Graph (ModuleGraph) import Unsafe.Coerce #endif @@ -132,8 +122,8 @@ import qualified Data.Set as Set #endif #if MIN_VERSION_ghc(9,5,0) -import GHC.Driver.Config.CoreToStg.Prep import GHC.Core.Lint.Interactive +import GHC.Driver.Config.CoreToStg.Prep #endif #if MIN_VERSION_ghc(9,7,0) @@ -482,11 +472,7 @@ mkHiFileResultNoCompile session tcm = do tcGblEnv = tmrTypechecked tcm details <- makeSimpleDetails hsc_env_tmp tcGblEnv sf <- finalSafeMode (ms_hspp_opts ms) tcGblEnv - iface' <- mkIfaceTc hsc_env_tmp sf details ms -#if MIN_VERSION_ghc(9,5,0) - Nothing -#endif - tcGblEnv + iface' <- mkIfaceTc hsc_env_tmp sf details ms Nothing tcGblEnv let iface = iface' { mi_globals = Nothing, mi_usages = filterUsages (mi_usages iface') } -- See Note [Clearing mi_globals after generating an iface] pure $! mkHiFileResult ms iface details (tmrRuntimeModules tcm) Nothing @@ -1266,7 +1252,7 @@ parseHeader dflags filename contents = do PFailedWithErrorMessages msgs -> throwE $ diagFromErrMsgs sourceParser dflags $ msgs dflags POk pst rdr_module -> do - let (warns, errs) = renderMessages $ getPsMessages pst dflags + let (warns, errs) = renderMessages $ getPsMessages pst -- Just because we got a `POk`, it doesn't mean there -- weren't errors! To clarify, the GHC parser @@ -1301,7 +1287,7 @@ parseFileContents env customPreprocessor filename ms = do POk pst rdr_module -> let hpm_annotations = mkApiAnns pst - psMessages = getPsMessages pst dflags + psMessages = getPsMessages pst in do let IdePreprocessedSource preproc_warns errs parsed = customPreprocessor rdr_module @@ -1310,7 +1296,7 @@ parseFileContents env customPreprocessor filename ms = do throwE $ diagFromStrings sourceParser DiagnosticSeverity_Error errs let preproc_warnings = diagFromStrings sourceParser DiagnosticSeverity_Warning preproc_warns - (parsed', msgs) <- liftIO $ applyPluginsParsedResultAction env dflags ms hpm_annotations parsed psMessages + (parsed', msgs) <- liftIO $ applyPluginsParsedResultAction env ms hpm_annotations parsed psMessages let (warns, errors) = renderMessages msgs -- Just because we got a `POk`, it doesn't mean there diff --git a/ghcide/src/Development/IDE/Core/FileStore.hs b/ghcide/src/Development/IDE/Core/FileStore.hs index e96a3984cf..6c0cb875b0 100644 --- a/ghcide/src/Development/IDE/Core/FileStore.hs +++ b/ghcide/src/Development/IDE/Core/FileStore.hs @@ -21,8 +21,7 @@ module Development.IDE.Core.FileStore( Log(..) ) where -import Control.Concurrent.STM.Stats (STM, atomically, - modifyTVar') +import Control.Concurrent.STM.Stats (STM, atomically) import Control.Concurrent.STM.TQueue (writeTQueue) import Control.Exception import Control.Monad.Extra @@ -32,10 +31,8 @@ import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LBS import qualified Data.HashMap.Strict as HashMap import Data.IORef -import Data.List (foldl') import qualified Data.Text as T import qualified Data.Text as Text -import qualified Data.Text.Utf16.Rope as Rope import Data.Time import Data.Time.Clock.POSIX import Development.IDE.Core.FileUtils diff --git a/ghcide/src/Development/IDE/Core/OfInterest.hs b/ghcide/src/Development/IDE/Core/OfInterest.hs index 098b2dedaa..abcf6342a8 100644 --- a/ghcide/src/Development/IDE/Core/OfInterest.hs +++ b/ghcide/src/Development/IDE/Core/OfInterest.hs @@ -24,7 +24,6 @@ import Control.Monad.IO.Class import Data.HashMap.Strict (HashMap) import qualified Data.HashMap.Strict as HashMap import Data.Proxy -import qualified Data.Text as T import Development.IDE.Graph import Control.Concurrent.STM.Stats (atomically, diff --git a/ghcide/src/Development/IDE/Core/PositionMapping.hs b/ghcide/src/Development/IDE/Core/PositionMapping.hs index 95e3a30cae..de02f5b1f7 100644 --- a/ghcide/src/Development/IDE/Core/PositionMapping.hs +++ b/ghcide/src/Development/IDE/Core/PositionMapping.hs @@ -29,7 +29,6 @@ import Control.Monad import Data.Algorithm.Diff import Data.Bifunctor import Data.List -import Data.Row import qualified Data.Text as T import qualified Data.Vector.Unboxed as V import qualified Language.LSP.Protocol.Lens as L diff --git a/ghcide/src/Development/IDE/Core/Rules.hs b/ghcide/src/Development/IDE/Core/Rules.hs index 1e96a99f2b..609736fc72 100644 --- a/ghcide/src/Development/IDE/Core/Rules.hs +++ b/ghcide/src/Development/IDE/Core/Rules.hs @@ -42,7 +42,6 @@ module Development.IDE.Core.Rules( getHieAstsRule, getBindingsRule, needsCompilationRule, - computeLinkableTypeForDynFlags, generateCoreRule, getImportMapRule, regenerateHiFile, @@ -58,17 +57,16 @@ module Development.IDE.Core.Rules( ) where import Control.Applicative -import Control.Concurrent.Async (concurrently) import Control.Concurrent.STM.Stats (atomically) import Control.Concurrent.STM.TVar import Control.Concurrent.Strict import Control.DeepSeq import Control.Exception (evaluate) import Control.Exception.Safe -import Control.Monad.Extra hiding (msum) +import Control.Monad.Extra import Control.Monad.IO.Unlift -import Control.Monad.Reader hiding (msum) -import Control.Monad.State hiding (msum) +import Control.Monad.Reader +import Control.Monad.State import Control.Monad.Trans.Except (ExceptT, except, runExceptT) import Control.Monad.Trans.Maybe @@ -78,7 +76,7 @@ import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LBS import Data.Coerce import Data.Default (Default, def) -import Data.Foldable hiding (msum) +import Data.Foldable import Data.Hashable import qualified Data.HashMap.Strict as HM import qualified Data.HashSet as HashSet @@ -90,10 +88,8 @@ import Data.List.Extra (nubOrdOn) import qualified Data.Map as M import Data.Maybe import Data.Proxy -import qualified Data.Set as Set import qualified Data.Text as T import qualified Data.Text.Encoding as T -import qualified Data.Text.Utf16.Rope as Rope import Data.Time (UTCTime (..)) import Data.Time.Clock.POSIX (posixSecondsToUTCTime) import Data.Tuple.Extra @@ -123,7 +119,6 @@ import Development.IDE.GHC.Compat hiding import qualified Development.IDE.GHC.Compat as Compat hiding (nest, vcat) -import Development.IDE.GHC.Compat.Env import qualified Development.IDE.GHC.Compat.Util as Util import Development.IDE.GHC.Error import Development.IDE.GHC.Util hiding @@ -396,16 +391,16 @@ rawDependencyInformation fs = do go :: NormalizedFilePath -- ^ Current module being processed -> Maybe ModSummary -- ^ ModSummary of the module -> RawDepM FilePathId - go f msum = do + go f mbModSum = do -- First check to see if we have already processed the FilePath -- If we have, just return its Id but don't update any of the state. -- Otherwise, we need to process its imports. checkAlreadyProcessed f $ do - let al = modSummaryToArtifactsLocation f msum + let al = modSummaryToArtifactsLocation f mbModSum -- Get a fresh FilePathId for the new file fId <- getFreshFid al -- Record this module and its location - whenJust msum $ \ms -> + whenJust mbModSum $ \ms -> modifyRawDepInfo (\rd -> rd { rawModuleMap = IntMap.insert (getFilePathId fId) (ShowableModule $ ms_mod ms) (rawModuleMap rd)}) @@ -552,8 +547,8 @@ getHieAstRuleDefinition f hsc tmr = do _ | Just asts <- masts -> do source <- getSourceFileSource f let exports = tcg_exports $ tmrTypechecked tmr - msum = tmrModSummary tmr - liftIO $ writeAndIndexHieFile hsc se msum f exports asts source + modSummary = tmrModSummary tmr + liftIO $ writeAndIndexHieFile hsc se modSummary f exports asts source _ -> pure [] let refmap = Compat.generateReferencesMap . Compat.getAsts <$> masts @@ -1125,7 +1120,6 @@ getLinkableRule recorder = getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType) getLinkableType f = use_ NeedsCompilation f --- needsCompilationRule :: Rules () needsCompilationRule :: NormalizedFilePath -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType)) needsCompilationRule file | "boot" `isSuffixOf` fromNormalizedFilePath file = @@ -1148,36 +1142,23 @@ needsCompilationRule file = do -- that we just threw away, and thus have to recompile all dependencies once -- again, this time keeping the object code. -- A file needs to be compiled if any file that depends on it uses TemplateHaskell or needs to be compiled - ms <- msrModSummary . fst <$> useWithStale_ GetModSummaryWithoutTimestamps file (modsums,needsComps) <- liftA2 (,) (map (fmap (msrModSummary . fst)) <$> usesWithStale GetModSummaryWithoutTimestamps revdeps) (uses NeedsCompilation revdeps) - pure $ computeLinkableType ms modsums (map join needsComps) + pure $ computeLinkableType modsums (map join needsComps) pure (Just $ encodeLinkableType res, Just res) where - computeLinkableType :: ModSummary -> [Maybe ModSummary] -> [Maybe LinkableType] -> Maybe LinkableType - computeLinkableType this deps xs + computeLinkableType :: [Maybe ModSummary] -> [Maybe LinkableType] -> Maybe LinkableType + computeLinkableType deps xs | Just ObjectLinkable `elem` xs = Just ObjectLinkable -- If any dependent needs object code, so do we - | Just BCOLinkable `elem` xs = Just this_type -- If any dependent needs bytecode, then we need to be compiled - | any (maybe False uses_th_qq) deps = Just this_type -- If any dependent needs TH, then we need to be compiled + | Just BCOLinkable `elem` xs = Just BCOLinkable -- If any dependent needs bytecode, then we need to be compiled + | any (maybe False uses_th_qq) deps = Just BCOLinkable -- If any dependent needs TH, then we need to be compiled | otherwise = Nothing -- If none of these conditions are satisfied, we don't need to compile - where - this_type = computeLinkableTypeForDynFlags (ms_hspp_opts this) uses_th_qq :: ModSummary -> Bool uses_th_qq (ms_hspp_opts -> dflags) = xopt LangExt.TemplateHaskell dflags || xopt LangExt.QuasiQuotes dflags --- | How should we compile this module? --- (assuming we do in fact need to compile it). --- Depends on whether it uses unboxed tuples or sums -computeLinkableTypeForDynFlags :: DynFlags -> LinkableType -computeLinkableTypeForDynFlags d - = BCOLinkable - where -- unboxed_tuples_or_sums is only used in GHC < 9.2 - _unboxed_tuples_or_sums = - xopt LangExt.UnboxedTuples d || xopt LangExt.UnboxedSums d - -- | Tracks which linkables are current, so we don't need to unload them newtype CompiledLinkables = CompiledLinkables { getCompiledLinkables :: Var (ModuleEnv UTCTime) } instance IsIdeGlobal CompiledLinkables diff --git a/ghcide/src/Development/IDE/Core/Shake.hs b/ghcide/src/Development/IDE/Core/Shake.hs index 28e22a6b48..5325b14e7e 100644 --- a/ghcide/src/Development/IDE/Core/Shake.hs +++ b/ghcide/src/Development/IDE/Core/Shake.hs @@ -124,7 +124,6 @@ import Development.IDE.Core.ProgressReporting import Development.IDE.Core.RuleTypes import Development.IDE.Core.Tracing import Development.IDE.GHC.Compat (NameCache, - NameCacheUpdater (..), initNameCache, knownKeyNames) import Development.IDE.GHC.Orphans () @@ -172,14 +171,20 @@ import qualified StmContainers.Map as STM import System.FilePath hiding (makeRelative) import System.IO.Unsafe (unsafePerformIO) import System.Time.Extra + -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if !MIN_VERSION_ghc(9,3,0) import Data.IORef -import Development.IDE.GHC.Compat (mkSplitUniqSupply, +import Development.IDE.GHC.Compat (NameCacheUpdater (NCU), + mkSplitUniqSupply, upNameCache) #endif +#if MIN_VERSION_ghc(9,3,0) +import Development.IDE.GHC.Compat (NameCacheUpdater) +#endif + data Log = LogCreateHieDbExportsMapStart | LogCreateHieDbExportsMapFinish !Int @@ -707,7 +712,7 @@ getStateKeys = (fmap.fmap) fst . atomically . ListT.toList . STM.listT . state -- | Must be called in the 'Initialized' handler and only once shakeSessionInit :: Recorder (WithPriority Log) -> IdeState -> IO () -shakeSessionInit recorder ide@IdeState{..} = do +shakeSessionInit recorder IdeState{..} = do -- Take a snapshot of the VFS - it should be empty as we've received no notifications -- till now, but it can't hurt to be in sync with the `lsp` library. vfs <- vfsSnapshot (lspEnv shakeExtras) diff --git a/ghcide/src/Development/IDE/GHC/CPP.hs b/ghcide/src/Development/IDE/GHC/CPP.hs index d11aa9f5a0..450cc702e8 100644 --- a/ghcide/src/Development/IDE/GHC/CPP.hs +++ b/ghcide/src/Development/IDE/GHC/CPP.hs @@ -18,11 +18,10 @@ where import Development.IDE.GHC.Compat as Compat import Development.IDE.GHC.Compat.Util import GHC +import GHC.Settings -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] -import GHC.Settings - #if !MIN_VERSION_ghc(9,3,0) import qualified GHC.Driver.Pipeline as Pipeline #endif diff --git a/ghcide/src/Development/IDE/GHC/Compat.hs b/ghcide/src/Development/IDE/GHC/Compat.hs index 51487ce534..75590d0596 100644 --- a/ghcide/src/Development/IDE/GHC/Compat.hs +++ b/ghcide/src/Development/IDE/GHC/Compat.hs @@ -1,8 +1,8 @@ -- Copyright (c) 2019 The DAML Authors. All rights reserved. -- SPDX-License-Identifier: Apache-2.0 -{-# LANGUAGE CPP #-} -{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE PatternSynonyms #-} -- | Attempt at hiding the GHC version differences we can. module Development.IDE.GHC.Compat( @@ -10,29 +10,14 @@ module Development.IDE.GHC.Compat( addIncludePathsQuote, getModuleHash, setUpTypedHoles, - NameCacheUpdater(..), -#if MIN_VERSION_ghc(9,3,0) - nameEnvElts, -#else - upNameCache, -#endif lookupNameCache, disableWarningsAsErrors, reLoc, reLocA, renderMessages, pattern PFailedWithErrorMessages, - -#if !MIN_VERSION_ghc(9,3,0) - extendModSummaryNoDeps, - emsModSummary, -#endif myCoreToStgExpr, - Usage(..), - - liftZonkM, - FastStringCompat, bytesFS, mkFastStringByteString, @@ -46,11 +31,6 @@ module Development.IDE.GHC.Compat( nodeAnnotations, mkAstNode, combineRealSrcSpans, -#if !MIN_VERSION_ghc(9,3,0) - nonDetOccEnvElts, -#endif - nonDetFoldOccEnv, - isQualifiedImport, GhcVersion(..), ghcVersion, @@ -88,9 +68,6 @@ module Development.IDE.GHC.Compat( simplifyExpr, tidyExpr, emptyTidyEnv, -#if MIN_VERSION_ghc(9,7,0) - tcInitTidyEnv, -#endif corePrepExpr, corePrepPgm, lintInteractiveExpr, @@ -98,11 +75,6 @@ module Development.IDE.GHC.Compat( HomePackageTable, lookupHpt, loadModulesHome, -#if MIN_VERSION_ghc(9,3,0) - Dependencies(dep_direct_mods), -#else - Dependencies(dep_mods), -#endif bcoFreeNames, ModIfaceAnnotation, pattern Annotation, @@ -125,13 +97,49 @@ module Development.IDE.GHC.Compat( expectJust, extract_cons, recDotDot, + +#if !MIN_VERSION_ghc(9,3,0) + Dependencies(dep_mods), + NameCacheUpdater(NCU), + extendModSummaryNoDeps, + emsModSummary, + nonDetNameEnvElts, + nonDetOccEnvElts, + upNameCache, +#endif + +#if MIN_VERSION_ghc(9,3,0) + Dependencies(dep_direct_mods), + NameCacheUpdater, +#endif + #if MIN_VERSION_ghc(9,5,0) XModulePs(..), #endif + +#if !MIN_VERSION_ghc(9,7,0) + liftZonkM, + nonDetFoldOccEnv, +#endif + +#if MIN_VERSION_ghc(9,7,0) + tcInitTidyEnv, +#endif ) where -import Prelude hiding (mod) -import Development.IDE.GHC.Compat.Core hiding (moduleUnitId) +import Compat.HieAst (enrichHie) +import Compat.HieBin +import Compat.HieTypes hiding + (nodeAnnotations) +import qualified Compat.HieTypes as GHC (nodeAnnotations) +import Compat.HieUtils +import qualified Data.ByteString as BS +import Data.Coerce (coerce) +import Data.List (foldl') +import qualified Data.Map as Map +import qualified Data.Set as S +import Data.String (IsString (fromString)) +import Development.IDE.GHC.Compat.Core import Development.IDE.GHC.Compat.Env import Development.IDE.GHC.Compat.Iface import Development.IDE.GHC.Compat.Logger @@ -140,90 +148,81 @@ import Development.IDE.GHC.Compat.Parser import Development.IDE.GHC.Compat.Plugins import Development.IDE.GHC.Compat.Units import Development.IDE.GHC.Compat.Util -import GHC hiding (HasSrcSpan, - ModLocation, - RealSrcSpan, exprType, - getLoc, lookupName) -import Data.Coerce (coerce) -import Data.String (IsString (fromString)) -import Compat.HieAst (enrichHie) -import Compat.HieBin -import Compat.HieTypes hiding (nodeAnnotations) -import qualified Compat.HieTypes as GHC (nodeAnnotations) -import Compat.HieUtils -import qualified Data.ByteString as BS -import Data.List (foldl') -import qualified Data.Map as Map -import qualified Data.Set as S - -import qualified GHC.Core.Opt.Pipeline as GHC -import GHC.Core.Tidy (tidyExpr) -import GHC.CoreToStg.Prep (corePrepPgm) -import qualified GHC.CoreToStg.Prep as GHC -import GHC.Driver.Hooks (hscCompileCoreExprHook) - -import GHC.ByteCode.Asm (bcoFreeNames) -import GHC.Types.Annotations (AnnTarget (ModuleTarget), - Annotation (..), - extendAnnEnvList) -import GHC.Types.Unique.DFM as UniqDFM -import GHC.Types.Unique.DSet as UniqDSet -import GHC.Types.Unique.Set as UniqSet -import GHC.Data.FastString +import GHC hiding (ModLocation, + RealSrcSpan, exprType, + getLoc, lookupName) +import Prelude hiding (mod) + +import qualified GHC.Core.Opt.Pipeline as GHC +import GHC.Core.Tidy (tidyExpr) +import GHC.CoreToStg.Prep (corePrepPgm) +import qualified GHC.CoreToStg.Prep as GHC +import GHC.Driver.Hooks (hscCompileCoreExprHook) + +import GHC.ByteCode.Asm (bcoFreeNames) import GHC.Core +import GHC.Data.FastString import GHC.Data.StringBuffer -import GHC.Driver.Session hiding (ExposePackage) +import GHC.Driver.Session hiding (ExposePackage) +import GHC.Iface.Make (mkIfaceExports) +import GHC.SysTools.Tasks (runPp, runUnlit) +import GHC.Types.Annotations (AnnTarget (ModuleTarget), + Annotation (..), + extendAnnEnvList) +import qualified GHC.Types.Avail as Avail +import GHC.Types.Unique.DFM as UniqDFM +import GHC.Types.Unique.DSet as UniqDSet +import GHC.Types.Unique.Set as UniqSet import GHC.Types.Var.Env -import GHC.Iface.Make (mkIfaceExports) -import GHC.SysTools.Tasks (runUnlit, runPp) -import qualified GHC.Types.Avail as Avail -import GHC.Iface.Env -import GHC.Types.SrcLoc (combineRealSrcSpans) -import GHC.Runtime.Context (icInteractiveModule) -import GHC.Unit.Home.ModInfo (HomePackageTable, - lookupHpt) -import GHC.Driver.Env as Env -import GHC.Unit.Module.ModIface import GHC.Builtin.Uniques import GHC.ByteCode.Types import GHC.CoreToStg import GHC.Data.Maybe -import GHC.Linker.Loader (loadDecls, loadExpr) +import GHC.Driver.Env as Env +import GHC.Iface.Env +import GHC.Linker.Loader (loadDecls, loadExpr) +import GHC.Runtime.Context (icInteractiveModule) import GHC.Stg.Pipeline import GHC.Stg.Syntax import GHC.StgToByteCode import GHC.Types.CostCentre import GHC.Types.IPE +import GHC.Types.SrcLoc (combineRealSrcSpans) +import GHC.Unit.Home.ModInfo (HomePackageTable, + lookupHpt) +import GHC.Unit.Module.ModIface -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if !MIN_VERSION_ghc(9,3,0) -import GHC.Unit.Module.Deps (Dependencies(dep_mods), Usage(..)) -import GHC.Unit.Module.ModSummary -import GHC.Runtime.Interpreter import Data.IORef +import GHC.Runtime.Interpreter +import GHC.Unit.Module.Deps (Dependencies (dep_mods), + Usage (..)) +import GHC.Unit.Module.ModSummary #endif #if MIN_VERSION_ghc(9,3,0) -import GHC.Unit.Module.Deps (Dependencies(dep_direct_mods), Usage(..)) -import GHC.Driver.Config.Stg.Pipeline +import GHC.Driver.Config.Stg.Pipeline +import GHC.Unit.Module.Deps (Dependencies (dep_direct_mods), + Usage (..)) #endif #if !MIN_VERSION_ghc(9,5,0) -import GHC.Core.Lint (lintInteractiveExpr) +import GHC.Core.Lint (lintInteractiveExpr) #endif #if MIN_VERSION_ghc(9,5,0) -import GHC.Core.Lint.Interactive (interactiveInScope) -import GHC.Driver.Config.Core.Lint.Interactive (lintInteractiveExpr) -import GHC.Driver.Config.Core.Opt.Simplify (initSimplifyExprOpts) -import GHC.Driver.Config.CoreToStg (initCoreToStgOpts) -import GHC.Driver.Config.CoreToStg.Prep (initCorePrepConfig) +import GHC.Core.Lint.Interactive (interactiveInScope) +import GHC.Driver.Config.Core.Lint.Interactive (lintInteractiveExpr) +import GHC.Driver.Config.Core.Opt.Simplify (initSimplifyExprOpts) +import GHC.Driver.Config.CoreToStg (initCoreToStgOpts) +import GHC.Driver.Config.CoreToStg.Prep (initCorePrepConfig) #endif #if MIN_VERSION_ghc(9,7,0) -import GHC.Tc.Zonk.TcType (tcInitTidyEnv) +import GHC.Tc.Zonk.TcType (tcInitTidyEnv) #endif #if !MIN_VERSION_ghc(9,7,0) @@ -241,9 +240,9 @@ nonDetOccEnvElts = occEnvElts type ModIfaceAnnotation = Annotation -#if MIN_VERSION_ghc(9,3,0) -nameEnvElts :: NameEnv a -> [a] -nameEnvElts = nonDetNameEnvElts +#if !MIN_VERSION_ghc(9,3,0) +nonDetNameEnvElts :: NameEnv a -> [a] +nonDetNameEnvElts = nameEnvElts #endif myCoreToStgExpr :: Logger -> DynFlags -> InteractiveContext diff --git a/ghcide/src/Development/IDE/GHC/Compat/Core.hs b/ghcide/src/Development/IDE/GHC/Compat/Core.hs index 467f4210e2..f6ab831b72 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Core.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Core.hs @@ -1,6 +1,5 @@ -{-# LANGUAGE CPP #-} -{-# LANGUAGE PatternSynonyms #-} -{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE PatternSynonyms #-} -- | Compat Core module that handles the GHC module hierarchy re-organization -- by re-exporting everything we care about. @@ -117,9 +116,6 @@ module Development.IDE.GHC.Compat.Core ( pattern ConPatIn, conPatDetails, mapConPatDetail, -#if MIN_VERSION_ghc(9,5,0) - mkVisFunTys, -#endif -- * Specs ImpDeclSpec(..), ImportSpec(..), @@ -408,156 +404,159 @@ import qualified GHC -- NOTE(ozkutuk): Cpp clashes Phase.Cpp, so we hide it. -- Not the greatest solution, but gets the job done -- (until the CPP extension is actually needed). -import GHC.LanguageExtensions.Type hiding (Cpp) - -import GHC.Hs.Binds - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] +import GHC.LanguageExtensions.Type hiding (Cpp) -import GHC.Builtin.Names hiding (Unique, printName) +import GHC.Builtin.Names hiding (Unique, printName) import GHC.Builtin.Types import GHC.Builtin.Types.Prim import GHC.Builtin.Utils +import GHC.Core (CoreProgram) import GHC.Core.Class import GHC.Core.Coercion import GHC.Core.ConLike -import GHC.Core.DataCon hiding (dataConExTyCoVars) -import qualified GHC.Core.DataCon as DataCon -import GHC.Core.FamInstEnv hiding (pprFamInst) +import GHC.Core.DataCon hiding (dataConExTyCoVars) +import qualified GHC.Core.DataCon as DataCon +import GHC.Core.FamInstEnv hiding (pprFamInst) import GHC.Core.InstEnv -import GHC.Types.Unique.FM import GHC.Core.PatSyn import GHC.Core.Predicate import GHC.Core.TyCo.Ppr -import qualified GHC.Core.TyCo.Rep as TyCoRep +import qualified GHC.Core.TyCo.Rep as TyCoRep import GHC.Core.TyCon import GHC.Core.Type import GHC.Core.Unify import GHC.Core.Utils -import GHC.Driver.CmdLine (Warn (..)) +import GHC.Driver.CmdLine (Warn (..)) import GHC.Driver.Hooks -import GHC.Driver.Main as GHC +import GHC.Driver.Main as GHC import GHC.Driver.Monad import GHC.Driver.Phases import GHC.Driver.Pipeline import GHC.Driver.Plugins -import GHC.Driver.Session hiding (ExposePackage) -import qualified GHC.Driver.Session as DynFlags +import GHC.Driver.Session hiding (ExposePackage) +import qualified GHC.Driver.Session as DynFlags +import GHC.Hs.Binds import GHC.HsToCore.Docs import GHC.HsToCore.Expr import GHC.HsToCore.Monad import GHC.Iface.Load -import GHC.Iface.Make as GHC +import GHC.Iface.Make as GHC import GHC.Iface.Recomp import GHC.Iface.Syntax -import GHC.Iface.Tidy as GHC +import GHC.Iface.Tidy as GHC import GHC.IfaceToCore import GHC.Parser -import GHC.Parser.Header hiding (getImports) -import GHC.Rename.Fixity (lookupFixityRn) +import GHC.Parser.Header hiding (getImports) +import GHC.Rename.Fixity (lookupFixityRn) import GHC.Rename.Names import GHC.Rename.Splice -import qualified GHC.Runtime.Interpreter as GHCi +import qualified GHC.Runtime.Interpreter as GHCi import GHC.Tc.Instance.Family import GHC.Tc.Module import GHC.Tc.Types -import GHC.Tc.Types.Evidence hiding ((<.>)) +import GHC.Tc.Types.Evidence hiding ((<.>)) import GHC.Tc.Utils.Env -import GHC.Tc.Utils.Monad hiding (Applicative (..), IORef, - MonadFix (..), MonadIO (..), - allM, anyM, concatMapM, - mapMaybeM, (<$>)) -import GHC.Tc.Utils.TcType as TcType -import qualified GHC.Types.Avail as Avail +import GHC.Tc.Utils.Monad hiding (Applicative (..), IORef, + MonadFix (..), MonadIO (..), allM, + anyM, concatMapM, mapMaybeM, + (<$>)) +import GHC.Tc.Utils.TcType as TcType +import qualified GHC.Types.Avail as Avail import GHC.Types.Basic import GHC.Types.Id -import GHC.Types.Name hiding (varName) +import GHC.Types.Name hiding (varName) import GHC.Types.Name.Cache import GHC.Types.Name.Env -import GHC.Types.Name.Reader hiding (GRE, gre_name, gre_imp, gre_lcl, gre_par) -import qualified GHC.Types.Name.Reader as RdrName -import GHC.Types.SrcLoc (BufPos, BufSpan, - SrcLoc (UnhelpfulLoc), - SrcSpan (UnhelpfulSpan)) -import qualified GHC.Types.SrcLoc as SrcLoc +import GHC.Types.Name.Reader hiding (GRE, gre_imp, gre_lcl, + gre_name, gre_par) +import qualified GHC.Types.Name.Reader as RdrName +import GHC.Types.SrcLoc (BufPos, BufSpan, + SrcLoc (UnhelpfulLoc), + SrcSpan (UnhelpfulSpan)) +import qualified GHC.Types.SrcLoc as SrcLoc +import GHC.Types.Unique.FM import GHC.Types.Unique.Supply -import GHC.Types.Var (Var (varName), setTyVarUnique, - setVarUnique) - -import qualified GHC.Types.Var as TypesVar -import GHC.Unit.Info (PackageName (..)) -import GHC.Unit.Module hiding (ModLocation (..), UnitId, - moduleUnit, - toUnitId) -import qualified GHC.Unit.Module as Module -import GHC.Unit.State (ModuleOrigin (..)) -import GHC.Utils.Error (Severity (..), emptyMessages) -import GHC.Utils.Panic hiding (try) -import qualified GHC.Utils.Panic.Plain as Plain - - -import Data.Foldable (toList) +import GHC.Types.Var (Var (varName), setTyVarUnique, + setVarUnique) + +import qualified GHC.Types.Var as TypesVar +import GHC.Unit.Info (PackageName (..)) +import GHC.Unit.Module hiding (ModLocation (..), UnitId, + moduleUnit, toUnitId) +import qualified GHC.Unit.Module as Module +import GHC.Unit.State (ModuleOrigin (..)) +import GHC.Utils.Error (Severity (..), emptyMessages) +import GHC.Utils.Panic hiding (try) +import qualified GHC.Utils.Panic.Plain as Plain + + +import Data.Foldable (toList) +import GHC.Core.Multiplicity (scaledThing) import GHC.Data.Bag -import GHC.Core.Multiplicity (scaledThing) import GHC.Driver.Env -import GHC.Hs (HsModule (..), SrcSpanAnn') -import GHC.Hs.Decls hiding (FunDep) +import GHC.Hs (HsModule (..), SrcSpanAnn') +import GHC.Hs.Decls hiding (FunDep) import GHC.Hs.Doc import GHC.Hs.Expr import GHC.Hs.Extension import GHC.Hs.ImpExp import GHC.Hs.Pat import GHC.Hs.Type -import GHC.Hs.Utils hiding (collectHsBindsBinders) -import qualified GHC.Linker.Loader as Linker +import GHC.Hs.Utils hiding (collectHsBindsBinders) +import qualified GHC.Linker.Loader as Linker import GHC.Linker.Types -import GHC.Parser.Lexer hiding (initParserState, getPsMessages) -import GHC.Parser.Annotation (EpAnn (..)) +import GHC.Parser.Annotation (EpAnn (..)) +import GHC.Parser.Lexer hiding (getPsMessages, + initParserState) import GHC.Platform.Ways -import GHC.Runtime.Context (InteractiveImport (..)) -#if !MIN_VERSION_ghc(9,7,0) -import GHC.Types.Avail (greNamePrintableName) -#endif -import GHC.Types.Fixity (LexicalFixity (..), Fixity (..), defaultFixity) +import GHC.Runtime.Context (InteractiveImport (..)) +import GHC.Types.Fixity (Fixity (..), LexicalFixity (..), + defaultFixity) import GHC.Types.Meta import GHC.Types.Name.Set -import GHC.Types.SourceFile (HscSource (..)) +import GHC.Types.SourceFile (HscSource (..)) import GHC.Types.SourceText -import GHC.Types.Target (Target (..), TargetId (..)) +import GHC.Types.Target (Target (..), TargetId (..)) import GHC.Types.TyThing import GHC.Types.TyThing.Ppr -import GHC.Unit.Finder hiding (mkHomeModLocation) +import GHC.Unit.Finder hiding (mkHomeModLocation) import GHC.Unit.Home.ModInfo import GHC.Unit.Module.Imported import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts -import GHC.Unit.Module.ModIface (IfaceExport, ModIface, - ModIface_ (..), mi_fix) -import GHC.Unit.Module.ModSummary (ModSummary (..)) -import Language.Haskell.Syntax hiding (FunDep) +import GHC.Unit.Module.ModIface (IfaceExport, ModIface, + ModIface_ (..), mi_fix) +import GHC.Unit.Module.ModSummary (ModSummary (..)) +import Language.Haskell.Syntax hiding (FunDep) + +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if !MIN_VERSION_ghc(9,3,0) -import GHC.Types.SourceFile (SourceModified(..)) -import GHC.Unit.Module.Graph (mkModuleGraph) -import qualified GHC.Unit.Finder as GHC +import GHC.Types.SourceFile (SourceModified (..)) +import qualified GHC.Unit.Finder as GHC +import GHC.Unit.Module.Graph (mkModuleGraph) #endif #if MIN_VERSION_ghc(9,3,0) -import GHC.Utils.Error (mkPlainErrorMsgEnvelope) -import GHC.Driver.Env.KnotVars -import GHC.Unit.Module.Graph -import GHC.Driver.Errors.Types -import GHC.Types.Unique.Map -import GHC.Types.Unique -import GHC.Utils.TmpFs -import GHC.Utils.Panic -import GHC.Unit.Finder.Types -import GHC.Unit.Env -import qualified GHC.Driver.Config.Tidy as GHC -import qualified GHC.Data.Strict as Strict -import GHC.Driver.Env as GHCi -import qualified GHC.Unit.Finder as GHC -import qualified GHC.Driver.Config.Finder as GHC +import qualified GHC.Data.Strict as Strict +import qualified GHC.Driver.Config.Finder as GHC +import qualified GHC.Driver.Config.Tidy as GHC +import GHC.Driver.Env as GHCi +import GHC.Driver.Env.KnotVars +import GHC.Driver.Errors.Types +import GHC.Types.Unique +import GHC.Types.Unique.Map +import GHC.Unit.Env +import qualified GHC.Unit.Finder as GHC +import GHC.Unit.Finder.Types +import GHC.Unit.Module.Graph +import GHC.Utils.Error (mkPlainErrorMsgEnvelope) +import GHC.Utils.Panic +import GHC.Utils.TmpFs +#endif + +#if !MIN_VERSION_ghc(9,7,0) +import GHC.Types.Avail (greNamePrintableName) #endif mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO Module.ModLocation @@ -627,6 +626,7 @@ pattern ExposePackage s a mr <- DynFlags.ExposePackage s a _ mr pattern ExposePackage s a mr = DynFlags.ExposePackage s a mr #endif +isVisibleFunArg :: Development.IDE.GHC.Compat.Core.FunTyFlag -> Bool #if __GLASGOW_HASKELL__ >= 906 isVisibleFunArg = TypesVar.isVisibleFunArg type FunTyFlag = TypesVar.FunTyFlag @@ -729,12 +729,15 @@ makeSimpleDetails hsc_env = hsc_env #endif -mkIfaceTc hsc_env sf details _ms tcGblEnv = -- ms is only used in GHC >= 9.4 - GHC.mkIfaceTc hsc_env sf details -#if MIN_VERSION_ghc(9,3,0) - _ms +mkIfaceTc :: HscEnv -> GHC.SafeHaskellMode -> ModDetails -> ModSummary -> Maybe CoreProgram -> TcGblEnv -> IO ModIface +mkIfaceTc hscEnv shm md _ms _mcp = +#if MIN_VERSION_ghc(9,5,0) + GHC.mkIfaceTc hscEnv shm md _ms _mcp -- mcp::Maybe CoreProgram is only used in GHC >= 9.6 +#elif MIN_VERSION_ghc(9,3,0) + GHC.mkIfaceTc hscEnv shm md _ms -- ms::ModSummary is only used in GHC >= 9.4 +#else + GHC.mkIfaceTc hscEnv shm md #endif - tcGblEnv mkBootModDetailsTc :: HscEnv -> TcGblEnv -> IO ModDetails mkBootModDetailsTc session = GHC.mkBootModDetailsTc @@ -756,11 +759,12 @@ initTidyOpts = pure #endif -driverNoStop = #if MIN_VERSION_ghc(9,3,0) - NoStop +driverNoStop :: StopPhase +driverNoStop = NoStop #else - StopLn +driverNoStop :: Phase +driverNoStop = StopLn #endif #if !MIN_VERSION_ghc(9,3,0) @@ -779,15 +783,14 @@ pattern NamedFieldPuns :: Extension pattern NamedFieldPuns = RecordPuns #endif +groupOrigin :: MatchGroup GhcRn body -> Origin #if MIN_VERSION_ghc(9,5,0) -mkVisFunTys = mkScaledFunctionTys mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b mapLoc = fmap groupOrigin = mg_ext #else mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b mapLoc = SrcLoc.mapLoc -groupOrigin :: MatchGroup p body -> Origin groupOrigin = mg_origin #endif diff --git a/ghcide/src/Development/IDE/GHC/Compat/Env.hs b/ghcide/src/Development/IDE/GHC/Compat/Env.hs index 7b4125bea9..bc963e2104 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Env.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Env.hs @@ -32,7 +32,7 @@ module Development.IDE.GHC.Compat.Env ( Home.mkHomeModule, -- * Provide backwards Compatible -- types and helper functions. - Logger(..), + Logger, UnitEnv, hscSetUnitEnv, hscSetFlags, @@ -63,8 +63,6 @@ module Development.IDE.GHC.Compat.Env ( import GHC (setInteractiveDynFlags) --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - import GHC.Driver.Backend as Backend import qualified GHC.Driver.Env as Env import GHC.Driver.Hooks (Hooks) @@ -78,9 +76,11 @@ import GHC.Unit.Types (UnitId) import GHC.Utils.Logger import GHC.Utils.TmpFs +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if !MIN_VERSION_ghc(9,3,0) -import GHC.Driver.Env (HscEnv, hsc_EPS) import qualified Data.Set as S +import GHC.Driver.Env (HscEnv, hsc_EPS) #endif #if MIN_VERSION_ghc(9,3,0) diff --git a/ghcide/src/Development/IDE/GHC/Compat/Iface.hs b/ghcide/src/Development/IDE/GHC/Compat/Iface.hs index d848083a4b..7a5fc10029 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Iface.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Iface.hs @@ -9,22 +9,20 @@ module Development.IDE.GHC.Compat.Iface ( import Development.IDE.GHC.Compat.Env import Development.IDE.GHC.Compat.Outputable import GHC +import qualified GHC.Iface.Load as Iface +import GHC.Unit.Finder.Types (FindResult) -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] +#if MIN_VERSION_ghc(9,3,0) +import GHC.Driver.Session (targetProfile) +#endif + #if MIN_VERSION_ghc(9,7,0) import GHC.Iface.Errors.Ppr (missingInterfaceErrorDiagnostic) import GHC.Iface.Errors.Types (IfaceMessage) #endif - -import qualified GHC.Iface.Load as Iface -import GHC.Unit.Finder.Types (FindResult) - -#if MIN_VERSION_ghc(9,3,0) -import GHC.Driver.Session (targetProfile) -#endif - writeIfaceFile :: HscEnv -> FilePath -> ModIface -> IO () #if MIN_VERSION_ghc(9,3,0) writeIfaceFile env fp iface = Iface.writeIface (hsc_logger env) (targetProfile $ hsc_dflags env) fp iface diff --git a/ghcide/src/Development/IDE/GHC/Compat/Logger.hs b/ghcide/src/Development/IDE/GHC/Compat/Logger.hs index b89dea0488..24922069ec 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Logger.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Logger.hs @@ -13,11 +13,11 @@ import Development.IDE.GHC.Compat.Core import Development.IDE.GHC.Compat.Env as Env import Development.IDE.GHC.Compat.Outputable --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] +import GHC.Utils.Logger as Logger import GHC.Utils.Outputable -import GHC.Utils.Logger as Logger +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if MIN_VERSION_ghc(9,3,0) import GHC.Types.Error diff --git a/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs b/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs index f14dbdced1..c751f7ae0b 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs @@ -10,7 +10,7 @@ module Development.IDE.GHC.Compat.Outputable ( printSDocQualifiedUnsafe, printWithoutUniques, mkPrintUnqualifiedDefault, - PrintUnqualified(..), + PrintUnqualified, defaultUserStyle, withPprStyle, -- * Parser errors @@ -53,40 +53,41 @@ module Development.IDE.GHC.Compat.Outputable ( textDoc, ) where --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - import GHC.Driver.Env import GHC.Driver.Ppr import GHC.Driver.Session import qualified GHC.Types.Error as Error -#if MIN_VERSION_ghc(9,7,0) -import GHC.Types.Error (defaultDiagnosticOpts) -#endif import GHC.Types.Name.Ppr import GHC.Types.Name.Reader import GHC.Types.SourceError import GHC.Types.SrcLoc import GHC.Unit.State -import GHC.Utils.Error hiding (mkWarnMsg) import GHC.Utils.Outputable as Out import GHC.Utils.Panic +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if !MIN_VERSION_ghc(9,3,0) import GHC.Parser.Errors import qualified GHC.Parser.Errors.Ppr as Ppr +import GHC.Utils.Error hiding (mkWarnMsg) #endif #if MIN_VERSION_ghc(9,3,0) import Data.Maybe import GHC.Driver.Config.Diagnostic import GHC.Parser.Errors.Types +import GHC.Utils.Error #endif #if MIN_VERSION_ghc(9,5,0) import GHC.Driver.Errors.Types (DriverMessage, GhcMessage) #endif +#if MIN_VERSION_ghc(9,7,0) +import GHC.Types.Error (defaultDiagnosticOpts) +#endif + #if MIN_VERSION_ghc(9,5,0) type PrintUnqualified = NamePprCtx #endif diff --git a/ghcide/src/Development/IDE/GHC/Compat/Parser.hs b/ghcide/src/Development/IDE/GHC/Compat/Parser.hs index 2b92076532..0dc40673bc 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Parser.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Parser.hs @@ -27,9 +27,6 @@ module Development.IDE.GHC.Compat.Parser ( import Development.IDE.GHC.Compat.Core import Development.IDE.GHC.Compat.Util - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - import qualified GHC.Parser.Annotation as Anno import qualified GHC.Parser.Lexer as Lexer import GHC.Types.SrcLoc (PsSpan (..)) @@ -43,6 +40,8 @@ import GHC (EpaCommentTok (..), import qualified GHC import GHC.Hs (hpm_module, hpm_src_files) +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if !MIN_VERSION_ghc(9,3,0) import qualified GHC.Driver.Config as Config #endif diff --git a/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs b/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs index 09c4ff720a..c8c96b1e1f 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs @@ -23,8 +23,7 @@ import Development.IDE.GHC.Compat.Core import Development.IDE.GHC.Compat.Env (hscSetFlags, hsc_dflags) import Development.IDE.GHC.Compat.Parser as Parser --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - +import qualified GHC.Driver.Env as Env import GHC.Driver.Plugins (Plugin (..), PluginWithArgs (..), StaticPlugin (..), @@ -32,17 +31,11 @@ import GHC.Driver.Plugins (Plugin (..), withPlugins) import qualified GHC.Runtime.Loader as Loader -#if !MIN_VERSION_ghc(9,3,0) -import Development.IDE.GHC.Compat.Outputable as Out -#endif - -import qualified GHC.Driver.Env as Env +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if !MIN_VERSION_ghc(9,3,0) import Data.Bifunctor (bimap) -#endif - -#if !MIN_VERSION_ghc(9,3,0) +import Development.IDE.GHC.Compat.Outputable as Out import Development.IDE.GHC.Compat.Util (Bag) #endif @@ -53,23 +46,20 @@ import GHC.Driver.Plugins (ParsedResult (..), import qualified GHC.Parser.Lexer as Lexer #endif - #if !MIN_VERSION_ghc(9,3,0) type PsMessages = (Bag WarnMsg, Bag ErrMsg) #endif -getPsMessages :: PState -> DynFlags -> PsMessages -getPsMessages pst _dflags = --dfags is only used if GHC < 9.2 +getPsMessages :: PState -> PsMessages +getPsMessages pst = #if MIN_VERSION_ghc(9,3,0) uncurry PsMessages $ Lexer.getPsMessages pst #else - bimap (fmap pprWarning) (fmap pprError) $ - getMessages pst + bimap (fmap pprWarning) (fmap pprError) $ getMessages pst #endif -applyPluginsParsedResultAction :: HscEnv -> DynFlags -> ModSummary -> Parser.ApiAnns -> ParsedSource -> PsMessages -> IO (ParsedSource, PsMessages) -applyPluginsParsedResultAction env _dflags ms hpm_annotations parsed msgs = do - -- dflags is only used in GHC < 9.2 +applyPluginsParsedResultAction :: HscEnv -> ModSummary -> Parser.ApiAnns -> ParsedSource -> PsMessages -> IO (ParsedSource, PsMessages) +applyPluginsParsedResultAction env ms hpm_annotations parsed msgs = do -- Apply parsedResultAction of plugins let applyPluginAction p opts = parsedResultAction p opts ms #if MIN_VERSION_ghc(9,3,0) diff --git a/ghcide/src/Development/IDE/GHC/Compat/Units.hs b/ghcide/src/Development/IDE/GHC/Compat/Units.hs index b0b677743d..0456e3135a 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Units.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Units.hs @@ -36,7 +36,7 @@ module Development.IDE.GHC.Compat.Units ( installedModule, -- * Module toUnitId, - Development.IDE.GHC.Compat.Units.moduleUnitId, + moduleUnitId, moduleUnit, -- * ExternalPackageState ExternalPackageState(..), @@ -53,9 +53,10 @@ import Development.IDE.GHC.Compat.Env import Development.IDE.GHC.Compat.Outputable import Prelude hiding (mod) --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - +import qualified GHC.Data.ShortText as ST import GHC.Types.Unique.Set +import GHC.Unit.External +import qualified GHC.Unit.Finder as GHC import qualified GHC.Unit.Info as UnitInfo import GHC.Unit.State (LookupResult, UnitInfo, UnitInfoMap, @@ -67,22 +68,15 @@ import GHC.Unit.State (LookupResult, UnitInfo, unitPackageVersion) import qualified GHC.Unit.State as State import GHC.Unit.Types -import qualified GHC.Unit.Types as Unit +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if !MIN_VERSION_ghc(9,3,0) import GHC.Data.FastString - -#endif - -import qualified GHC.Data.ShortText as ST -import GHC.Unit.External -import qualified GHC.Unit.Finder as GHC - -#if !MIN_VERSION_ghc(9,3,0) import GHC.Unit.Env import GHC.Unit.Finder hiding (findImportedModule) +import qualified GHC.Unit.Types as Unit #endif #if MIN_VERSION_ghc(9,3,0) @@ -210,10 +204,10 @@ defUnitId = Definite installedModule :: unit -> ModuleName -> GenModule unit installedModule = Module - +#if !MIN_VERSION_ghc(9,3,0) moduleUnitId :: Module -> UnitId -moduleUnitId = - Unit.toUnitId . Unit.moduleUnit +moduleUnitId = Unit.toUnitId . Unit.moduleUnit +#endif filterInplaceUnits :: [UnitId] -> [PackageFlag] -> ([UnitId], [PackageFlag]) filterInplaceUnits us packageFlags = diff --git a/ghcide/src/Development/IDE/GHC/Compat/Util.hs b/ghcide/src/Development/IDE/GHC/Compat/Util.hs index 708f2af0c2..2c60c35b15 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Util.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Util.hs @@ -66,13 +66,10 @@ module Development.IDE.GHC.Compat.Util ( atEnd, ) where --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - import Control.Exception.Safe (MonadCatch, catch, try) import GHC.Data.Bag import GHC.Data.BooleanFormula import GHC.Data.EnumSet - import GHC.Data.FastString import GHC.Data.Maybe import GHC.Data.Pair @@ -83,6 +80,8 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable (pprHsString) import GHC.Utils.Panic hiding (try) +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if !MIN_VERSION_ghc(9,3,0) import GHC.Utils.Misc #endif @@ -90,4 +89,3 @@ import GHC.Utils.Misc #if MIN_VERSION_ghc(9,3,0) import GHC.Data.Bool #endif - diff --git a/ghcide/src/Development/IDE/GHC/CoreFile.hs b/ghcide/src/Development/IDE/GHC/CoreFile.hs index ae7f8213e7..ec210a1207 100644 --- a/ghcide/src/Development/IDE/GHC/CoreFile.hs +++ b/ghcide/src/Development/IDE/GHC/CoreFile.hs @@ -21,22 +21,17 @@ import Data.Maybe import qualified Data.Text as T import Development.IDE.GHC.Compat import qualified Development.IDE.GHC.Compat.Util as Util -import GHC.Fingerprint -import Prelude hiding (mod) - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - import GHC.Core import GHC.CoreToIface +import GHC.Fingerprint import GHC.Iface.Binary import GHC.Iface.Env import GHC.Iface.Recomp.Binary (fingerprintBinMem) import GHC.IfaceToCore import GHC.Types.Id.Make -import GHC.Utils.Binary - - import GHC.Types.TypeEnv +import GHC.Utils.Binary +import Prelude hiding (mod) -- | Initial ram buffer to allocate for writing interface files diff --git a/ghcide/src/Development/IDE/GHC/Orphans.hs b/ghcide/src/Development/IDE/GHC/Orphans.hs index d8460d5fca..63f663840c 100644 --- a/ghcide/src/Development/IDE/GHC/Orphans.hs +++ b/ghcide/src/Development/IDE/GHC/Orphans.hs @@ -11,34 +11,37 @@ import Development.IDE.GHC.Compat import Development.IDE.GHC.Util import Control.DeepSeq -import Control.Monad.Trans.Reader (ReaderT (..)) +import Control.Monad.Trans.Reader (ReaderT (..)) import Data.Aeson import Data.Hashable -import Data.String (IsString (fromString)) -import Data.Text (unpack) - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] +import Data.String (IsString (fromString)) +import Data.Text (unpack) import GHC.ByteCode.Types import GHC.Data.Bag import GHC.Data.FastString -import qualified GHC.Data.StringBuffer as SB +import qualified GHC.Data.StringBuffer as SB import GHC.Types.SrcLoc +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if !MIN_VERSION_ghc(9,3,0) -import GHC (ModuleGraph) -import GHC.Types.Unique (getKey) +import GHC.Types.Unique (getKey) +import GHC.Unit.Module.Graph (ModuleGraph) #endif -import Data.Bifunctor (Bifunctor (..)) +import Data.Bifunctor (Bifunctor (..)) import GHC.Parser.Annotation #if MIN_VERSION_ghc(9,3,0) import GHC.Types.PkgQual + #endif #if MIN_VERSION_ghc(9,5,0) import GHC.Unit.Home.ModInfo +import GHC.Unit.Module.Location (ModLocation (..)) +import GHC.Unit.Module.WholeCoreBindings #endif -- Orphan instance for Shake.hs @@ -56,11 +59,22 @@ instance NFData SafeHaskellMode where rnf = rwhnf instance Show Linkable where show = unpack . printOutputable instance NFData Linkable where rnf (LM a b c) = rnf a `seq` rnf b `seq` rnf c instance NFData Unlinked where - rnf (DotO f) = rnf f - rnf (DotA f) = rnf f - rnf (DotDLL f) = rnf f - rnf (BCOs a b) = seqCompiledByteCode a `seq` liftRnf rwhnf b - rnf _ = error "rnf: not implemented for Unlinked" + rnf (DotO f) = rnf f + rnf (DotA f) = rnf f + rnf (DotDLL f) = rnf f + rnf (BCOs a b) = seqCompiledByteCode a `seq` liftRnf rwhnf b +#if MIN_VERSION_ghc(9,5,0) + rnf (CoreBindings wcb) = rnf wcb + rnf (LoadedBCOs us) = rnf us + +instance NFData WholeCoreBindings where + rnf (WholeCoreBindings bs m ml) = rnf bs `seq` rnf m `seq` rnf ml + +instance NFData ModLocation where + rnf (ModLocation mf f1 f2 f3 f4 f5) = rnf mf `seq` rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf f5 + +#endif + instance Show PackageFlag where show = unpack . printOutputable instance Show InteractiveImport where show = unpack . printOutputable instance Show PackageName where show = unpack . printOutputable diff --git a/ghcide/src/Development/IDE/GHC/Util.hs b/ghcide/src/Development/IDE/GHC/Util.hs index 75ee2cf49d..03384aec92 100644 --- a/ghcide/src/Development/IDE/GHC/Util.hs +++ b/ghcide/src/Development/IDE/GHC/Util.hs @@ -62,9 +62,6 @@ import GHC.IO.Handle.Types import Ide.PluginUtils (unescape) import System.FilePath --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - import GHC.Data.EnumSet import GHC.Data.FastString import GHC.Data.StringBuffer diff --git a/ghcide/src/Development/IDE/Import/DependencyInformation.hs b/ghcide/src/Development/IDE/Import/DependencyInformation.hs index 6ae27e2912..95478fa25c 100644 --- a/ghcide/src/Development/IDE/Import/DependencyInformation.hs +++ b/ghcide/src/Development/IDE/Import/DependencyInformation.hs @@ -60,7 +60,7 @@ import Development.IDE.GHC.Compat -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if !MIN_VERSION_ghc(9,3,0) -import GHC +import GHC.Unit.Module.Graph (ModuleGraph) #endif -- | The imports for a given module. diff --git a/ghcide/src/Development/IDE/Import/FindImports.hs b/ghcide/src/Development/IDE/Import/FindImports.hs index ff6c7f90cd..6140199772 100644 --- a/ghcide/src/Development/IDE/Import/FindImports.hs +++ b/ghcide/src/Development/IDE/Import/FindImports.hs @@ -239,7 +239,7 @@ notFoundErr env modName reason = LookupUnusable unusable -> let unusables' = map get_unusable unusable #if MIN_VERSION_ghc(9,6,4) && (!MIN_VERSION_ghc(9,8,1) || MIN_VERSION_ghc(9,8,2)) - get_unusable (m, ModUnusable r) = r + get_unusable (_m, ModUnusable r) = r #else get_unusable (m, ModUnusable r) = (moduleUnit m, r) #endif diff --git a/ghcide/src/Development/IDE/LSP/HoverDefinition.hs b/ghcide/src/Development/IDE/LSP/HoverDefinition.hs index 0401247ac5..9c8876a554 100644 --- a/ghcide/src/Development/IDE/LSP/HoverDefinition.hs +++ b/ghcide/src/Development/IDE/LSP/HoverDefinition.hs @@ -20,7 +20,7 @@ import Data.Maybe (fromMaybe) import Development.IDE.Core.Actions import qualified Development.IDE.Core.Rules as Shake import Development.IDE.Core.Shake (IdeAction, IdeState (..), - ideLogger, runIdeAction) + runIdeAction) import Development.IDE.Types.Location import Ide.Logger import Ide.Plugin.Error diff --git a/ghcide/src/Development/IDE/LSP/LanguageServer.hs b/ghcide/src/Development/IDE/LSP/LanguageServer.hs index e4493436cb..76893c38a0 100644 --- a/ghcide/src/Development/IDE/LSP/LanguageServer.hs +++ b/ghcide/src/Development/IDE/LSP/LanguageServer.hs @@ -34,7 +34,7 @@ import UnliftIO.Exception import qualified Colog.Core as Colog import Control.Monad.IO.Unlift (MonadUnliftIO) import Development.IDE.Core.IdeConfiguration -import Development.IDE.Core.Shake hiding (Log, Priority) +import Development.IDE.Core.Shake hiding (Log) import Development.IDE.Core.Tracing import qualified Development.IDE.Session as Session import Development.IDE.Types.Shake (WithHieDb) diff --git a/ghcide/src/Development/IDE/LSP/Notifications.hs b/ghcide/src/Development/IDE/LSP/Notifications.hs index 06402f67ae..4f5475442c 100644 --- a/ghcide/src/Development/IDE/LSP/Notifications.hs +++ b/ghcide/src/Development/IDE/LSP/Notifications.hs @@ -31,7 +31,7 @@ import qualified Development.IDE.Core.FileStore as FileStore import Development.IDE.Core.IdeConfiguration import Development.IDE.Core.OfInterest hiding (Log, LogShake) import Development.IDE.Core.Service hiding (Log, LogShake) -import Development.IDE.Core.Shake hiding (Log, Priority) +import Development.IDE.Core.Shake hiding (Log) import qualified Development.IDE.Core.Shake as Shake import Development.IDE.Types.Location import Ide.Logger diff --git a/ghcide/src/Development/IDE/LSP/Outline.hs b/ghcide/src/Development/IDE/LSP/Outline.hs index 4f350b52d0..8d466a61a6 100644 --- a/ghcide/src/Development/IDE/LSP/Outline.hs +++ b/ghcide/src/Development/IDE/LSP/Outline.hs @@ -9,8 +9,10 @@ module Development.IDE.LSP.Outline where import Control.Monad.IO.Class +import Data.Foldable (toList) import Data.Functor import Data.Generics hiding (Prefix) +import Data.List.NonEmpty (nonEmpty) import Data.Maybe import Development.IDE.Core.Rules import Development.IDE.Core.Shake @@ -29,9 +31,6 @@ import Language.LSP.Protocol.Message -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] -import Data.List.NonEmpty (nonEmpty) -import Data.Foldable (toList) - #if !MIN_VERSION_ghc(9,3,0) import qualified Data.Text as T #endif diff --git a/ghcide/src/Development/IDE/Main.hs b/ghcide/src/Development/IDE/Main.hs index d3fb7dd852..04d4b4cb42 100644 --- a/ghcide/src/Development/IDE/Main.hs +++ b/ghcide/src/Development/IDE/Main.hs @@ -34,8 +34,7 @@ import Data.Maybe (catMaybes, isJust) import qualified Data.Text as T import Development.IDE (Action, Priority (Debug, Error), - Rules, emptyFilePath, - hDuplicateTo') + Rules, hDuplicateTo') import Development.IDE.Core.Debouncer (Debouncer, newAsyncDebouncer) import Development.IDE.Core.FileStore (isWatchSupported, @@ -88,10 +87,9 @@ import Development.IDE.Types.Options (IdeGhcSession, defaultIdeOptions, optModifyDynFlags, optTesting) -import Development.IDE.Types.Shake (WithHieDb, toKey, +import Development.IDE.Types.Shake (WithHieDb, toNoFileKey) -import GHC.Conc (atomically, - getNumProcessors) +import GHC.Conc (getNumProcessors) import GHC.IO.Encoding (setLocaleEncoding) import GHC.IO.Handle (hDuplicate) import HIE.Bios.Cradle (findCradle) diff --git a/ghcide/src/Development/IDE/Plugin/Completions.hs b/ghcide/src/Development/IDE/Plugin/Completions.hs index e7cd60a10b..7f68fc2599 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions.hs @@ -56,8 +56,6 @@ import Development.IDE.Core.Rules (usePropertyAction) import qualified Ide.Plugin.Config as Config --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - import qualified GHC.LanguageExtensions as LangExt data Log = LogShake Shake.Log deriving Show diff --git a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs index 99fe6e6294..145e9a2b37 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs @@ -22,7 +22,6 @@ import Data.Generics import Data.List.Extra as List hiding (stripPrefix) import qualified Data.Map as Map -import Data.Row import Prelude hiding (mod) import Data.Maybe (fromMaybe, isJust, @@ -66,13 +65,14 @@ import Development.IDE hiding (line) import Development.IDE.Spans.AtPoint (pointCommand) --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] import GHC.Plugins (Depth (AllTheWay), mkUserStyle, neverQualify, sdocStyle) +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] + #if !MIN_VERSION_ghc(9,3,0) import GHC.Plugins (defaultSDocContext, renderWithContext) diff --git a/ghcide/src/Development/IDE/Plugin/Completions/Types.hs b/ghcide/src/Development/IDE/Plugin/Completions/Types.hs index f2b3be0712..2d950d66a9 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions/Types.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions/Types.hs @@ -21,14 +21,11 @@ import Development.IDE.GHC.Compat import Development.IDE.Graph (RuleResult) import Development.IDE.Spans.Common () import GHC.Generics (Generic) +import qualified GHC.Types.Name.Occurrence as Occ import Ide.Plugin.Properties import Language.LSP.Protocol.Types (CompletionItemKind (..), Uri) import qualified Language.LSP.Protocol.Types as J --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - -import qualified GHC.Types.Name.Occurrence as Occ - -- | Produce completions info for a file type instance RuleResult LocalCompletions = CachedCompletions type instance RuleResult NonLocalCompletions = CachedCompletions diff --git a/ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs b/ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs index 319b75d031..ec5c6bf84b 100644 --- a/ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs +++ b/ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs @@ -7,7 +7,7 @@ module Development.IDE.Plugin.HLS.GhcIde descriptors , Log(..) ) where -import Control.Monad.IO.Class + import Development.IDE import qualified Development.IDE.LSP.HoverDefinition as Hover import qualified Development.IDE.LSP.Notifications as Notifications diff --git a/ghcide/src/Development/IDE/Spans/AtPoint.hs b/ghcide/src/Development/IDE/Spans/AtPoint.hs index 5bff7d62f5..434c684b96 100644 --- a/ghcide/src/Development/IDE/Spans/AtPoint.hs +++ b/ghcide/src/Development/IDE/Spans/AtPoint.hs @@ -56,7 +56,6 @@ import Data.List (isSuffixOf) import Data.List.Extra (dropEnd1, nubOrd) import Data.Version (showVersion) -import Development.IDE.GHC.Compat (getSourceNodeIds) import Development.IDE.Types.Shake (WithHieDb) import HieDb hiding (pointCommand, withHieDb) diff --git a/ghcide/src/Development/IDE/Spans/LocalBindings.hs b/ghcide/src/Development/IDE/Spans/LocalBindings.hs index 0fd74cf0dc..8ca811eaa0 100644 --- a/ghcide/src/Development/IDE/Spans/LocalBindings.hs +++ b/ghcide/src/Development/IDE/Spans/LocalBindings.hs @@ -22,7 +22,8 @@ import Development.IDE.GHC.Compat (Name, NameEnv, RealSrcSpan, getBindSiteFromContext, getScopeFromContext, identInfo, identType, isSystemName, - nameEnvElts, realSrcSpanEnd, + nonDetNameEnvElts, + realSrcSpanEnd, realSrcSpanStart, unitNameEnv) import Development.IDE.GHC.Error @@ -99,7 +100,7 @@ instance Show Bindings where -- 'RealSrcSpan', getLocalScope :: Bindings -> RealSrcSpan -> [(Name, Maybe Type)] getLocalScope bs rss - = nameEnvElts + = nonDetNameEnvElts $ foldMap snd $ IM.dominators (realSrcSpanToInterval rss) $ getLocalBindings bs @@ -109,7 +110,7 @@ getLocalScope bs rss -- 'RealSrcSpan', getDefiningBindings :: Bindings -> RealSrcSpan -> [(Name, Maybe Type)] getDefiningBindings bs rss - = nameEnvElts + = nonDetNameEnvElts $ foldMap snd $ IM.dominators (realSrcSpanToInterval rss) $ getBindingSites bs @@ -121,7 +122,7 @@ getDefiningBindings bs rss getFuzzyScope :: Bindings -> Position -> Position -> [(Name, Maybe Type)] getFuzzyScope bs a b = filter (not . isSystemName . fst) - $ nameEnvElts + $ nonDetNameEnvElts $ foldMap snd $ IM.intersections (Interval a b) $ getLocalBindings bs @@ -133,7 +134,7 @@ getFuzzyScope bs a b -- `PositionMapping` getFuzzyDefiningBindings :: Bindings -> Position -> Position -> [(Name, Maybe Type)] getFuzzyDefiningBindings bs a b - = nameEnvElts + = nonDetNameEnvElts $ foldMap snd $ IM.intersections (Interval a b) $ getBindingSites bs diff --git a/ghcide/src/Development/IDE/Types/Location.hs b/ghcide/src/Development/IDE/Types/Location.hs index 7623c1cf25..06ca9cbeca 100644 --- a/ghcide/src/Development/IDE/Types/Location.hs +++ b/ghcide/src/Development/IDE/Types/Location.hs @@ -2,7 +2,6 @@ -- SPDX-License-Identifier: Apache-2.0 {-# LANGUAGE CPP #-} - -- | Types and functions for working with source code locations. module Development.IDE.Types.Location ( Location(..) @@ -36,8 +35,6 @@ import Language.LSP.Protocol.Types (Location (..), Position (..), import qualified Language.LSP.Protocol.Types as LSP import Text.ParserCombinators.ReadP as ReadP --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - import GHC.Data.FastString import GHC.Types.SrcLoc as GHC diff --git a/ghcide/src/Development/IDE/Types/Shake.hs b/ghcide/src/Development/IDE/Types/Shake.hs index 36ba151762..7b3a70d14f 100644 --- a/ghcide/src/Development/IDE/Types/Shake.hs +++ b/ghcide/src/Development/IDE/Types/Shake.hs @@ -7,7 +7,7 @@ module Development.IDE.Types.Shake Value (..), ValueWithDiagnostics (..), Values, - Key (..), + Key, BadDependency (..), ShakeValue(..), currentValue, diff --git a/ghcide/test/exe/FindDefinitionAndHoverTests.hs b/ghcide/test/exe/FindDefinitionAndHoverTests.hs index 68ca0d3350..b50f4081ff 100644 --- a/ghcide/test/exe/FindDefinitionAndHoverTests.hs +++ b/ghcide/test/exe/FindDefinitionAndHoverTests.hs @@ -12,19 +12,12 @@ import qualified Language.LSP.Protocol.Lens as L import Language.LSP.Test import System.Info.Extra (isWindows) -import Control.Lens ((^.)) -import Test.Tasty -import Test.Tasty.HUnit --- import TestUtils import Config -import Debug.Trace (traceM) -import Development.IDE (readFileUtf8) +import Control.Lens ((^.)) import Development.IDE.Test (expectDiagnostics, standardizeQuotes) -import System.Directory (copyFile) -import System.FilePath (()) import Test.Hls -import Test.Hls.FileSystem (copy, copyDir, file, toAbsFp) +import Test.Hls.FileSystem (copyDir) import Text.Regex.TDFA ((=~)) tests :: TestTree diff --git a/ghcide/test/exe/Main.hs b/ghcide/test/exe/Main.hs index 2dd21838cc..8c6f876f39 100644 --- a/ghcide/test/exe/Main.hs +++ b/ghcide/test/exe/Main.hs @@ -32,8 +32,7 @@ module Main (main) where -- import Test.QuickCheck.Instances () import Data.Function ((&)) import qualified HieDbRetry -import Ide.Logger (LoggingColumn (DataColumn, PriorityColumn), - Pretty (pretty), +import Ide.Logger (Pretty (pretty), Priority (Debug), WithPriority (WithPriority, priority), cfilter, cmapWithPrio, diff --git a/ghcide/test/exe/TestUtils.hs b/ghcide/test/exe/TestUtils.hs index 0a13dd9717..140d48df10 100644 --- a/ghcide/test/exe/TestUtils.hs +++ b/ghcide/test/exe/TestUtils.hs @@ -1,6 +1,5 @@ -{-# LANGUAGE GADTs #-} -{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE GADTs #-} module TestUtils where @@ -11,16 +10,12 @@ import Control.Lens ((.~)) import qualified Control.Lens as Lens import qualified Control.Lens.Extras as Lens import Control.Monad -import Control.Monad.IO.Class (liftIO) import Data.Foldable import Data.Function ((&)) import Data.Maybe -import qualified Data.Text as T import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion) -import Development.IDE.GHC.Util import qualified Development.IDE.Main as IDE -import Development.IDE.Test (canonicalizeUri, - configureCheckProject, +import Development.IDE.Test (configureCheckProject, expectNoMoreDiagnostics) import Development.IDE.Test.Runfiles import Development.IDE.Types.Location diff --git a/haskell-language-server.cabal b/haskell-language-server.cabal index 49ba2f5a41..bbe36a733a 100644 --- a/haskell-language-server.cabal +++ b/haskell-language-server.cabal @@ -14,7 +14,7 @@ copyright: The Haskell IDE Team license: Apache-2.0 license-file: LICENSE build-type: Simple -tested-with: GHC == 9.8.2 || ==9.6.4 || ==9.4.8 || ==9.2.8 +tested-with: GHC ==9.8.2 || ==9.6.5 || ==9.4.8 || ==9.2.8 extra-source-files: README.md ChangeLog.md @@ -258,7 +258,6 @@ library hls-cabal-plugin , lsp ^>=2.5 , lsp-types ^>=2.2 , regex-tdfa ^>=1.3.1 - , stm , text , text-rope , transformers @@ -408,7 +407,6 @@ test-suite hls-call-hierarchy-plugin-tests , filepath , haskell-language-server:hls-call-hierarchy-plugin , hls-test-utils == 2.8.0.0 - , ghcide:ghcide-test-utils , lens , lsp , lsp-test @@ -1688,7 +1686,7 @@ test-suite hls-refactor-plugin-tests , parser-combinators , data-default , extra - , ghcide:{ghcide, ghcide-test-utils} + , ghcide:ghcide , shake , hls-plugin-api , lsp-test @@ -1768,7 +1766,6 @@ test-suite hls-semantic-tokens-plugin-tests , filepath , haskell-language-server:hls-semantic-tokens-plugin , hls-test-utils == 2.8.0.0 - , ghcide:ghcide-test-utils , hls-plugin-api , lens , lsp @@ -1833,7 +1830,6 @@ test-suite hls-notes-plugin-tests , base , directory , filepath - , ghcide:ghcide-test-utils , haskell-language-server:hls-notes-plugin , hls-test-utils == 2.8.0.0 default-extensions: OverloadedStrings @@ -2003,7 +1999,7 @@ test-suite func-test , deepseq , extra , filepath - , ghcide:{ghcide, ghcide-test-utils} + , ghcide:ghcide , hashable , hls-plugin-api , hls-test-utils == 2.8.0.0 @@ -2276,8 +2272,7 @@ test-suite ghcide-bench-test lsp-test ^>= 0.17, tasty, tasty-hunit >= 0.10, - tasty-rerun, - hls-test-utils + tasty-rerun default-extensions: LambdaCase OverloadedStrings diff --git a/hls-test-utils/hls-test-utils.cabal b/hls-test-utils/hls-test-utils.cabal index dbddcefd57..f6233a08aa 100644 --- a/hls-test-utils/hls-test-utils.cabal +++ b/hls-test-utils/hls-test-utils.cabal @@ -57,7 +57,7 @@ library , temporary , text - ghc-options: -Wall -Wunused-packages + ghc-options: -Wall -Wunused-packages -Wno-name-shadowing if flag(pedantic) ghc-options: -Werror diff --git a/hls-test-utils/src/Development/IDE/Test.hs b/hls-test-utils/src/Development/IDE/Test.hs index b128666ff1..30f951e903 100644 --- a/hls-test-utils/src/Development/IDE/Test.hs +++ b/hls-test-utils/src/Development/IDE/Test.hs @@ -79,7 +79,7 @@ expectNoMoreDiagnostics timeout = expectMessages SMethod_TextDocumentPublishDiagnostics timeout $ \diagsNot -> do let fileUri = diagsNot ^. L.params . L.uri actual = diagsNot ^. L.params . L.diagnostics - unless (actual == []) $ liftIO $ + unless (null actual) $ liftIO $ assertFailure $ "Got unexpected diagnostics for " <> show fileUri <> " got " diff --git a/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Rules.hs b/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Rules.hs index 8c9725a90f..6990c4a6e5 100644 --- a/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Rules.hs +++ b/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Rules.hs @@ -13,21 +13,19 @@ import qualified Data.HashSet as Set import Data.IORef import qualified Data.Map.Strict as Map import Data.String (fromString) -import Development.IDE (GetModSummaryWithoutTimestamps (GetModSummaryWithoutTimestamps), - GetParsedModuleWithComments (GetParsedModuleWithComments), +import Development.IDE (GetParsedModuleWithComments (GetParsedModuleWithComments), IdeState, + LinkableType (BCOLinkable), NeedsCompilation (NeedsCompilation), NormalizedFilePath, RuleBody (RuleNoDiagnostics), Rules, defineEarlyCutoff, encodeLinkableType, fromNormalizedFilePath, - msrModSummary, realSrcSpanToRange, useWithStale_, use_) import Development.IDE.Core.PositionMapping (toCurrentRange) -import Development.IDE.Core.Rules (computeLinkableTypeForDynFlags, - needsCompilationRule) +import Development.IDE.Core.Rules (needsCompilationRule) import Development.IDE.Core.Shake (IsIdeGlobal, RuleBody (RuleWithCustomNewnessCheck), addIdeGlobal, @@ -121,11 +119,10 @@ isEvaluatingRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ redefinedNeedsCompilation :: Recorder (WithPriority Log) -> Rules () redefinedNeedsCompilation recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleWithCustomNewnessCheck (<=) $ \NeedsCompilation f -> do isEvaluating <- use_ IsEvaluating f - - if not isEvaluating then needsCompilationRule f else do - ms <- msrModSummary . fst <$> useWithStale_ GetModSummaryWithoutTimestamps f - let df' = ms_hspp_opts ms - linkableType = computeLinkableTypeForDynFlags df' + if isEvaluating then do + let linkableType = BCOLinkable fp = encodeLinkableType $ Just linkableType - pure (Just fp, Just (Just linkableType)) + else + needsCompilationRule f +