diff --git a/ghcide/session-loader/Development/IDE/Session.hs b/ghcide/session-loader/Development/IDE/Session.hs index d30630d0f..31b1f5965 100644 --- a/ghcide/session-loader/Development/IDE/Session.hs +++ b/ghcide/session-loader/Development/IDE/Session.hs @@ -100,14 +100,17 @@ import Data.Foldable (for_) import Data.HashMap.Strict (HashMap) import Data.HashSet (HashSet) import qualified Data.HashSet as Set +import qualified Data.Set as OS import Database.SQLite.Simple import Development.IDE.Core.Tracing (withTrace) import Development.IDE.Core.WorkerThread (awaitRunInThread, withWorkerQueue) +import qualified Development.IDE.GHC.Compat.Util as Compat import Development.IDE.Session.Diagnostics (renderCradleError) import Development.IDE.Types.Shake (WithHieDb, WithHieDbShield (..), toNoFileKey) +import GHC.Data.Graph.Directed import HieDb.Create import HieDb.Types import HieDb.Utils @@ -116,13 +119,6 @@ import qualified System.Random as Random import System.Random (RandomGen) import Text.ParserCombinators.ReadP (readP_to_S) - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - -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 @@ -832,7 +828,7 @@ checkHomeUnitsClosed' ue home_id_set where go rest this this_uis = plusUniqMap_C OS.union - (addToUniqMap_C OS.union external_depends this (OS.fromList $ this_deps)) + (addToUniqMap_C OS.union external_depends this (OS.fromList this_deps)) rest where external_depends = mapUniqMap (OS.fromList . unitDepends) @@ -1154,7 +1150,7 @@ setOptions cfp (ComponentOptions theOpts compRoot _) dflags rootDir = do -- This works because there won't be any dependencies on the -- executable unit. "main" -> - let hash = B.unpack $ B16.encode $ H.finalize $ H.updates H.init (map B.pack $ this_opts) + let hash = B.unpack $ B16.encode $ H.finalize $ H.updates H.init (map B.pack this_opts) hashed_uid = Compat.toUnitId (Compat.stringToUnit ("main-"++hash)) in setHomeUnitId_ hashed_uid dflags' _ -> dflags' diff --git a/ghcide/src/Development/IDE/Core/Compile.hs b/ghcide/src/Development/IDE/Core/Compile.hs index a8dad581b..a9611902f 100644 --- a/ghcide/src/Development/IDE/Core/Compile.hs +++ b/ghcide/src/Development/IDE/Core/Compile.hs @@ -39,71 +39,78 @@ module Development.IDE.Core.Compile ) where import Control.Concurrent.Extra -import Control.Concurrent.STM.Stats hiding (orElse) -import Control.DeepSeq (NFData (..), force, rnf) -import Control.Exception (evaluate) +import Control.Concurrent.STM.Stats hiding (orElse) +import Control.DeepSeq (NFData (..), force, + rnf) +import Control.Exception (evaluate) import Control.Exception.Safe -import Control.Lens hiding (List, pre, (<.>)) +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) -import Data.Bifunctor (first, second) +import qualified Control.Monad.Trans.State.Strict as S +import Data.Aeson (toJSON) +import Data.Bifunctor (first, second) import Data.Binary -import qualified Data.ByteString as BS +import qualified Data.ByteString as BS import Data.Coerce -import qualified Data.DList as DL +import qualified Data.DList as DL import Data.Functor import Data.Generics.Aliases import Data.Generics.Schemes -import qualified Data.HashMap.Strict as HashMap -import Data.IntMap (IntMap) +import qualified Data.HashMap.Strict as HashMap +import Data.IntMap (IntMap) import Data.IORef import Data.List.Extra -import qualified Data.Map.Strict as Map +import qualified Data.Map.Strict as Map import Data.Maybe -import Data.Proxy (Proxy (Proxy)) -import qualified Data.Text as T -import Data.Time (UTCTime (..)) -import Data.Tuple.Extra (dupe) +import Data.Proxy (Proxy (Proxy)) +import qualified Data.Text as T +import Data.Time (UTCTime (..)) +import Data.Tuple.Extra (dupe) import Debug.Trace -import Development.IDE.Core.FileStore (resetInterfaceStore) +import Development.IDE.Core.FileStore (resetInterfaceStore) import Development.IDE.Core.Preprocessor +import Development.IDE.Core.ProgressReporting (ProgressReporting (..), + progressReportingOutsideState) import Development.IDE.Core.RuleTypes import Development.IDE.Core.Shake -import Development.IDE.Core.Tracing (withTrace) -import Development.IDE.GHC.Compat hiding (assert, - loadInterface, parseHeader, - parseModule, tcRnModule, - writeHieFile) -import qualified Development.IDE.GHC.Compat as Compat -import qualified Development.IDE.GHC.Compat as GHC -import qualified Development.IDE.GHC.Compat.Util as Util -import Development.IDE.Core.ProgressReporting (ProgressReporting (..), progressReportingOutsideState) +import Development.IDE.Core.Tracing (withTrace) +import Development.IDE.GHC.Compat hiding (assert, + loadInterface, + parseHeader, + parseModule, + tcRnModule, + writeHieFile) +import qualified Development.IDE.GHC.Compat as Compat +import qualified Development.IDE.GHC.Compat as GHC +import qualified Development.IDE.GHC.Compat.Util as Util import Development.IDE.GHC.CoreFile import Development.IDE.GHC.Error -import Development.IDE.GHC.Orphans () +import Development.IDE.GHC.Orphans () import Development.IDE.GHC.Util import Development.IDE.GHC.Warnings import Development.IDE.Types.Diagnostics import Development.IDE.Types.Location import Development.IDE.Types.Options -import GHC (ForeignHValue, - GetDocsFailure (..), - parsedSource) -import qualified GHC.LanguageExtensions as LangExt +import GHC (ForeignHValue, + GetDocsFailure (..), + parsedSource) +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.Server as LSP -import Prelude hiding (mod) +import HieDb hiding (withHieDb) +import qualified Language.LSP.Protocol.Message as LSP +import Language.LSP.Protocol.Types (DiagnosticTag (..)) +import qualified Language.LSP.Server as LSP +import Prelude hiding (mod) import System.Directory import System.FilePath -import System.IO.Extra (fixIO, newTempFileWithin) +import System.IO.Extra (fixIO, + newTempFileWithin) -import qualified GHC as G +import qualified Data.Set as Set +import qualified GHC as G import GHC.Tc.Gen.Splice import GHC.Types.ForeignStubs import GHC.Types.HpcInfo @@ -112,18 +119,16 @@ import GHC.Types.TypeEnv -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] -import qualified Data.Set as Set - #if MIN_VERSION_ghc(9,5,0) import GHC.Core.Lint.Interactive import GHC.Driver.Config.CoreToStg.Prep #endif #if MIN_VERSION_ghc(9,7,0) -import Data.Foldable (toList) +import Data.Foldable (toList) import GHC.Unit.Module.Warnings #else -import Development.IDE.Core.FileStore (shareFilePath) +import Development.IDE.Core.FileStore (shareFilePath) #endif --Simple constants to make sure the source is consistently named @@ -292,7 +297,7 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do {- load it -} ; (fv_hvs, lbss, pkgs) <- loadDecls (hscInterp hsc_env') hsc_env' srcspan bcos - ; let hval = ((expectJust "hscCompileCoreExpr'" $ lookup (idName binding_id) fv_hvs), lbss, pkgs) + ; let hval = (expectJust "hscCompileCoreExpr'" $ lookup (idName binding_id) fv_hvs, lbss, pkgs) ; modifyIORef' var (flip extendModuleEnvList [(mi_module $ hm_iface hm, linkableHash lb) | lb <- lbs, let hm = linkableHomeMod lb]) ; return hval } diff --git a/ghcide/src/Development/IDE/Core/Preprocessor.hs b/ghcide/src/Development/IDE/Core/Preprocessor.hs index 188fe39ab..2ef76ad3b 100644 --- a/ghcide/src/Development/IDE/Core/Preprocessor.hs +++ b/ghcide/src/Development/IDE/Core/Preprocessor.hs @@ -28,13 +28,10 @@ import Development.IDE.GHC.Error import Development.IDE.Types.Diagnostics import Development.IDE.Types.Location import qualified GHC.LanguageExtensions as LangExt +import GHC.Utils.Logger (LogFlags (..)) import System.FilePath import System.IO.Extra --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - -import GHC.Utils.Logger (LogFlags (..)) - -- | Given a file and some contents, apply any necessary preprocessors, -- e.g. unlit/cpp. Return the resulting buffer and the DynFlags it implies. preprocessor :: HscEnv -> FilePath -> Maybe Util.StringBuffer -> ExceptT [FileDiagnostic] IO (Util.StringBuffer, [String], HscEnv, Util.Fingerprint) diff --git a/ghcide/src/Development/IDE/Core/Rules.hs b/ghcide/src/Development/IDE/Core/Rules.hs index 582d3b560..590fd59da 100644 --- a/ghcide/src/Development/IDE/Core/Rules.hs +++ b/ghcide/src/Development/IDE/Core/Rules.hs @@ -167,13 +167,8 @@ import System.Directory (doesFileExist) import System.Info.Extra (isWindows) -import GHC.Fingerprint - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - import qualified Data.IntMap as IM - +import GHC.Fingerprint data Log diff --git a/ghcide/src/Development/IDE/Core/Shake.hs b/ghcide/src/Development/IDE/Core/Shake.hs index 7c53b09c7..d8db7f67c 100644 --- a/ghcide/src/Development/IDE/Core/Shake.hs +++ b/ghcide/src/Development/IDE/Core/Shake.hs @@ -126,6 +126,7 @@ import Development.IDE.Core.RuleTypes import Development.IDE.Core.Tracing import Development.IDE.Core.WorkerThread import Development.IDE.GHC.Compat (NameCache, + NameCacheUpdater, initNameCache, knownKeyNames) import Development.IDE.GHC.Orphans () @@ -174,10 +175,6 @@ import System.FilePath hiding (makeRelative) import System.IO.Unsafe (unsafePerformIO) import System.Time.Extra --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - -import Development.IDE.GHC.Compat (NameCacheUpdater) data Log = LogCreateHieDbExportsMapStart diff --git a/ghcide/src/Development/IDE/Core/Tracing.hs b/ghcide/src/Development/IDE/Core/Tracing.hs index b55dcc7af..34839faae 100644 --- a/ghcide/src/Development/IDE/Core/Tracing.hs +++ b/ghcide/src/Development/IDE/Core/Tracing.hs @@ -61,7 +61,7 @@ withTelemetryRecorder k = withSpan "Logger" $ \sp -> -- | Returns a logger that produces telemetry events in a single span. telemetryLogRecorder :: SpanInFlight -> Recorder (WithPriority (Doc a)) telemetryLogRecorder sp = Recorder $ \WithPriority {..} -> - liftIO $ addEvent sp (fromString $ show priority) (encodeUtf8 $ trim $ renderStrict $ layoutCompact $ payload) + liftIO $ addEvent sp (fromString $ show priority) (encodeUtf8 $ trim $ renderStrict $ layoutCompact payload) where -- eventlog message size is limited by EVENT_PAYLOAD_SIZE_MAX = STG_WORD16_MAX trim = T.take (fromIntegral(maxBound :: Word16) - 10) diff --git a/ghcide/src/Development/IDE/GHC/CPP.hs b/ghcide/src/Development/IDE/GHC/CPP.hs index 73e955a40..289794d2a 100644 --- a/ghcide/src/Development/IDE/GHC/CPP.hs +++ b/ghcide/src/Development/IDE/GHC/CPP.hs @@ -22,7 +22,6 @@ import GHC.Settings -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - #if !MIN_VERSION_ghc(9,5,0) import qualified GHC.Driver.Pipeline.Execute as Pipeline #endif diff --git a/ghcide/src/Development/IDE/GHC/Compat.hs b/ghcide/src/Development/IDE/GHC/Compat.hs index 636755e8c..d6184bcd5 100644 --- a/ghcide/src/Development/IDE/GHC/Compat.hs +++ b/ghcide/src/Development/IDE/GHC/Compat.hs @@ -169,6 +169,7 @@ import GHC.Builtin.Uniques import GHC.ByteCode.Types import GHC.CoreToStg import GHC.Data.Maybe +import GHC.Driver.Config.Stg.Pipeline import GHC.Driver.Env as Env import GHC.Iface.Env import GHC.Linker.Loader (loadDecls, loadExpr) @@ -181,15 +182,12 @@ import GHC.Types.IPE import GHC.Types.SrcLoc (combineRealSrcSpans) import GHC.Unit.Home.ModInfo (HomePackageTable, lookupHpt) +import GHC.Unit.Module.Deps (Dependencies (dep_direct_mods), + Usage (..)) import GHC.Unit.Module.ModIface -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - -import GHC.Driver.Config.Stg.Pipeline -import GHC.Unit.Module.Deps (Dependencies (dep_direct_mods), - Usage (..)) - #if !MIN_VERSION_ghc(9,5,0) import GHC.Core.Lint (lintInteractiveExpr) #endif diff --git a/ghcide/src/Development/IDE/GHC/Compat/Core.hs b/ghcide/src/Development/IDE/GHC/Compat/Core.hs index 8ba1e769c..15ce2f441 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Core.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Core.hs @@ -487,12 +487,15 @@ import qualified GHC.Utils.Panic.Plain as Plain import Data.Foldable (toList) import GHC.Core.Multiplicity (scaledThing) import GHC.Data.Bag +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 -import GHC.Hs (HsModule (..)) -#if !MIN_VERSION_ghc(9,9,0) -import GHC.Hs (SrcSpanAnn') -#endif -import GHC.Hs.Decls hiding (FunDep) +import GHC.Driver.Env as GHCi +import GHC.Driver.Env.KnotVars +import GHC.Driver.Errors.Types +import GHC.Hs (HsModule (..)) +import GHC.Hs.Decls hiding (FunDep) import GHC.Hs.Doc import GHC.Hs.Expr import GHC.Hs.Extension @@ -516,39 +519,36 @@ import GHC.Types.SourceText import GHC.Types.Target (Target (..), TargetId (..)) import GHC.Types.TyThing import GHC.Types.TyThing.Ppr +import GHC.Types.Unique +import GHC.Types.Unique.Map +import GHC.Unit.Env import GHC.Unit.Finder hiding (mkHomeModLocation) +import qualified GHC.Unit.Finder as GHC +import GHC.Unit.Finder.Types import GHC.Unit.Home.ModInfo +import GHC.Unit.Module.Graph 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 GHC.Utils.Error (mkPlainErrorMsgEnvelope) +import GHC.Utils.Panic +import GHC.Utils.TmpFs import Language.Haskell.Syntax hiding (FunDep) -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] -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 - #if !MIN_VERSION_ghc(9,7,0) import GHC.Types.Avail (greNamePrintableName) #endif +#if !MIN_VERSION_ghc(9,9,0) +import GHC.Hs (SrcSpanAnn') +#endif + mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO Module.ModLocation mkHomeModLocation df mn f = pure $ GHC.mkHomeModLocation (GHC.initFinderOpts df) mn f diff --git a/ghcide/src/Development/IDE/GHC/Compat/Env.hs b/ghcide/src/Development/IDE/GHC/Compat/Env.hs index 28f61e76f..988739e3b 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Env.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Env.hs @@ -57,6 +57,7 @@ module Development.IDE.GHC.Compat.Env ( import GHC (setInteractiveDynFlags) import GHC.Driver.Backend as Backend +import GHC.Driver.Env (HscEnv, hscSetActiveUnitId) import qualified GHC.Driver.Env as Env import GHC.Driver.Hooks (Hooks) import GHC.Driver.Session @@ -69,12 +70,6 @@ import GHC.Unit.Types (UnitId) import GHC.Utils.Logger import GHC.Utils.TmpFs --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - -import GHC.Driver.Env (HscEnv, hscSetActiveUnitId) - - hsc_EPS :: HscEnv -> UnitEnv hsc_EPS = Env.hsc_unit_env diff --git a/ghcide/src/Development/IDE/GHC/Compat/Iface.hs b/ghcide/src/Development/IDE/GHC/Compat/Iface.hs index 750b32450..e76de880d 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Iface.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Iface.hs @@ -9,13 +9,12 @@ module Development.IDE.GHC.Compat.Iface ( import Development.IDE.GHC.Compat.Env import Development.IDE.GHC.Compat.Outputable import GHC +import GHC.Driver.Session (targetProfile) import qualified GHC.Iface.Load as Iface import GHC.Unit.Finder.Types (FindResult) -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] -import GHC.Driver.Session (targetProfile) - #if MIN_VERSION_ghc(9,7,0) import GHC.Iface.Errors.Ppr (missingInterfaceErrorDiagnostic) import GHC.Iface.Errors.Types (IfaceMessage) diff --git a/ghcide/src/Development/IDE/GHC/Compat/Logger.hs b/ghcide/src/Development/IDE/GHC/Compat/Logger.hs index fb4d98d0f..32ec11da4 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Logger.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Logger.hs @@ -14,13 +14,10 @@ import Development.IDE.GHC.Compat.Env as Env import Development.IDE.GHC.Compat.Outputable +import GHC.Types.Error import GHC.Utils.Logger as Logger import GHC.Utils.Outputable --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - -import GHC.Types.Error - putLogHook :: Logger -> HscEnv -> HscEnv putLogHook logger env = env { hsc_logger = logger } diff --git a/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs b/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs index 87f248285..078d11643 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Outputable.hs @@ -48,26 +48,24 @@ module Development.IDE.GHC.Compat.Outputable ( textDoc, ) where +import Data.Maybe +import GHC.Driver.Config.Diagnostic import GHC.Driver.Env import GHC.Driver.Ppr import GHC.Driver.Session +import GHC.Parser.Errors.Types import qualified GHC.Types.Error as Error 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 import GHC.Utils.Outputable as Out import GHC.Utils.Panic -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - -import Data.Maybe -import GHC.Driver.Config.Diagnostic -import GHC.Parser.Errors.Types -import GHC.Utils.Error - #if MIN_VERSION_ghc(9,5,0) import GHC.Driver.Errors.Types (DriverMessage, GhcMessage) #endif @@ -115,7 +113,7 @@ pprNoLocMsgEnvelope (MsgEnvelope { errMsgDiagnostic = e #if MIN_VERSION_ghc(9,7,0) formatBulleted e #else - formatBulleted _ctx $ e + formatBulleted _ctx e #endif diff --git a/ghcide/src/Development/IDE/GHC/Compat/Parser.hs b/ghcide/src/Development/IDE/GHC/Compat/Parser.hs index fe3d6b592..25d23bcad 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Parser.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Parser.hs @@ -34,12 +34,8 @@ import GHC (EpaCommentTok (..), pm_mod_summary, pm_parsed_source) import qualified GHC -import GHC.Hs (hpm_module, hpm_src_files) - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - import qualified GHC.Driver.Config.Parser as Config +import GHC.Hs (hpm_module, hpm_src_files) diff --git a/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs b/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs index c5b9d795f..f388db3f0 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Plugins.hs @@ -24,19 +24,15 @@ import Development.IDE.GHC.Compat.Env (hscSetFlags, hsc_dflags) import Development.IDE.GHC.Compat.Parser as Parser import qualified GHC.Driver.Env as Env -import GHC.Driver.Plugins (Plugin (..), - PluginWithArgs (..), - StaticPlugin (..), - defaultPlugin, withPlugins) -import qualified GHC.Runtime.Loader as Loader - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - import GHC.Driver.Plugins (ParsedResult (..), + Plugin (..), + PluginWithArgs (..), PsMessages (..), - staticPlugins) + StaticPlugin (..), + defaultPlugin, + staticPlugins, withPlugins) import qualified GHC.Parser.Lexer as Lexer +import qualified GHC.Runtime.Loader as Loader getPsMessages :: PState -> PsMessages @@ -47,7 +43,7 @@ applyPluginsParsedResultAction :: HscEnv -> ModSummary -> ParsedSource -> PsMess applyPluginsParsedResultAction env ms parsed msgs = do -- Apply parsedResultAction of plugins let applyPluginAction p opts = parsedResultAction p opts ms - fmap (\result -> (hpm_module (parsedResultModule result), (parsedResultMessages result))) $ runHsc env $ withPlugins + fmap (\result -> (hpm_module (parsedResultModule result), parsedResultMessages result)) $ runHsc env $ withPlugins (Env.hsc_plugins env) applyPluginAction (ParsedResult (HsParsedModule parsed []) msgs) diff --git a/ghcide/src/Development/IDE/GHC/Compat/Units.hs b/ghcide/src/Development/IDE/GHC/Compat/Units.hs index 4f5a320fa..f7f634e44 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Units.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Units.hs @@ -52,10 +52,17 @@ import Development.IDE.GHC.Compat.Env import Development.IDE.GHC.Compat.Outputable import Prelude hiding (mod) +import Control.Monad +import qualified Data.List.NonEmpty as NE +import qualified Data.Map.Strict as Map +import qualified GHC import qualified GHC.Data.ShortText as ST +import qualified GHC.Driver.Session as DynFlags +import GHC.Types.PkgQual (PkgQual (NoPkgQual)) import GHC.Types.Unique.Set import GHC.Unit.External import qualified GHC.Unit.Finder as GHC +import GHC.Unit.Home.ModInfo import qualified GHC.Unit.Info as UnitInfo import GHC.Unit.State (LookupResult, UnitInfo, UnitInfoMap, @@ -68,17 +75,6 @@ import GHC.Unit.State (LookupResult, UnitInfo, import qualified GHC.Unit.State as State import GHC.Unit.Types --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - -import Control.Monad -import qualified Data.List.NonEmpty as NE -import qualified Data.Map.Strict as Map -import qualified GHC -import qualified GHC.Driver.Session as DynFlags -import GHC.Types.PkgQual (PkgQual (NoPkgQual)) -import GHC.Unit.Home.ModInfo - type PreloadUnitClosure = UniqSet UnitId @@ -91,7 +87,7 @@ createUnitEnvFromFlags unitDflags = newInternalUnitEnv dflags = mkHomeUnitEnv dflags emptyHomePackageTable Nothing unitEnvList = NE.map (\dflags -> (homeUnitId_ dflags, newInternalUnitEnv dflags)) unitDflags in - unitEnv_new (Map.fromList (NE.toList (unitEnvList))) + unitEnv_new (Map.fromList (NE.toList unitEnvList)) initUnits :: [DynFlags] -> HscEnv -> IO HscEnv initUnits unitDflags env = do diff --git a/ghcide/src/Development/IDE/GHC/Compat/Util.hs b/ghcide/src/Development/IDE/GHC/Compat/Util.hs index ab6c1e7f0..1f9e3a160 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Util.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Util.hs @@ -68,6 +68,7 @@ module Development.IDE.GHC.Compat.Util ( import Control.Exception.Safe (MonadCatch, catch, try) import GHC.Data.Bag +import GHC.Data.Bool import GHC.Data.BooleanFormula import GHC.Data.EnumSet import GHC.Data.FastString @@ -79,8 +80,3 @@ import GHC.Types.Unique.DFM 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] - - -import GHC.Data.Bool diff --git a/ghcide/src/Development/IDE/GHC/CoreFile.hs b/ghcide/src/Development/IDE/GHC/CoreFile.hs index ec210a120..f2b58ee02 100644 --- a/ghcide/src/Development/IDE/GHC/CoreFile.hs +++ b/ghcide/src/Development/IDE/GHC/CoreFile.hs @@ -197,7 +197,7 @@ tcIfaceId = fmap getIfaceId . tcIfaceDecl False <=< unmangle_decl_name name' <- newIfaceName (mkVarOcc $ getOccString name) pure $ ifid{ ifName = name' } | otherwise = pure ifid - unmangle_decl_name _ifid = error $ "tcIfaceId: got non IfaceId: " + unmangle_decl_name _ifid = error "tcIfaceId: got non IfaceId: " -- invariant: 'IfaceId' is always a 'IfaceId' constructor getIfaceId (AnId identifier) = identifier getIfaceId _ = error "tcIfaceId: got non Id" diff --git a/ghcide/src/Development/IDE/GHC/Orphans.hs b/ghcide/src/Development/IDE/GHC/Orphans.hs index c19c8f685..357266235 100644 --- a/ghcide/src/Development/IDE/GHC/Orphans.hs +++ b/ghcide/src/Development/IDE/GHC/Orphans.hs @@ -17,20 +17,17 @@ import Data.Hashable import Data.String (IsString (fromString)) import Data.Text (unpack) +import Data.Bifunctor (Bifunctor (..)) import GHC.ByteCode.Types import GHC.Data.Bag import GHC.Data.FastString import qualified GHC.Data.StringBuffer as SB -import GHC.Types.SrcLoc - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - -import Data.Bifunctor (Bifunctor (..)) import GHC.Parser.Annotation +import GHC.Types.SrcLoc import GHC.Types.PkgQual +-- See Note [Guidelines For Using CPP In GHCIDE Import Statements] #if MIN_VERSION_ghc(9,5,0) import GHC.Unit.Home.ModInfo diff --git a/ghcide/src/Development/IDE/Import/DependencyInformation.hs b/ghcide/src/Development/IDE/Import/DependencyInformation.hs index 67adedb83..5372a1364 100644 --- a/ghcide/src/Development/IDE/Import/DependencyInformation.hs +++ b/ghcide/src/Development/IDE/Import/DependencyInformation.hs @@ -47,17 +47,13 @@ import Data.List.NonEmpty (NonEmpty (..), nonEmpty) import qualified Data.List.NonEmpty as NonEmpty import Data.Maybe import Data.Tuple.Extra hiding (first, second) +import Development.IDE.GHC.Compat import Development.IDE.GHC.Orphans () -import GHC.Generics (Generic) -import Prelude hiding (mod) - import Development.IDE.Import.FindImports (ArtifactsLocation (..)) import Development.IDE.Types.Diagnostics import Development.IDE.Types.Location - -import Development.IDE.GHC.Compat - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] +import GHC.Generics (Generic) +import Prelude hiding (mod) -- | 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 59e2a301c..e17c490c5 100644 --- a/ghcide/src/Development/IDE/Import/FindImports.hs +++ b/ghcide/src/Development/IDE/Import/FindImports.hs @@ -14,25 +14,20 @@ module Development.IDE.Import.FindImports ) where import Control.DeepSeq -import Development.IDE.GHC.Compat as Compat -import Development.IDE.GHC.Error as ErrUtils -import Development.IDE.GHC.Orphans () -import Development.IDE.Types.Diagnostics -import Development.IDE.Types.Location - --- standard imports import Control.Monad.Extra import Control.Monad.IO.Class import Data.List (find, isSuffixOf) import Data.Maybe import qualified Data.Set as S -import System.FilePath - --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - - +import Development.IDE.GHC.Compat as Compat +import Development.IDE.GHC.Error as ErrUtils +import Development.IDE.GHC.Orphans () +import Development.IDE.Types.Diagnostics +import Development.IDE.Types.Location import GHC.Types.PkgQual import GHC.Unit.State +import System.FilePath + data Import = FileImport !ArtifactsLocation diff --git a/ghcide/src/Development/IDE/LSP/Outline.hs b/ghcide/src/Development/IDE/LSP/Outline.hs index 879aed712..af2a0f1c9 100644 --- a/ghcide/src/Development/IDE/LSP/Outline.hs +++ b/ghcide/src/Development/IDE/LSP/Outline.hs @@ -30,8 +30,6 @@ import Language.LSP.Protocol.Types (DocumentSymbol (..), type (|?) (InL, InR), uriToFilePath) --- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - moduleOutline :: PluginMethodHandler IdeState Method_TextDocumentDocumentSymbol @@ -138,13 +136,13 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_ins documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl FamEqn { feqn_tycon, feqn_pats } })) = Just (defDocumentSymbol l :: DocumentSymbol) { _name = - printOutputable $ pprHsArgsApp (unLoc feqn_tycon) Prefix (feqn_pats) + printOutputable $ pprHsArgsApp (unLoc feqn_tycon) Prefix feqn_pats , _kind = SymbolKind_Interface } documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl _ FamEqn { feqn_tycon, feqn_pats } })) = Just (defDocumentSymbol l :: DocumentSymbol) { _name = - printOutputable $ pprHsArgsApp (unLoc feqn_tycon) Prefix (feqn_pats) + printOutputable $ pprHsArgsApp (unLoc feqn_tycon) Prefix feqn_pats , _kind = SymbolKind_Interface } documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) = diff --git a/ghcide/src/Development/IDE/LSP/Server.hs b/ghcide/src/Development/IDE/LSP/Server.hs index e2b234557..605250491 100644 --- a/ghcide/src/Development/IDE/LSP/Server.hs +++ b/ghcide/src/Development/IDE/LSP/Server.hs @@ -41,7 +41,7 @@ requestHandler m k = LSP.requestHandler m $ \TRequestMessage{_method,_id,_params trace x = otTracedHandler "Request" (show _method) $ \sp -> do traceWithSpan sp _params x - writeChan chan $ ReactorRequest (_id) (trace $ LSP.runLspT env $ resp' =<< k ide _params) (LSP.runLspT env . resp' . Left) + writeChan chan $ ReactorRequest _id (trace $ LSP.runLspT env $ resp' =<< k ide _params) (LSP.runLspT env . resp' . Left) notificationHandler :: forall m c. PluginMethod Notification m => diff --git a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs index 2ce70afeb..9fdc196cd 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs @@ -74,7 +74,6 @@ import GHC.Plugins (Depth (AllTheWay), -- See Note [Guidelines For Using CPP In GHCIDE Import Statements] - #if MIN_VERSION_ghc(9,5,0) import Language.Haskell.Syntax.Basic #endif diff --git a/ghcide/test/exe/ReferenceTests.hs b/ghcide/test/exe/ReferenceTests.hs index bc69a8fdb..013cecaa8 100644 --- a/ghcide/test/exe/ReferenceTests.hs +++ b/ghcide/test/exe/ReferenceTests.hs @@ -161,7 +161,7 @@ data IncludeDeclaration = YesIncludeDeclaration | NoExcludeDeclaration -getReferences' :: SymbolLocation -> IncludeDeclaration -> Session ([Location]) +getReferences' :: SymbolLocation -> IncludeDeclaration -> Session [Location] getReferences' (file, l, c) includeDeclaration = do doc <- openDoc file "haskell" getReferences doc (Position l c) $ toBool includeDeclaration diff --git a/ghcide/test/exe/WatchedFileTests.hs b/ghcide/test/exe/WatchedFileTests.hs index a4683ecbc..d013f673a 100644 --- a/ghcide/test/exe/WatchedFileTests.hs +++ b/ghcide/test/exe/WatchedFileTests.hs @@ -66,7 +66,7 @@ tests = testGroup "watched files" ["module B where" ,"b :: Int" ,"b = 0"] - sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $ + sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams [FileEvent (filePathToUri $ sessionDir "B.hs") FileChangeType_Changed ] expectDiagnostics [("A.hs", [(DiagnosticSeverity_Error, (3, 4), "Couldn't match expected type '()' with actual type 'Int'")])] ] diff --git a/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs b/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs index 13526c053..f4ac94e1f 100644 --- a/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs +++ b/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs @@ -464,11 +464,8 @@ filterByImport (ImportDecl{ideclHiding = Just (_, L _ names)}) then Just res else Nothing where importedNames = S.fromList $ map (ieName . unLoc) names - res = flip Map.filter avails $ \a -> - any (`S.member` importedNames) - $ concatMap - getAvailNames - a + res = Map.filter (any (any (`S.member` importedNames) . getAvailNames)) avails + allFilteredAvailsNames = S.fromList $ concatMap getAvailNames $ mconcat diff --git a/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Compat/ExactPrint.hs b/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Compat/ExactPrint.hs index d8b86217d..7c337dcd0 100644 --- a/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Compat/ExactPrint.hs +++ b/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Compat/ExactPrint.hs @@ -7,7 +7,7 @@ module Development.IDE.GHC.Compat.ExactPrint , transformA ) where -import Language.Haskell.GHC.ExactPrint as ExactPrint +import Language.Haskell.GHC.ExactPrint as ExactPrint printA :: (ExactPrint ast) => ast -> String printA ast = exactPrint ast @@ -16,4 +16,4 @@ transformA :: Monad m => ast1 -> (ast1 -> TransformT m ast2) -> m ast2 transformA ast f = do (ast',_ ,_) <- runTransformFromT 0 (f ast) - return $ ast' + return ast' diff --git a/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs b/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs index 35b67f156..a50ed3f3d 100644 --- a/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs +++ b/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs @@ -563,7 +563,7 @@ suggestRemoveRedundantExport :: ParsedModule -> Diagnostic -> Maybe (T.Text, [Ra suggestRemoveRedundantExport ParsedModule{pm_parsed_source = L _ HsModule{..}} Diagnostic{..} | msg <- unifySpaces _message , Just export <- hsmodExports - , Just exportRange <- getLocatedRange $ export + , Just exportRange <- getLocatedRange export , exports <- unLoc export , Just (removeFromExport, !ranges) <- fmap (getRanges exports . notInScope) (extractNotInScopeName msg) <|> (,[_range]) <$> matchExportItem msg @@ -1625,7 +1625,7 @@ data ImportSuggestion = ImportSuggestion !Int !CodeActionKind !NewImport -- which would lead to an unlawful Ord instance. simpleCompareImportSuggestion :: ImportSuggestion -> ImportSuggestion -> Ordering simpleCompareImportSuggestion (ImportSuggestion s1 _ i1) (ImportSuggestion s2 _ i2) - = flip compare s1 s2 <> compare i1 i2 + = compare s2 s1 <> compare i1 i2 newtype NewImport = NewImport {unNewImport :: T.Text} deriving (Show, Eq, Ord) diff --git a/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs b/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs index 6a0b0673c..eacd47e2d 100644 --- a/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs +++ b/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs @@ -225,7 +225,7 @@ semanticTokensFullDeltaTests = semanticTokensTests :: TestTree semanticTokensTests = - testGroup "other semantic Token test" $ + testGroup "other semantic Token test" [ testCase "module import test" $ do let file1 = "TModuleA.hs" let file2 = "TModuleB.hs" diff --git a/plugins/hls-splice-plugin/src/Ide/Plugin/Splice.hs b/plugins/hls-splice-plugin/src/Ide/Plugin/Splice.hs index fbe59500a..daddf77df 100644 --- a/plugins/hls-splice-plugin/src/Ide/Plugin/Splice.hs +++ b/plugins/hls-splice-plugin/src/Ide/Plugin/Splice.hs @@ -191,7 +191,7 @@ expandTHSplice _eStyle ideState _ params@ExpandSpliceParams {..} = ExceptT $ do pure (Right edits) case res of Nothing -> pure $ Right $ InR Null - Just (Left err) -> pure $ Left $ err + Just (Left err) -> pure $ Left err Just (Right edit) -> do _ <- pluginSendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing edit) (\_ -> pure ()) pure $ Right $ InR Null diff --git a/src/Ide/Main.hs b/src/Ide/Main.hs index cbe3f33bb..d32bb66e8 100644 --- a/src/Ide/Main.hs +++ b/src/Ide/Main.hs @@ -89,7 +89,7 @@ defaultMain recorder args idePlugins = do $ map describePlugin $ sortOn pluginId $ ipMap idePlugins - putStrLn $ show pluginSummary + print pluginSummary BiosMode PrintCradleType -> do dir <- IO.getCurrentDirectory diff --git a/test/functional/Main.hs b/test/functional/Main.hs index 004c817d2..daa342f69 100644 --- a/test/functional/Main.hs +++ b/test/functional/Main.hs @@ -12,8 +12,8 @@ main :: IO () main = defaultTestRunner $ testGroup "haskell-language-server" [ Config.tests , ConfigSchema.tests - , ignoreInEnv [HostOS Windows] "Tests gets stuck in ci" $ Format.tests + , ignoreInEnv [HostOS Windows] "Tests gets stuck in ci" Format.tests , FunctionalBadProject.tests , HieBios.tests - , ignoreInEnv [HostOS Windows] "Tests gets stuck in ci" $ Progress.tests + , ignoreInEnv [HostOS Windows] "Tests gets stuck in ci" Progress.tests ]