Skip to content

Commit 283c6b0

Browse files
committed
Drop min_version_ghc (8.8.4 is min supported)
1 parent 97fc712 commit 283c6b0

File tree

10 files changed

+10
-138
lines changed

10 files changed

+10
-138
lines changed

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1181,9 +1181,7 @@ getModSummaryFromImports env fp modTime contents = do
11811181
msrModSummary =
11821182
ModSummary
11831183
{ ms_mod = modl
1184-
#if MIN_VERSION_ghc(8,8,0)
11851184
, ms_hie_date = Nothing
1186-
#endif
11871185
#if MIN_VERSION_ghc(9,3,0)
11881186
, ms_dyn_obj_date = Nothing
11891187
, ms_ghc_prim_import = ghc_prim_import

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -62,9 +62,6 @@ module Development.IDE.Core.Rules(
6262
DisplayTHWarning(..),
6363
) where
6464

65-
#if !MIN_VERSION_ghc(8,8,0)
66-
import Control.Applicative (liftA2)
67-
#endif
6865
import Control.Concurrent.Async (concurrently)
6966
import Control.Concurrent.Strict
7067
import Control.DeepSeq

ghcide/src/Development/IDE/Core/Tracing.hs

Lines changed: 4 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -37,25 +37,16 @@ import OpenTelemetry.Eventlog (SpanInFlight (..), addEvent,
3737
beginSpan, endSpan, setTag,
3838
withSpan)
3939

40-
#if MIN_VERSION_ghc(8,8,0)
41-
otTracedProvider :: MonadUnliftIO m => PluginId -> ByteString -> m a -> m a
42-
otTracedGarbageCollection :: (MonadMask f, MonadIO f, Show a) => ByteString -> f [a] -> f [a]
43-
withEventTrace :: (MonadMask m, MonadIO m) => String -> ((ByteString -> m ()) -> m a) -> m a
44-
#else
45-
otTracedProvider :: MonadUnliftIO m => PluginId -> String -> m a -> m a
46-
otTracedGarbageCollection :: (MonadMask f, MonadIO f, Show a) => String -> f [a] -> f [a]
47-
withEventTrace :: (MonadMask m, MonadIO m) => String -> ((ByteString -> m ()) -> m a) -> m a
48-
#endif
4940

50-
withTrace :: (MonadMask m, MonadIO m) =>
51-
String -> ((String -> String -> m ()) -> m a) -> m a
41+
withTrace :: (MonadMask m, MonadIO m) => String -> ((String -> String -> m ()) -> m a) -> m a
5242
withTrace name act
5343
| userTracingEnabled
5444
= withSpan (fromString name) $ \sp -> do
5545
let setSpan' k v = setTag sp (fromString k) (fromString v)
5646
act setSpan'
5747
| otherwise = act (\_ _ -> pure ())
5848

49+
withEventTrace :: (MonadMask m, MonadIO m) => String -> ((ByteString -> m ()) -> m a) -> m a
5950
withEventTrace name act
6051
| userTracingEnabled
6152
= withSpan (fromString name) $ \sp -> do
@@ -125,6 +116,7 @@ otTracedAction key file mode result act
125116
(\sp -> act (liftIO . setTag sp "diagnostics" . encodeUtf8 . showDiagnostics ))
126117
| otherwise = act (\_ -> return ())
127118

119+
otTracedGarbageCollection :: (MonadMask f, MonadIO f, Show a) => ByteString -> f [a] -> f [a]
128120
otTracedGarbageCollection label act
129121
| userTracingEnabled = fst <$>
130122
generalBracket
@@ -138,6 +130,7 @@ otTracedGarbageCollection label act
138130
(const act)
139131
| otherwise = act
140132

133+
otTracedProvider :: MonadUnliftIO m => PluginId -> ByteString -> m a -> m a
141134
otTracedProvider (PluginId pluginName) provider act
142135
| userTracingEnabled = do
143136
runInIO <- askRunInIO
@@ -146,4 +139,3 @@ otTracedProvider (PluginId pluginName) provider act
146139
runInIO act
147140
| otherwise = act
148141

149-

ghcide/src/Development/IDE/GHC/Compat.hs

Lines changed: 2 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -228,18 +228,8 @@ import DynFlags hiding (ExposePackage)
228228
import HscTypes
229229
import MkIface hiding (writeIfaceFile)
230230

231-
#if MIN_VERSION_ghc(8,8,0)
232231
import StringBuffer (hPutStringBuffer)
233-
#endif
234232
import qualified SysTools
235-
236-
#if !MIN_VERSION_ghc(8,8,0)
237-
import qualified EnumSet
238-
import SrcLoc (RealLocated)
239-
240-
import Foreign.ForeignPtr
241-
import System.IO
242-
#endif
243233
#endif
244234

245235
import Compat.HieAst (enrichHie)
@@ -385,13 +375,6 @@ corePrepExpr _ = GHC.corePrepExpr
385375
simplifyExpr df _ = GHC.simplifyExpr df
386376
#endif
387377

388-
#if !MIN_VERSION_ghc(8,8,0)
389-
hPutStringBuffer :: Handle -> StringBuffer -> IO ()
390-
hPutStringBuffer hdl (StringBuffer buf len cur)
391-
= withForeignPtr (plusForeignPtr buf cur) $ \ptr ->
392-
hPutBuf hdl ptr len
393-
#endif
394-
395378
#if MIN_VERSION_ghc(9,2,0)
396379
type ErrMsg = MsgEnvelope DecoratedSDoc
397380
#endif
@@ -445,12 +428,7 @@ hieExportNames = nameListFromAvails . hie_exports
445428
type NameCacheUpdater = NameCache
446429
#else
447430
upNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
448-
#if MIN_VERSION_ghc(8,8,0)
449431
upNameCache = updNameCache
450-
#else
451-
upNameCache ref upd_fn
452-
= atomicModifyIORef' ref upd_fn
453-
#endif
454432
#endif
455433

456434
#if !MIN_VERSION_ghc(9,0,1)
@@ -480,27 +458,15 @@ addIncludePathsQuote path x = x{includePaths = f $ includePaths x}
480458
where f i = i{includePathsQuote = path : includePathsQuote i}
481459

482460
setHieDir :: FilePath -> DynFlags -> DynFlags
483-
setHieDir _f d =
484-
#if MIN_VERSION_ghc(8,8,0)
485-
d { hieDir = Just _f}
486-
#else
487-
d
488-
#endif
461+
setHieDir _f d = d { hieDir = Just _f}
489462

490463
dontWriteHieFiles :: DynFlags -> DynFlags
491-
dontWriteHieFiles d =
492-
#if MIN_VERSION_ghc(8,8,0)
493-
gopt_unset d Opt_WriteHie
494-
#else
495-
d
496-
#endif
464+
dontWriteHieFiles d = gopt_unset d Opt_WriteHie
497465

498466
setUpTypedHoles ::DynFlags -> DynFlags
499467
setUpTypedHoles df
500468
= flip gopt_unset Opt_AbstractRefHoleFits -- too spammy
501-
#if MIN_VERSION_ghc(8,8,0)
502469
$ flip gopt_unset Opt_ShowDocsOfHoleFits -- not used
503-
#endif
504470
$ flip gopt_unset Opt_ShowMatchesOfHoleFits -- nice but broken (forgets module qualifiers)
505471
$ flip gopt_unset Opt_ShowProvOfHoleFits -- not used
506472
$ flip gopt_unset Opt_ShowTypeAppOfHoleFits -- not used
@@ -533,12 +499,6 @@ disableWarningsAsErrors :: DynFlags -> DynFlags
533499
disableWarningsAsErrors df =
534500
flip gopt_unset Opt_WarnIsError $ foldl' wopt_unset_fatal df [toEnum 0 ..]
535501

536-
#if !MIN_VERSION_ghc(8,8,0)
537-
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
538-
wopt_unset_fatal dfs f
539-
= dfs { fatalWarningFlags = EnumSet.delete f (fatalWarningFlags dfs) }
540-
#endif
541-
542502
isQualifiedImport :: ImportDecl a -> Bool
543503
#if MIN_VERSION_ghc(8,10,0)
544504
isQualifiedImport ImportDecl{ideclQualified = NotQualified} = False

ghcide/src/Development/IDE/GHC/Compat/CPP.hs

Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -20,11 +20,7 @@ import FileCleanup
2020
import Packages
2121
import Panic
2222
import SysTools
23-
#if MIN_VERSION_ghc(8,8,2)
2423
import LlvmCodeGen (llvmVersionList)
25-
#elif MIN_VERSION_ghc(8,8,0)
26-
import LlvmCodeGen (LlvmVersion (..))
27-
#endif
2824
import Control.Monad
2925
import Data.List (intercalate)
3026
import Data.Maybe
@@ -136,16 +132,9 @@ getBackendDefs :: DynFlags -> IO [String]
136132
getBackendDefs dflags | hscTarget dflags == HscLlvm = do
137133
llvmVer <- figureLlvmVersion dflags
138134
return $ case llvmVer of
139-
#if MIN_VERSION_ghc(8,8,2)
140135
Just v
141136
| [m] <- llvmVersionList v -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m, 0) ]
142137
| m:n:_ <- llvmVersionList v -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m, n) ]
143-
#elif MIN_VERSION_ghc(8,8,0)
144-
Just (LlvmVersion n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (n,0) ]
145-
Just (LlvmVersionOld m n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m,n) ]
146-
#else
147-
Just n -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format n ]
148-
#endif
149138
_ -> []
150139
where
151140
format (major, minor)

ghcide/src/Development/IDE/GHC/Compat/Core.hs

Lines changed: 2 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -36,11 +36,9 @@ module Development.IDE.GHC.Compat.Core (
3636
maxRefHoleFits,
3737
maxValidHoleFits,
3838
setOutputFile,
39-
#if MIN_VERSION_ghc(8,8,0)
4039
CommandLineOption,
4140
#if !MIN_VERSION_ghc(9,2,0)
4241
staticPlugins,
43-
#endif
4442
#endif
4543
sPgm_F,
4644
settings,
@@ -263,7 +261,7 @@ module Development.IDE.GHC.Compat.Core (
263261
SrcLoc.noSrcSpan,
264262
SrcLoc.noSrcLoc,
265263
SrcLoc.noLoc,
266-
#if !MIN_VERSION_ghc(8,10,0) && MIN_VERSION_ghc(8,8,0)
264+
#if !MIN_VERSION_ghc(8,10,0)
267265
SrcLoc.dL,
268266
#endif
269267
-- * Finder
@@ -734,19 +732,12 @@ import NameCache
734732
import NameEnv
735733
import NameSet
736734
import Packages
737-
#if MIN_VERSION_ghc(8,8,0)
738735
import Panic hiding (try)
739736
import qualified PlainPanic as Plain
740-
#else
741-
import Panic hiding (GhcException, try)
742-
import qualified Panic as Plain
743-
#endif
744737
import Parser
745738
import PatSyn
746739
import RnFixity
747-
#if MIN_VERSION_ghc(8,8,0)
748740
import Plugins
749-
#endif
750741
import PprTyThing hiding (pprFamInst)
751742
import PrelInfo
752743
import PrelNames hiding (Unique, printName)
@@ -791,10 +782,8 @@ import SrcLoc (RealLocated,
791782
#endif
792783

793784

794-
#if !MIN_VERSION_ghc(8,8,0)
795785
import Data.List (isSuffixOf)
796786
import System.FilePath
797-
#endif
798787

799788

800789
#if MIN_VERSION_ghc(9,2,0)
@@ -931,42 +920,19 @@ pattern L l a <- GHC.L (getLoc -> l) a
931920
{-# COMPLETE L #-}
932921
#endif
933922

934-
#elif MIN_VERSION_ghc(8,8,0)
923+
#else
935924
type HasSrcSpan = SrcLoc.HasSrcSpan
936925
getLoc :: SrcLoc.HasSrcSpan a => a -> SrcLoc.SrcSpan
937926
getLoc = SrcLoc.getLoc
938-
939-
#else
940-
941-
class HasSrcSpan a where
942-
getLoc :: a -> SrcSpan
943-
instance HasSrcSpan Name where
944-
getLoc = nameSrcSpan
945-
instance HasSrcSpan (SrcLoc.GenLocated SrcSpan a) where
946-
getLoc = SrcLoc.getLoc
947-
948927
#endif
949928

950929
getRealSrcSpan :: SrcLoc.RealLocated a -> SrcLoc.RealSrcSpan
951-
#if !MIN_VERSION_ghc(8,8,0)
952-
getRealSrcSpan = SrcLoc.getLoc
953-
#else
954930
getRealSrcSpan = SrcLoc.getRealSrcSpan
955-
#endif
956-
957931

958932
-- | Add the @-boot@ suffix to all output file paths associated with the
959933
-- module, not including the input file itself
960934
addBootSuffixLocnOut :: GHC.ModLocation -> GHC.ModLocation
961-
#if !MIN_VERSION_ghc(8,8,0)
962-
addBootSuffixLocnOut locn
963-
= locn { Module.ml_hi_file = Module.addBootSuffix (Module.ml_hi_file locn)
964-
, Module.ml_obj_file = Module.addBootSuffix (Module.ml_obj_file locn)
965-
}
966-
#else
967935
addBootSuffixLocnOut = Module.addBootSuffixLocnOut
968-
#endif
969-
970936

971937
dataConExTyCoVars :: DataCon -> [TyCoVar]
972938
#if __GLASGOW_HASKELL__ >= 808
@@ -1031,25 +997,15 @@ noExtField = GHC.noExt
1031997
#endif
1032998

1033999
ml_hie_file :: GHC.ModLocation -> FilePath
1034-
#if !MIN_VERSION_ghc(8,8,0)
1035-
ml_hie_file ml
1036-
| "boot" `isSuffixOf ` Module.ml_hi_file ml = Module.ml_hi_file ml -<.> ".hie-boot"
1037-
| otherwise = Module.ml_hi_file ml -<.> ".hie"
1038-
#else
10391000
ml_hie_file = Module.ml_hie_file
1040-
#endif
10411001

10421002
#if !MIN_VERSION_ghc(9,0,0)
10431003
pattern NotBoot, IsBoot :: IsBootInterface
10441004
pattern NotBoot = False
10451005
pattern IsBoot = True
10461006
#endif
10471007

1048-
#if MIN_VERSION_ghc(8,8,0)
10491008
type PlainGhcException = Plain.PlainGhcException
1050-
#else
1051-
type PlainGhcException = Plain.GhcException
1052-
#endif
10531009

10541010
#if MIN_VERSION_ghc(9,0,0)
10551011
-- This is from the old api, but it still simplifies

ghcide/src/Development/IDE/GHC/Compat/Plugins.hs

Lines changed: 1 addition & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -11,10 +11,8 @@ module Development.IDE.GHC.Compat.Plugins (
1111
initializePlugins,
1212

1313
-- * Static plugins
14-
#if MIN_VERSION_ghc(8,8,0)
1514
StaticPlugin(..),
1615
hsc_static_plugins,
17-
#endif
1816
) where
1917

2018
#if MIN_VERSION_ghc(9,0,0)
@@ -31,16 +29,11 @@ import GHC.Driver.Plugins (ParsedResult (..),
3129
staticPlugins)
3230
#endif
3331
import qualified GHC.Runtime.Loader as Loader
34-
#elif MIN_VERSION_ghc(8,8,0)
35-
import qualified DynamicLoading as Loader
36-
import Plugins
3732
#else
3833
import qualified DynamicLoading as Loader
39-
import Plugins (Plugin (..), defaultPlugin,
40-
withPlugins)
34+
import Plugins
4135
#endif
4236
import Development.IDE.GHC.Compat.Core
43-
import Development.IDE.GHC.Compat.Env (hscSetFlags, hsc_dflags)
4437
import Development.IDE.GHC.Compat.Parser as Parser
4538

4639
applyPluginsParsedResultAction :: HscEnv -> DynFlags -> ModSummary -> Parser.ApiAnns -> ParsedSource -> IO ParsedSource
@@ -76,7 +69,6 @@ initializePlugins env = do
7669
#endif
7770

7871

79-
#if MIN_VERSION_ghc(8,8,0)
8072
hsc_static_plugins :: HscEnv -> [StaticPlugin]
8173
#if MIN_VERSION_ghc(9,3,0)
8274
hsc_static_plugins = staticPlugins . Env.hsc_plugins
@@ -85,4 +77,3 @@ hsc_static_plugins = Env.hsc_static_plugins
8577
#else
8678
hsc_static_plugins = staticPlugins . hsc_dflags
8779
#endif
88-
#endif

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -280,11 +280,7 @@ typeLocationsAtPoint withHieDb lookupModule _ideOptions pos (HAR _ ast _ _ hieKi
280280
where ni = nodeInfo' x
281281
getTypes ts = flip concatMap (unfold ts) $ \case
282282
HTyVarTy n -> [n]
283-
#if MIN_VERSION_ghc(8,8,0)
284283
HAppTy a (HieArgs xs) -> getTypes (a : map snd xs)
285-
#else
286-
HAppTy a b -> getTypes [a,b]
287-
#endif
288284
HTyConApp tc (HieArgs xs) -> ifaceTyConName tc : getTypes (map snd xs)
289285
HForAllTy _ a -> getTypes [a]
290286
#if MIN_VERSION_ghc(9,0,1)

ghcide/src/Development/IDE/Spans/Pragmas.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -416,10 +416,7 @@ mkLexerPState dynFlags stringBuffer =
416416
startRealSrcLoc = mkRealSrcLoc "asdf" 1 1
417417
updateDynFlags = flip gopt_unset Opt_Haddock . flip gopt_set Opt_KeepRawTokenStream
418418
finalDynFlags = updateDynFlags dynFlags
419-
#if !MIN_VERSION_ghc(8,8,1)
420-
pState = mkPState finalDynFlags stringBuffer startRealSrcLoc
421-
finalPState = pState{ use_pos_prags = False }
422-
#elif !MIN_VERSION_ghc(8,10,1)
419+
#if !MIN_VERSION_ghc(8,10,1)
423420
mkLexerParserFlags =
424421
mkParserFlags'
425422
<$> warningFlags

plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -306,11 +306,7 @@ suggestRuleRewrites originatingFile pos ms_mod (L _ HsRules {rds_rules}) =
306306
]
307307
| L (locA -> l) r <- rds_rules,
308308
pos `isInsideSrcSpan` l,
309-
#if MIN_VERSION_ghc(8,8,0)
310309
let HsRule {rd_name = L _ (_, rn)} = r,
311-
#else
312-
let HsRule _ (L _ (_,rn)) _ _ _ _ = r,
313-
#endif
314310
let ruleName = unpackFS rn
315311
]
316312
where

0 commit comments

Comments
 (0)