diff --git a/.github/workflows/test.yml b/.github/workflows/test.yml index 659b6df72f..0c6d9b0f00 100644 --- a/.github/workflows/test.yml +++ b/.github/workflows/test.yml @@ -200,7 +200,7 @@ jobs: name: Test hls-fourmolu-plugin run: cabal test hls-fourmolu-plugin --test-options="-j1 --rerun-update" || cabal test hls-fourmolu-plugin --test-options="-j1 --rerun" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-fourmolu-plugin --test-options="-j1 --rerun" - - if: ${{ needs.pre_job.outputs.should_skip != 'true' && matrix.test && matrix.ghc != '9.0.1' }} + - if: ${{ needs.pre_job.outputs.should_skip != 'true' && matrix.test }} name: Test hls-tactics-plugin test suite run: cabal test hls-tactics-plugin --test-options="-j1 --rerun-update" || cabal test hls-tactics-plugin --test-options="-j1 --rerun" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-tactics-plugin --test-options="-j1 --rerun" diff --git a/cabal-ghc901.project b/cabal-ghc901.project index 325b3763b7..476ee5109f 100644 --- a/cabal-ghc901.project +++ b/cabal-ghc901.project @@ -6,7 +6,7 @@ packages: ./ghcide ./hls-plugin-api ./hls-test-utils - -- ./plugins/hls-tactics-plugin + ./plugins/hls-tactics-plugin -- ./plugins/hls-brittany-plugin -- ./plugins/hls-stylish-haskell-plugin -- ./plugins/hls-fourmolu-plugin @@ -65,7 +65,7 @@ index-state: 2021-09-16T07:00:23Z constraints: -- These plugins don't work on GHC9 yet - haskell-language-server -brittany -class -fourmolu -stylishhaskell -tactic + haskell-language-server -brittany -class -fourmolu -stylishhaskell allow-newer: floskell:base, diff --git a/configuration-ghc-901.nix b/configuration-ghc-901.nix index f10724f125..81c7acc012 100644 --- a/configuration-ghc-901.nix +++ b/configuration-ghc-901.nix @@ -3,7 +3,6 @@ let disabledPlugins = [ - "hls-tactics-plugin" "hls-brittany-plugin" "hls-stylish-haskell-plugin" "hls-fourmolu-plugin" @@ -54,7 +53,10 @@ let dependent-sum-template = hself.callCabal2nix "dependent-sum-template" "${dependent-sum-src}/dependent-sum-template" { }; - hlint = hself.hlint_3_3_1; + hlint = hself.hlint_3_3_4; + + generic-lens = hself.generic-lens_2_2_0_0; + generic-lens-core = hself.generic-lens-core_2_2_0_0; ghc-lib-parser = hself.ghc-lib-parser_9_0_1_20210324; @@ -85,7 +87,6 @@ let "-f-class" "-f-fourmolu" "-f-stylishhaskell" - "-f-tactic" ]) { }; # YOLO diff --git a/flake.lock b/flake.lock index ed2b424993..8dd8d39887 100644 --- a/flake.lock +++ b/flake.lock @@ -49,11 +49,11 @@ }, "nixpkgs": { "locked": { - "lastModified": 1630887066, - "narHash": "sha256-0ecIlrLsNIIa+zrNmzXXmbMBLZlmHU/aWFsa4bq99Hk=", + "lastModified": 1631786778, + "narHash": "sha256-CCMDj/0yXJnrlO4/NpHKhYRifNADQ1WUeQmFUD4sU4c=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "5e47a07e9f2d7ed999f2c7943b0896f5f7321ca3", + "rev": "a39ee95a86b1fbdfa9edd65f3810b23d82457241", "type": "github" }, "original": { diff --git a/ghcide/src/Development/IDE/GHC/Compat/Core.hs b/ghcide/src/Development/IDE/GHC/Compat/Core.hs index b2f560e9c3..1ab4aafe62 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Core.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Core.hs @@ -66,7 +66,10 @@ module Development.IDE.GHC.Compat.Core ( -- slightly unsafe setUnsafeGlobalDynFlags, -- * Linear Haskell +#if !MIN_VERSION_ghc(9,0,0) Scaled, + unrestricted, +#endif scaledThing, -- * Interface Files IfaceExport, @@ -121,9 +124,12 @@ module Development.IDE.GHC.Compat.Core ( TyCoRep.CoercionTy ), pattern FunTy, + pattern ConPatIn, Development.IDE.GHC.Compat.Core.splitForAllTyCoVars, +#if !MIN_VERSION_ghc(9,0,0) Development.IDE.GHC.Compat.Core.mkVisFunTys, Development.IDE.GHC.Compat.Core.mkInfForAllTys, +#endif -- * Specs ImpDeclSpec(..), ImportSpec(..), @@ -336,6 +342,7 @@ module Development.IDE.GHC.Compat.Core ( module GHC.Types.Var, module GHC.Unit.Module, module GHC.Utils.Error, + module TcType, #else module BasicTypes, module Class, @@ -769,7 +776,9 @@ dataConExTyCoVars = DataCon.dataConExTyVars type Scaled a = a scaledThing :: Scaled a -> a scaledThing = id -#endif + +unrestricted :: a -> Scaled a +unrestricted = id mkVisFunTys :: [Scaled Type] -> Type -> Type mkVisFunTys = @@ -781,10 +790,7 @@ mkVisFunTys = mkInfForAllTys :: [TyVar] -> Type -> Type mkInfForAllTys = -#if MIN_VERSION_ghc(9,0,0) - TcType.mkInfForAllTys -#else - mkInvForAllTys + mkInfForAllTys #endif splitForAllTyCoVars :: Type -> ([TyCoVar], Type) @@ -846,3 +852,10 @@ type PlainGhcException = Plain.PlainGhcException #else type PlainGhcException = Plain.GhcException #endif + +#if MIN_VERSION_ghc(9,0,0) +-- This is from the old api, but it still simplifies +pattern ConPatIn :: SrcLoc.Located (ConLikeP GhcPs) -> HsConPatDetails GhcPs -> Pat GhcPs +pattern ConPatIn con args = ConPat NoExtField con args +#endif + diff --git a/plugins/hls-tactics-plugin/src/Wingman/CodeGen.hs b/plugins/hls-tactics-plugin/src/Wingman/CodeGen.hs index 5f2f86605c..2ef491a5ec 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/CodeGen.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/CodeGen.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} @@ -57,7 +58,7 @@ destructMatches use_field_puns f scrut t jdg = do Just (dcs, apps) -> fmap unzipTrace $ for dcs $ \dc -> do let con = RealDataCon dc - ev = concatMap mkEvidence $ dataConInstArgTys dc apps + ev = concatMap (mkEvidence . scaledThing) $ dataConInstArgTys dc apps -- We explicitly do not need to add the method hypothesis to -- #syn_scoped method_hy = foldMap evidenceToHypothesis ev @@ -140,6 +141,7 @@ mkDestructPat already_in_scope con names in (names', ) $ ConPatIn (noLoc $ Unqual $ occName $ conLikeName con) + -- $ ConPat NoExtField (noLoc $ Unqual $ occName $ conLikeName con) $ RecCon $ HsRecFields rec_fields $ Nothing @@ -186,7 +188,7 @@ conLikeInstOrigArgTys' -- ^ Types of arguments to the ConLike with returned type is instantiated with the second argument. conLikeInstOrigArgTys' con uniTys = let exvars = conLikeExTys con - in conLikeInstOrigArgTys con $ + in map scaledThing $ conLikeInstOrigArgTys con $ uniTys ++ fmap mkTyVarTy exvars -- Rationale: At least in GHC <= 8.10, 'dataConInstOrigArgTys' -- unifies the second argument with DataCon's universals followed by existentials. @@ -230,7 +232,11 @@ destructLambdaCase' use_field_puns f jdg = do when (isDestructBlacklisted jdg) $ cut -- throwError NoApplicableTactic let g = jGoal jdg case splitFunTy_maybe (unCType g) of +#if __GLASGOW_HASKELL__ >= 900 + Just (_multiplicity, arg, _) | isAlgType arg -> +#else Just (arg, _) | isAlgType arg -> +#endif fmap (fmap noLoc lambdaCase) <$> destructMatches use_field_puns f Nothing (CType arg) jdg _ -> cut -- throwError $ GoalMismatch "destructLambdaCase'" g diff --git a/plugins/hls-tactics-plugin/src/Wingman/Context.hs b/plugins/hls-tactics-plugin/src/Wingman/Context.hs index 9aea0bf5eb..2e3880893a 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/Context.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/Context.hs @@ -11,6 +11,7 @@ import Development.IDE.GHC.Compat.Util import Wingman.GHC (normalizeType) import Wingman.Judgements.Theta import Wingman.Types +-- import GHC.Tc.Utils.TcType (tcSplitPhiTy, tcSplitTyConApp) mkContext diff --git a/plugins/hls-tactics-plugin/src/Wingman/EmptyCase.hs b/plugins/hls-tactics-plugin/src/Wingman/EmptyCase.hs index 42c62cfc19..8cbdd442e7 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/EmptyCase.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/EmptyCase.hs @@ -88,7 +88,7 @@ scrutinzedType :: EmptyCaseSort Type -> Maybe Type scrutinzedType (EmptyCase ty) = pure ty scrutinzedType (EmptyLamCase ty) = case tacticsSplitFunTy ty of - (_, _, tys, _) -> listToMaybe tys + (_, _, tys, _) -> listToMaybe $ map scaledThing tys ------------------------------------------------------------------------------ diff --git a/plugins/hls-tactics-plugin/src/Wingman/GHC.hs b/plugins/hls-tactics-plugin/src/Wingman/GHC.hs index 647d6cd60b..9da9f5ade7 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/GHC.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/GHC.hs @@ -17,6 +17,7 @@ import Data.Traversable import Development.IDE.GHC.Compat import Development.IDE.GHC.Compat.Util import GHC.SourceGen (lambda) +-- import GHC.Tc.Utils.TcType (tcSplitSigmaTy, tcSplitNestedSigmaTys, tcSplitFunTys, tyCoVarsOfTypeList) import Generics.SYB (Data, everything, everywhere, listify, mkQ, mkT) import Wingman.StaticPlugin (pattern MetaprogramSyntax) import Wingman.Types @@ -57,7 +58,7 @@ isFunction _ = True ------------------------------------------------------------------------------ -- | Split a function, also splitting out its quantified variables and theta -- context. -tacticsSplitFunTy :: Type -> ([TyVar], ThetaType, [Type], Type) +tacticsSplitFunTy :: Type -> ([TyVar], ThetaType, [Scaled Type], Type) tacticsSplitFunTy t = let (vars, theta, t') = tcSplitNestedSigmaTys t (args, res) = tcSplitFunTys t' @@ -182,7 +183,11 @@ allOccNames = everything (<>) $ mkQ mempty $ \case ------------------------------------------------------------------------------ -- | Unpack the relevant parts of a 'Match' +#if __GLASGOW_HASKELL__ >= 900 +pattern AMatch :: HsMatchContext (NoGhcTc GhcPs) -> [Pat GhcPs] -> HsExpr GhcPs -> Match GhcPs (LHsExpr GhcPs) +#else pattern AMatch :: HsMatchContext (NameOrRdrName (IdP GhcPs)) -> [Pat GhcPs] -> HsExpr GhcPs -> Match GhcPs (LHsExpr GhcPs) +#endif pattern AMatch ctx pats body <- Match { m_ctxt = ctx , m_pats = fmap fromPatCompat -> pats @@ -195,7 +200,7 @@ pattern SingleLet bind pats val expr <- HsLet _ (L _ (HsValBinds _ (ValBinds _ (bagToList -> - [(L _ (FunBind _ (L _ bind) (MG _ (L _ [L _ (AMatch _ pats val)]) _) _ _))]) _))) + [L _ (FunBind {fun_id = (L _ bind), fun_matches = (MG _ (L _ [L _ (AMatch _ pats val)]) _)})]) _))) (L _ expr) @@ -258,7 +263,11 @@ pattern LamCase matches <- -- @Just False@ if it can't be homomorphic -- @Just True@ if it can lambdaCaseable :: Type -> Maybe Bool +#if __GLASGOW_HASKELL__ >= 900 +lambdaCaseable (splitFunTy_maybe -> Just (_multiplicity, arg, res)) +#else lambdaCaseable (splitFunTy_maybe -> Just (arg, res)) +#endif | isJust (algebraicTyCon arg) = Just $ isJust $ algebraicTyCon res lambdaCaseable _ = Nothing diff --git a/plugins/hls-tactics-plugin/src/Wingman/Judgements/Theta.hs b/plugins/hls-tactics-plugin/src/Wingman/Judgements/Theta.hs index c2fccd4d7d..b9fc3e0059 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/Judgements/Theta.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/Judgements/Theta.hs @@ -180,7 +180,11 @@ absBinds _ _ = [] ------------------------------------------------------------------------------ -- | Extract evidence from 'HsWrapper's in scope wrapperBinds :: SrcSpan -> LHsExpr GhcTc -> [PredType] +#if __GLASGOW_HASKELL__ >= 900 +wrapperBinds dst (L src (XExpr (WrapExpr (HsWrap h _)))) +#else wrapperBinds dst (L src (HsWrap _ h _)) +#endif | dst `isSubspanOf` src = wrapper h wrapperBinds _ _ = [] @@ -196,7 +200,11 @@ matchBinds _ _ = [] ------------------------------------------------------------------------------ -- | Extract evidence from a 'ConPatOut'. patBinds :: Pat GhcTc -> [PredType] +#if __GLASGOW_HASKELL__ >= 900 +patBinds (ConPat{ pat_con_ext = ConPatTc { cpt_dicts = dicts }}) +#else patBinds (ConPatOut { pat_dicts = dicts }) +#endif = fmap idType dicts patBinds _ = [] diff --git a/plugins/hls-tactics-plugin/src/Wingman/LanguageServer.hs b/plugins/hls-tactics-plugin/src/Wingman/LanguageServer.hs index 3524194fb1..ae3b4eb5c4 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/LanguageServer.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/LanguageServer.hs @@ -292,8 +292,8 @@ getAlreadyDestructed (unTrack -> span) (unTrack -> binds) = getSpanAndTypeAtHole :: Tracked age Range - -> Tracked age (HieASTs b) - -> Maybe (Tracked age RealSrcSpan, b) + -> Tracked age (HieASTs Type) + -> Maybe (Tracked age RealSrcSpan, Type) getSpanAndTypeAtHole r@(unTrack -> range) (unTrack -> hf) = do join $ listToMaybe $ M.elems $ flip M.mapWithKey (getAsts hf) $ \fs ast -> case selectSmallestContaining (rangeToRealSrcSpan (FastString.unpackFS fs) range) ast of @@ -386,7 +386,11 @@ buildPatHy prov (fromPatCompat -> p0) = (RealDataCon $ tupleDataCon boxity $ length pats) tys $ zip [0.. ] pats - ConPatOut (L _ con) args _ _ _ f _ -> +#if __GLASGOW_HASKELL__ >= 900 + ConPat {pat_con = (L _ con), pat_con_ext = ConPatTc {cpt_arg_tys = args}, pat_args = f} -> +#else + ConPatOut {pat_con = (L _ con), pat_arg_tys = args, pat_args = f} -> +#endif case f of PrefixCon l_pgt -> mkDerivedConHypothesis prov con args $ zip [0..] l_pgt @@ -540,7 +544,11 @@ wingmanRules plId = do L span (HsVar _ (L _ name)) | isHole (occName name) -> maybeToList $ srcSpanToRange span +#if __GLASGOW_HASKELL__ >= 900 + L span (HsUnboundVar _ occ) +#else L span (HsUnboundVar _ (TrueExprHole occ)) +#endif | isHole occ -> maybeToList $ srcSpanToRange span #if __GLASGOW_HASKELL__ <= 808 diff --git a/plugins/hls-tactics-plugin/src/Wingman/LanguageServer/TacticProviders.hs b/plugins/hls-tactics-plugin/src/Wingman/LanguageServer/TacticProviders.hs index 631baf58b7..f6672a354e 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/LanguageServer/TacticProviders.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/LanguageServer/TacticProviders.hs @@ -296,7 +296,7 @@ homoFilter codomain domain = liftLambdaCase :: r -> (Type -> Type -> r) -> Type -> r liftLambdaCase nil f t = case tacticsSplitFunTy t of - (_, _, arg : _, res) -> f res arg + (_, _, arg : _, res) -> f res $ scaledThing arg _ -> nil diff --git a/plugins/hls-tactics-plugin/src/Wingman/Naming.hs b/plugins/hls-tactics-plugin/src/Wingman/Naming.hs index 05f5c2b85a..3dcb365d46 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/Naming.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/Naming.hs @@ -17,6 +17,7 @@ import Data.Traversable import Development.IDE.GHC.Compat.Core hiding (IsFunction) import Text.Hyphenation (hyphenate, english_US) import Wingman.GHC (tcTyVar_maybe) +-- import GHC.Tc.Utils.TcType (tcSplitFunTys, isBoolTy, isIntegerTy, isIntTy, isFloatingTy, isStringTy, tcSplitAppTys) ------------------------------------------------------------------------------ @@ -38,11 +39,11 @@ data Purpose pattern IsPredicate :: Type pattern IsPredicate <- - (tcSplitFunTys -> ([isFunTy -> False], isBoolTy -> True)) + (tcSplitFunTys -> ([isFunTy . scaledThing -> False], isBoolTy -> True)) pattern IsFunction :: [Type] -> Type -> Type pattern IsFunction args res <- - (tcSplitFunTys -> (args@(_:_), res)) + (first (map scaledThing) . tcSplitFunTys -> (args@(_:_), res)) pattern IsString :: Type pattern IsString <- diff --git a/plugins/hls-tactics-plugin/src/Wingman/Tactics.hs b/plugins/hls-tactics-plugin/src/Wingman/Tactics.hs index d6909a11ca..b2fb62d9ca 100644 --- a/plugins/hls-tactics-plugin/src/Wingman/Tactics.hs +++ b/plugins/hls-tactics-plugin/src/Wingman/Tactics.hs @@ -24,7 +24,6 @@ import Data.Maybe import Data.Set (Set) import qualified Data.Set as S import Data.Traversable (for) -import DataCon import Development.IDE.GHC.Compat hiding (empty) import GHC.Exts import GHC.SourceGen ((@@)) @@ -132,7 +131,8 @@ intros' params = rule $ \jdg -> do let g = jGoal jdg case tacticsSplitFunTy $ unCType g of (_, _, [], _) -> cut -- failure $ GoalMismatch "intros" g - (_, _, args, res) -> do + (_, _, scaledArgs, res) -> do + let args = map scaledThing scaledArgs ctx <- ask let gen_names = mkManyGoodNames (hyNamesInScope $ jEntireHypothesis jdg) args occs = case params of @@ -145,7 +145,7 @@ intros' params = rule $ \jdg -> do bound_occs = fmap fst bindings hy' = lambdaHypothesis top_hole bindings jdg' = introduce ctx hy' - $ withNewGoal (CType $ mkVisFunTys (drop num_occs args) res) jdg + $ withNewGoal (CType $ mkVisFunTys (drop num_occs scaledArgs) res) jdg ext <- newSubgoal jdg' pure $ ext @@ -291,6 +291,7 @@ apply (Unsaturated n) hi = tracing ("apply' " <> show (hi_name hi)) $ do . blacklistingDestruct . flip withNewGoal jdg . CType + . scaledThing ) saturated_args pure $ ext @@ -524,6 +525,7 @@ applyByType ty = tracing ("applyByType " <> show ty) $ do . blacklistingDestruct . flip withNewGoal jdg . CType + . scaledThing ) args app <- newSubgoal . blacklistingDestruct $ withNewGoal (CType ty) jdg pure $ @@ -540,7 +542,7 @@ nary :: Int -> TacticsM () nary n = do a <- newUnivar b <- newUnivar - applyByType $ mkVisFunTys (replicate n a) b + applyByType $ mkVisFunTys (replicate n $ unrestricted a) b self :: TacticsM () @@ -558,7 +560,7 @@ cata :: HyInfo CType -> TacticsM () cata hi = do (_, _, calling_args, _) <- tacticsSplitFunTy . unCType <$> getDefiningType - freshened_args <- traverse freshTyvars calling_args + freshened_args <- traverse (freshTyvars . scaledThing) calling_args diff <- hyDiff $ destruct hi -- For for every destructed term, check to see if it can unify with any of @@ -625,7 +627,7 @@ with_arg = rule $ \jdg -> do let g = jGoal jdg fresh_ty <- newUnivar a <- newSubgoal $ withNewGoal (CType fresh_ty) jdg - f <- newSubgoal $ withNewGoal (coerce mkVisFunTys [fresh_ty] g) jdg + f <- newSubgoal $ withNewGoal (coerce mkVisFunTys [unrestricted fresh_ty] g) jdg pure $ fmap noLoc $ (@@) <$> fmap unLoc f <*> fmap unLoc a diff --git a/plugins/hls-tactics-plugin/test/AutoTupleSpec.hs b/plugins/hls-tactics-plugin/test/AutoTupleSpec.hs index a3164f713f..11ba11e2ae 100644 --- a/plugins/hls-tactics-plugin/test/AutoTupleSpec.hs +++ b/plugins/hls-tactics-plugin/test/AutoTupleSpec.hs @@ -7,11 +7,10 @@ module AutoTupleSpec where import Control.Monad (replicateM) import Control.Monad.State (evalState) import Data.Either (isRight) -import OccName (mkVarOcc) +import Development.IDE.GHC.Compat.Core ( mkVarOcc, mkBoxedTupleTy ) import System.IO.Unsafe import Test.Hspec import Test.QuickCheck -import TysWiredIn (mkBoxedTupleTy) import Wingman.Judgements (mkFirstJudgement) import Wingman.Machinery import Wingman.Tactics (auto') diff --git a/plugins/hls-tactics-plugin/test/UnificationSpec.hs b/plugins/hls-tactics-plugin/test/UnificationSpec.hs index db39fdfe10..69ea9c2459 100644 --- a/plugins/hls-tactics-plugin/test/UnificationSpec.hs +++ b/plugins/hls-tactics-plugin/test/UnificationSpec.hs @@ -12,13 +12,13 @@ import Data.Maybe (mapMaybe) import qualified Data.Set as S import Data.Traversable import Data.Tuple (swap) -import TcType (substTy, tcGetTyVar_maybe) +import Development.IDE.GHC.Compat.Core (substTy, tcGetTyVar_maybe, mkBoxedTupleTy) import Test.Hspec import Test.QuickCheck -import TysWiredIn (mkBoxedTupleTy) import Wingman.GHC import Wingman.Machinery (newUnivar) import Wingman.Types +-- import GHC.Tc.Utils.TcType (tcGetTyVar_maybe) spec :: Spec diff --git a/plugins/hls-tactics-plugin/test/Utils.hs b/plugins/hls-tactics-plugin/test/Utils.hs index 36bdc8dfc8..25558be8f0 100644 --- a/plugins/hls-tactics-plugin/test/Utils.hs +++ b/plugins/hls-tactics-plugin/test/Utils.hs @@ -23,6 +23,7 @@ import qualified Data.Text.IO as T import Ide.Plugin.Tactic as Tactic import Language.LSP.Types import Language.LSP.Types.Lens hiding (actions, applyEdit, capabilities, executeCommand, id, line, message, name, rename, title) +import qualified Language.LSP.Types.Lens as J import System.Directory (doesFileExist) import System.FilePath import Test.Hls @@ -112,7 +113,10 @@ mkGoldenTest eq tc occ line col input = Just (InR CodeAction {_command = Just c}) <- pure $ find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions executeCommand c - _resp <- skipManyTill anyMessage (message SWorkspaceApplyEdit) + resp <- skipManyTill anyMessage (Right <$> message SWorkspaceApplyEdit <|> Left <$> message SWindowShowMessage) + case resp of + Left nm -> liftIO $ expectationFailure $ "Expected WorkspaceApplyEdit.\nInstead got message:\n " ++ show (nm ^. params . J.message) + Right _ -> pure () edited <- documentContents doc let expected_name = input <.> "expected" <.> "hs" -- Write golden tests if they don't already exist diff --git a/stack-9.0.1.yaml b/stack-9.0.1.yaml index 7de85baba2..6245968357 100644 --- a/stack-9.0.1.yaml +++ b/stack-9.0.1.yaml @@ -18,7 +18,7 @@ packages: - ./plugins/hls-rename-plugin - ./plugins/hls-retrie-plugin - ./plugins/hls-splice-plugin - # - ./plugins/hls-tactics-plugin + - ./plugins/hls-tactics-plugin # - ./plugins/hls-brittany-plugin # - ./plugins/hls-stylish-haskell-plugin - ./plugins/hls-floskell-plugin @@ -38,7 +38,9 @@ extra-deps: - dependent-sum-0.7.1.0@sha256:0e419237f5b86da3659772afff9cab355c0f8d5b3fdb15a5b30e673d8dc83941,2147 - extra-1.7.9 - floskell-0.10.5 -- ghc-source-gen-0.4.1.0 +- generic-lens-2.2.0.0@sha256:4008a39f464e377130346e46062e2ac1211f9d2e256bbb1857216e889c7196be,3867 +- generic-lens-core-2.2.0.0@sha256:b6b69e992f15fa80001de737f41f2123059011a1163d6c8941ce2e3ab44f8c03,2913 +# - ghc-source-gen-0.4.2.0 # Already in snapshot - heapsize-0.3.0.1@sha256:0b69aa97a46d819b700ac7b145f3b5493c3565cf2c5b8298682238d405d0326e,1417 - hie-bios-0.7.6 - hiedb-0.4.1.0 @@ -104,7 +106,6 @@ flags: pedantic: true class: false - tactic: false # Dependencies fail fourmolu: false stylishHaskell: false @@ -118,6 +119,6 @@ flags: embed: true nix: - packages: [ icu libcxx zlib ] + packages: [ icu libcxx zlib darwin.apple_sdk.frameworks.CoreServices darwin.apple_sdk.frameworks.Cocoa ] concurrent-tests: false diff --git a/test/functional/FunctionalCodeAction.hs b/test/functional/FunctionalCodeAction.hs index 6c0bd95c4a..820f2c8483 100644 --- a/test/functional/FunctionalCodeAction.hs +++ b/test/functional/FunctionalCodeAction.hs @@ -422,8 +422,7 @@ typedHoleTests = testGroup "typed hole code actions" [ , "foo x = maxBound" ] - , expectFailIfGhc9 "The wingman plugin doesn't yet compile in GHC9" $ - testCase "doesn't work when wingman is active" $ + , testCase "doesn't work when wingman is active" $ runSession hlsCommand fullCaps "test/testdata" $ do doc <- openDoc "TypedHoles.hs" "haskell" _ <- waitForDiagnosticsFromSource doc "typecheck" @@ -457,8 +456,7 @@ typedHoleTests = testGroup "typed hole code actions" [ , " stuff (A a) = A (a + 1)" ] - , expectFailIfGhc9 "The wingman plugin doesn't yet compile in GHC9" $ - testCase "doesnt show more suggestions when wingman is active" $ + , testCase "doesnt show more suggestions when wingman is active" $ runSession hlsCommand fullCaps "test/testdata" $ do doc <- openDoc "TypedHoles2.hs" "haskell" _ <- waitForDiagnosticsFromSource doc "typecheck" @@ -545,12 +543,6 @@ unusedTermTests = testGroup "unused term code actions" [ nub kinds @?= nub [Just CodeActionRefactorInline, Just CodeActionRefactorExtract] ] -expectFailIfGhc9 :: String -> TestTree -> TestTree -expectFailIfGhc9 reason = - case ghcVersion of - GHC90 -> expectFailBecause reason - _ -> id - disableWingman :: Session () disableWingman = sendConfigurationChanged $ def