Skip to content

Enable a bunch of plugins that build with ghc 9.4 #3136

New issue

Have a question about this project? # for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “#”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? # to your account

Merged
merged 12 commits into from
Sep 6, 2022
16 changes: 8 additions & 8 deletions .github/workflows/test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,7 @@ jobs:
name: Test hls-class-plugin
run: cabal test hls-class-plugin --test-options="$TEST_OPTS" || cabal test hls-class-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-class-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-pragmas-plugin
run: cabal test hls-pragmas-plugin --test-options="$TEST_OPTS" || cabal test hls-pragmas-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-pragmas-plugin --test-options="$TEST_OPTS"

Expand Down Expand Up @@ -212,15 +212,15 @@ jobs:
name: Test hls-tactics-plugin test suite
run: cabal test hls-tactics-plugin --test-options="$TEST_OPTS" || cabal test hls-tactics-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-tactics-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-refine-imports-plugin test suite
run: cabal test hls-refine-imports-plugin --test-options="$TEST_OPTS" || cabal test hls-refine-imports-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-refine-imports-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-explicit-imports-plugin test suite
run: cabal test hls-explicit-imports-plugin --test-options="$TEST_OPTS" || cabal test hls-explicit-imports-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-explicit-imports-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-call-hierarchy-plugin test suite
run: cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS" || cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-call-hierarchy-plugin --test-options="$TEST_OPTS"

Expand All @@ -236,31 +236,31 @@ jobs:
name: Test hls-stan-plugin test suite
run: cabal test hls-stan-plugin --test-options="$TEST_OPTS" || cabal test hls-hlint-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-stan-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-module-name-plugin test suite
run: cabal test hls-module-name-plugin --test-options="$TEST_OPTS" || cabal test hls-module-name-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-module-name-plugin --test-options="$TEST_OPTS"

- if: matrix.test
name: Test hls-alternate-number-format-plugin test suite
run: cabal test hls-alternate-number-format-plugin --test-options="$TEST_OPTS" || cabal test hls-alternate-number-format-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-alternate-number-format-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-qualify-imported-names-plugin test suite
run: cabal test hls-qualify-imported-names-plugin --test-options="$TEST_OPTS" || cabal test hls-qualify-imported-names-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-qualify-imported-names-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
name: Test hls-code-range-plugin test suite
run: cabal test hls-code-range-plugin --test-options="$TEST_OPTS" || cabal test hls-code-range-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-code-range-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-change-type-signature test suite
run: cabal test hls-change-type-signature-plugin --test-options="$TEST_OPTS" || cabal test hls-change-type-signature-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-change-type-signature-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
name: Test hls-gadt-plugin test suit
run: cabal test hls-gadt-plugin --test-options="$TEST_OPTS" || cabal test hls-gadt-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-gadt-plugin --test-options="$TEST_OPTS"

- if: matrix.test && matrix.ghc != '9.4.2'
- if: matrix.test
name: Test hls-explicit-fixity-plugin test suite
run: cabal test hls-explicit-fixity-plugin --test-options="$TEST_OPTS" || cabal test hls-explicit-fixity-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-explicit-fixity-plugin --test-options="$TEST_OPTS"

Expand Down
1 change: 1 addition & 0 deletions .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@
- Ide.Plugin.Class.ExactPrint
- TExpectedActual
- TRigidType
- TRigidType2
- RightToLeftFixities
- Typeclass
- Wingman.Judgements
Expand Down
6 changes: 3 additions & 3 deletions ghcide/src/Development/IDE/GHC/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ module Development.IDE.GHC.Compat(
NameCacheUpdater(..),
#if MIN_VERSION_ghc(9,3,0)
getMessages,
diagnosticMessage,
renderDiagnosticMessageWithHints,
nameEnvElts,
#else
upNameCache,
Expand Down Expand Up @@ -402,7 +402,7 @@ type WarnMsg = MsgEnvelope DecoratedSDoc
getMessages' :: PState -> DynFlags -> (Bag WarnMsg, Bag ErrMsg)
getMessages' pst dflags =
#if MIN_VERSION_ghc(9,3,0)
bimap (fmap (fmap diagnosticMessage) . getMessages) (fmap (fmap diagnosticMessage) . getMessages) $ getPsMessages pst
bimap (fmap (fmap renderDiagnosticMessageWithHints) . getMessages) (fmap (fmap renderDiagnosticMessageWithHints) . getMessages) $ getPsMessages pst
#else
#if MIN_VERSION_ghc(9,2,0)
bimap (fmap pprWarning) (fmap pprError) $
Expand All @@ -417,7 +417,7 @@ getMessages' pst dflags =
pattern PFailedWithErrorMessages :: forall a b. (b -> Bag (MsgEnvelope DecoratedSDoc)) -> ParseResult a
pattern PFailedWithErrorMessages msgs
#if MIN_VERSION_ghc(9,3,0)
<- PFailed (const . fmap (fmap diagnosticMessage) . getMessages . getPsErrorMessages -> msgs)
<- PFailed (const . fmap (fmap renderDiagnosticMessageWithHints) . getMessages . getPsErrorMessages -> msgs)
#else
<- PFailed (const . fmap pprError . getErrorMessages -> msgs)
#endif
Expand Down
8 changes: 7 additions & 1 deletion ghcide/src/Development/IDE/GHC/Compat/Outputable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module Development.IDE.GHC.Compat.Outputable (
PsError,
#if MIN_VERSION_ghc(9,3,0)
DiagnosticReason(..),
renderDiagnosticMessageWithHints,
#else
pprWarning,
pprError,
Expand Down Expand Up @@ -201,9 +202,14 @@ mkPrintUnqualifiedDefault env =
HscTypes.mkPrintUnqualified (hsc_dflags env)
#endif

#if MIN_VERSION_ghc(9,3,0)
renderDiagnosticMessageWithHints :: Diagnostic a => a -> DecoratedSDoc
renderDiagnosticMessageWithHints a = Error.unionDecoratedSDoc (diagnosticMessage a) (mkDecorated $ map ppr $ diagnosticHints a)
#endif

#if MIN_VERSION_ghc(9,3,0)
mkWarnMsg :: DynFlags -> Maybe DiagnosticReason -> b -> SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc
mkWarnMsg df reason _logFlags l st doc = fmap diagnosticMessage $ mkMsgEnvelope (initDiagOpts df) l st (mkPlainDiagnostic (fromMaybe WarningWithoutFlag reason) [] doc)
mkWarnMsg df reason _logFlags l st doc = fmap renderDiagnosticMessageWithHints $ mkMsgEnvelope (initDiagOpts df) l st (mkPlainDiagnostic (fromMaybe WarningWithoutFlag reason) [] doc)
#else
mkWarnMsg :: a -> b -> DynFlags -> SrcSpan -> PrintUnqualified -> SDoc -> MsgEnvelope DecoratedSDoc
mkWarnMsg _ _ =
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/GHC/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ catchSrcErrors dflags fromWhere ghcM = do
ghcExceptionToDiagnostics dflags = return . Left . diagFromGhcException fromWhere dflags
sourceErrorToDiagnostics dflags = return . Left . diagFromErrMsgs fromWhere dflags
#if MIN_VERSION_ghc(9,3,0)
. fmap (fmap Compat.diagnosticMessage) . Compat.getMessages
. fmap (fmap Compat.renderDiagnosticMessageWithHints) . Compat.getMessages
#endif
. srcErrorMessages

Expand Down
18 changes: 9 additions & 9 deletions haskell-language-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ common class
cpp-options: -Dhls_class

common callHierarchy
if flag(callHierarchy) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(callHierarchy)
build-depends: hls-call-hierarchy-plugin ^>= 1.0
cpp-options: -Dhls_callHierarchy

Expand All @@ -259,12 +259,12 @@ common eval
cpp-options: -Dhls_eval

common importLens
if flag(importLens) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(importLens)
build-depends: hls-explicit-imports-plugin ^>= 1.1
cpp-options: -Dhls_importLens

common refineImports
if flag(refineImports) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(refineImports)
build-depends: hls-refine-imports-plugin ^>=1.0
cpp-options: -Dhls_refineImports

Expand Down Expand Up @@ -294,12 +294,12 @@ common stan
cpp-options: -Dhls_stan

common moduleName
if flag(moduleName) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(moduleName)
build-depends: hls-module-name-plugin ^>= 1.0
cpp-options: -Dhls_moduleName

common pragmas
if flag(pragmas) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(pragmas)
build-depends: hls-pragmas-plugin ^>= 1.0
cpp-options: -Dhls_pragmas

Expand All @@ -314,17 +314,17 @@ common alternateNumberFormat
cpp-options: -Dhls_alternateNumberFormat

common qualifyImportedNames
if flag(qualifyImportedNames) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(qualifyImportedNames)
build-depends: hls-qualify-imported-names-plugin ^>=1.0
cpp-options: -Dhls_qualifyImportedNames

common codeRange
if flag(codeRange) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(codeRange)
build-depends: hls-code-range-plugin ^>= 1.0
cpp-options: -Dhls_codeRange

common changeTypeSignature
if flag(changeTypeSignature) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(changeTypeSignature)
build-depends: hls-change-type-signature-plugin ^>= 1.0
cpp-options: -Dhls_changeTypeSignature

Expand All @@ -334,7 +334,7 @@ common gadt
cpp-options: -Dhls_gadt

common explicitFixity
if flag(explicitFixity) && (impl(ghc < 9.4.1) || flag(ignore-plugins-ghc-bounds))
if flag(explicitFixity)
build-depends: hls-explicit-fixity-plugin ^>= 1.0
cpp-options: -DexplicitFixity

Expand Down
6 changes: 3 additions & 3 deletions hls-test-utils/src/Test/Hls/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -153,9 +153,9 @@ ignoreForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree
ignoreForGhcVersions vers = ignoreInEnv (map GhcVer vers)

-- | Mark as broken if GHC does not match only work versions.
onlyWorkForGhcVersions :: [GhcVersion] -> String -> TestTree -> TestTree
onlyWorkForGhcVersions vers reason =
if ghcVersion `elem` vers
onlyWorkForGhcVersions :: (GhcVersion -> Bool) -> String -> TestTree -> TestTree
onlyWorkForGhcVersions p reason =
if p ghcVersion
then id
else expectFailBecause reason

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,7 @@ extra-source-files:
test/testdata/*.hs

library
if impl(ghc >= 9.3)
buildable: False
else
buildable: True
buildable: True
exposed-modules: Ide.Plugin.CallHierarchy
other-modules:
Ide.Plugin.CallHierarchy.Internal
Expand Down Expand Up @@ -47,10 +44,7 @@ library
default-extensions: DataKinds

test-suite tests
if impl(ghc >= 9.3)
buildable: False
else
buildable: True
buildable: True
type: exitcode-stdio-1.0
default-language: Haskell2010
hs-source-dirs: test
Expand Down
4 changes: 2 additions & 2 deletions plugins/hls-call-hierarchy-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -166,13 +166,13 @@ prepareCallHierarchyTests =
expected = mkCallHierarchyItemC "A" SkConstructor range selRange
oneCaseWithCreate contents 1 13 expected
, testGroup "type signature"
[ testCase "next line" $ do
[ knownBrokenForGhcVersions [GHC94] "type signature broken" $ testCase "next line" $ do
let contents = T.unlines ["a::Int", "a=3"]
range = mkRange 1 0 1 3
selRange = mkRange 1 0 1 1
expected = mkCallHierarchyItemV "a" SkFunction range selRange
oneCaseWithCreate contents 0 0 expected
, testCase "multi functions" $ do
, knownBrokenForGhcVersions [GHC94] "type signature broken" $ testCase "multi functions" $ do
let contents = T.unlines [ "a,b::Int", "a=3", "b=4"]
range = mkRange 2 0 2 3
selRange = mkRange 2 0 2 1
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: 2.4
name: hls-change-type-signature-plugin
version: 1.0.1.0
version: 1.0.1.1
synopsis: Change a declarations type signature with a Code Action
description:
Please see the README on GitHub at <https://github.com/haskell/plugins/hls-change-type-signature-plugin/README.md>
Expand All @@ -19,10 +19,7 @@ extra-source-files:
test/testdata/*.yaml

library
if impl(ghc >= 9.3)
buildable: False
else
buildable: True
buildable: True
exposed-modules: Ide.Plugin.ChangeTypeSignature
hs-source-dirs: src
build-depends:
Expand Down Expand Up @@ -50,10 +47,7 @@ library


test-suite tests
if impl(ghc >= 9.3)
buildable: False
else
buildable: True
buildable: True
type: exitcode-stdio-1.0
default-language: Haskell2010
hs-source-dirs: test
Expand Down
5 changes: 3 additions & 2 deletions plugins/hls-change-type-signature-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Ide.Plugin.ChangeTypeSignature (errorMessageRegexes)
import qualified Ide.Plugin.ChangeTypeSignature as ChangeTypeSignature
import System.FilePath ((<.>), (</>))
import Test.Hls (CodeAction (..), Command,
GhcVersion (GHC92), IdeState,
GhcVersion (..), IdeState,
PluginDescriptor,
Position (Position),
Range (Range), Session,
Expand Down Expand Up @@ -38,7 +38,8 @@ test :: TestTree
test = testGroup "changeTypeSignature" [
testRegexes
, codeActionTest "TExpectedActual" 4 11
, knownBrokenForGhcVersions [GHC92] "Error Message in 9.2 does not provide enough info" $ codeActionTest "TRigidType" 4 14
, knownBrokenForGhcVersions [GHC92, GHC94] "Error Message in 9.2/9.4 does not provide enough info" $ codeActionTest "TRigidType" 4 14
, codeActionTest "TRigidType2" 4 6
, codeActionTest "TLocalBinding" 7 22
, codeActionTest "TLocalBindingShadow1" 11 8
, codeActionTest "TLocalBindingShadow2" 7 22
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module TRigidType2 where

test :: [Int] -> Int
test = head
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module TRigidType2 where

test :: a -> Int
test = head
9 changes: 0 additions & 9 deletions plugins/hls-code-range-plugin/hls-code-range-plugin.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -21,10 +21,6 @@ extra-source-files:
test/testdata/selection-range/*.txt

library
if impl(ghc >= 9.3)
buildable: False
else
buildable: True
exposed-modules:
Ide.Plugin.CodeRange
Ide.Plugin.CodeRange.Rules
Expand All @@ -42,7 +38,6 @@ library
, ghcide ^>=1.6 || ^>=1.7
, hashable
, hls-plugin-api ^>=1.3 || ^>=1.4
, hls-refactor-plugin
, lens
, lsp
, mtl
Expand All @@ -52,10 +47,6 @@ library
, vector

test-suite tests
if impl(ghc >= 9.3)
buildable: False
else
buildable: True
type: exitcode-stdio-1.0
default-language: Haskell2010
hs-source-dirs: test
Expand Down
6 changes: 1 addition & 5 deletions plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,6 @@ import Development.IDE.Core.PositionMapping (PositionMapping,
fromCurrentPosition,
toCurrentRange)
import Development.IDE.Types.Logger (Pretty (..))
import qualified Development.IDE.GHC.ExactPrint as E
import Development.IDE.Plugin.CodeAction
import Ide.Plugin.CodeRange.Rules (CodeRange (..),
GetCodeRange (..),
codeRangeRule)
Expand All @@ -57,20 +55,18 @@ import Language.LSP.Types (List (List),
import Prelude hiding (log, span)

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId = mkExactprintPluginDescriptor (cmapWithPrio LogExactPrint recorder) $ (defaultPluginDescriptor plId)
descriptor recorder plId = (defaultPluginDescriptor plId)
{ pluginHandlers = mkPluginHandler STextDocumentSelectionRange selectionRangeHandler
-- TODO @sloorush add folding range
-- <> mkPluginHandler STextDocumentFoldingRange foldingRangeHandler
, pluginRules = codeRangeRule (cmapWithPrio LogRules recorder)
}

data Log = LogRules Rules.Log
| LogExactPrint E.Log

instance Pretty Log where
pretty log = case log of
LogRules codeRangeLog -> pretty codeRangeLog
LogExactPrint exactPrintLog -> pretty exactPrintLog

selectionRangeHandler :: IdeState -> PluginId -> SelectionRangeParams -> LspM c (Either ResponseError (List SelectionRange))
selectionRangeHandler ide _ SelectionRangeParams{..} = do
Expand Down
Loading