Skip to content

Commit ff9a182

Browse files
isovectorjneiramergify[bot]
authored
Implement Tactic Featuresets (#1398)
* Implement featuresets * Make Tactics tests run with a full feature set * Respond to feedback from @wz1000 * Cleanup imports in Types Co-authored-by: Javier Neira <[email protected]> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent ba12bbd commit ff9a182

File tree

10 files changed

+206
-28
lines changed

10 files changed

+206
-28
lines changed

haskell-language-server.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -462,6 +462,7 @@ test-suite func-test
462462
Splice
463463
HaddockComments
464464
Ide.Plugin.Splice.Types
465+
Ide.Plugin.Tactic.FeatureSet
465466
Ide.Plugin.Tactic.TestTypes
466467
Ide.Plugin.Eval.Types
467468

plugins/hls-tactics-plugin/hls-tactics-plugin.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ library
2929
Ide.Plugin.Tactic.CodeGen.Utils
3030
Ide.Plugin.Tactic.Context
3131
Ide.Plugin.Tactic.Debug
32+
Ide.Plugin.Tactic.FeatureSet
3233
Ide.Plugin.Tactic.GHC
3334
Ide.Plugin.Tactic.Judgements
3435
Ide.Plugin.Tactic.KnownStrategies

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic.hs

+7-3
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ import Development.IDE.GHC.Compat
3333
import Development.IDE.GHC.ExactPrint
3434
import Development.Shake.Classes
3535
import Ide.Plugin.Tactic.CaseSplit
36+
import Ide.Plugin.Tactic.FeatureSet (hasFeature, Feature (..))
3637
import Ide.Plugin.Tactic.GHC
3738
import Ide.Plugin.Tactic.LanguageServer
3839
import Ide.Plugin.Tactic.LanguageServer.TacticProviders
@@ -66,13 +67,15 @@ descriptor plId = (defaultPluginDescriptor plId)
6667

6768
codeActionProvider :: PluginMethodHandler IdeState TextDocumentCodeAction
6869
codeActionProvider state plId (CodeActionParams _ _ (TextDocumentIdentifier uri) range _ctx)
69-
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri =
70+
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri = do
71+
features <- getFeatureSet
7072
liftIO $ fromMaybeT (Right $ List []) $ do
71-
(_, jdg, _, dflags) <- judgementForHole state nfp range
73+
(_, jdg, _, dflags) <- judgementForHole state nfp range features
7274
actions <- lift $
7375
-- This foldMap is over the function monoid.
7476
foldMap commandProvider [minBound .. maxBound]
7577
dflags
78+
features
7679
plId
7780
uri
7881
range
@@ -84,9 +87,10 @@ codeActionProvider _ _ _ = pure $ Right $ List []
8487
tacticCmd :: (OccName -> TacticsM ()) -> CommandFunction IdeState TacticParams
8588
tacticCmd tac state (TacticParams uri range var_name)
8689
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri = do
90+
features <- getFeatureSet
8791
ccs <- getClientCapabilities
8892
res <- liftIO $ fromMaybeT (Right Nothing) $ do
89-
(range', jdg, ctx, dflags) <- judgementForHole state nfp range
93+
(range', jdg, ctx, dflags) <- judgementForHole state nfp range features
9094
let span = rangeToRealSrcSpan (fromNormalizedFilePath nfp) range'
9195
pm <- MaybeT $ useAnnotatedSource "tacticsCmd" state nfp
9296

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/Context.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,6 @@ import Bag
77
import Control.Arrow
88
import Control.Monad.Reader
99
import Data.List
10-
import Data.Map (Map)
11-
import qualified Data.Map as M
1210
import Data.Maybe (mapMaybe)
1311
import Data.Set (Set)
1412
import qualified Data.Set as S
@@ -20,16 +18,18 @@ import OccName
2018
import TcRnTypes
2119
import TcType (substTy, tcSplitSigmaTy)
2220
import Unify (tcUnifyTy)
21+
import Ide.Plugin.Tactic.FeatureSet (FeatureSet)
2322

2423

25-
mkContext :: [(OccName, CType)] -> TcGblEnv -> Context
26-
mkContext locals tcg = Context
24+
mkContext :: FeatureSet -> [(OccName, CType)] -> TcGblEnv -> Context
25+
mkContext features locals tcg = Context
2726
{ ctxDefiningFuncs = locals
2827
, ctxModuleFuncs = fmap splitId
2928
. (getFunBindId =<<)
3029
. fmap unLoc
3130
. bagToList
3231
$ tcg_binds tcg
32+
, ctxFeatureSet = features
3333
}
3434

3535

Original file line numberDiff line numberDiff line change
@@ -0,0 +1,92 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE PatternSynonyms #-}
3+
{-# LANGUAGE ViewPatterns #-}
4+
5+
module Ide.Plugin.Tactic.FeatureSet
6+
( Feature (..)
7+
, FeatureSet
8+
, hasFeature
9+
, defaultFeatures
10+
, allFeatures
11+
, parseFeatureSet
12+
, prettyFeatureSet
13+
) where
14+
15+
import Data.List (intercalate)
16+
import Data.Maybe (mapMaybe, listToMaybe)
17+
import Data.Set (Set)
18+
import qualified Data.Set as S
19+
import qualified Data.Text as T
20+
21+
22+
------------------------------------------------------------------------------
23+
-- | All the available features. A 'FeatureSet' describes the ones currently
24+
-- available to the user.
25+
data Feature = CantHaveAnEmptyDataType
26+
deriving (Eq, Ord, Show, Read, Enum, Bounded)
27+
28+
29+
------------------------------------------------------------------------------
30+
-- | A collection of enabled features.
31+
type FeatureSet = Set Feature
32+
33+
34+
------------------------------------------------------------------------------
35+
-- | Parse a feature set.
36+
parseFeatureSet :: T.Text -> FeatureSet
37+
parseFeatureSet
38+
= mappend defaultFeatures
39+
. S.fromList
40+
. mapMaybe (readMaybe . mappend featurePrefix . rot13 . T.unpack)
41+
. T.split (== '/')
42+
43+
44+
------------------------------------------------------------------------------
45+
-- | Features that are globally enabled for all users.
46+
defaultFeatures :: FeatureSet
47+
defaultFeatures = S.fromList
48+
[
49+
]
50+
51+
52+
------------------------------------------------------------------------------
53+
-- | All available features.
54+
allFeatures :: FeatureSet
55+
allFeatures = S.fromList $ enumFromTo minBound maxBound
56+
57+
58+
------------------------------------------------------------------------------
59+
-- | Pretty print a feature set.
60+
prettyFeatureSet :: FeatureSet -> String
61+
prettyFeatureSet
62+
= intercalate "/"
63+
. fmap (rot13 . drop (length featurePrefix) . show)
64+
. S.toList
65+
66+
67+
------------------------------------------------------------------------------
68+
-- | Is a given 'Feature' currently enabled?
69+
hasFeature :: Feature -> FeatureSet -> Bool
70+
hasFeature = S.member
71+
72+
73+
------------------------------------------------------------------------------
74+
-- | Like 'read', but not partial.
75+
readMaybe :: Read a => String -> Maybe a
76+
readMaybe = fmap fst . listToMaybe . reads
77+
78+
79+
featurePrefix :: String
80+
featurePrefix = "Feature"
81+
82+
83+
rot13 :: String -> String
84+
rot13 = fmap (toEnum . rot13int . fromEnum)
85+
86+
87+
rot13int :: Integral a => a -> a
88+
rot13int x
89+
| (fromIntegral x :: Word) - 97 < 26 = 97 + rem (x - 84) 26
90+
| (fromIntegral x :: Word) - 65 < 26 = 65 + rem (x - 52) 26
91+
| otherwise = x
92+

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/LanguageServer.hs

+26-6
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE FlexibleContexts #-}
12
{-# LANGUAGE GADTs #-}
23
{-# LANGUAGE LambdaCase #-}
34
{-# LANGUAGE OverloadedStrings #-}
@@ -8,6 +9,8 @@ module Ide.Plugin.Tactic.LanguageServer where
89
import Control.Arrow
910
import Control.Monad
1011
import Control.Monad.Trans.Maybe
12+
import Data.Aeson (Value(Object), fromJSON)
13+
import Data.Aeson.Types (Result(Success, Error))
1114
import Data.Coerce
1215
import Data.Functor ((<&>))
1316
import Data.Generics.Aliases (mkQ)
@@ -29,12 +32,17 @@ import Development.IDE.Spans.LocalBindings (Bindings, getDefiningBindi
2932
import Development.Shake (RuleResult, Action)
3033
import Development.Shake.Classes
3134
import qualified FastString
35+
import Ide.Plugin.Config (PluginConfig(plcConfig))
36+
import qualified Ide.Plugin.Config as Plugin
3237
import Ide.Plugin.Tactic.Context
38+
import Ide.Plugin.Tactic.FeatureSet
3339
import Ide.Plugin.Tactic.GHC
3440
import Ide.Plugin.Tactic.Judgements
3541
import Ide.Plugin.Tactic.Range
36-
import Ide.Plugin.Tactic.TestTypes (TacticCommand)
42+
import Ide.Plugin.Tactic.TestTypes (cfg_feature_set, TacticCommand)
3743
import Ide.Plugin.Tactic.Types
44+
import Ide.PluginUtils (getPluginConfig)
45+
import Language.LSP.Server (MonadLsp)
3846
import Language.LSP.Types
3947
import OccName
4048
import Prelude hiding (span)
@@ -69,6 +77,16 @@ runStaleIde
6977
runStaleIde state nfp a = MaybeT $ runIde state $ useWithStale a nfp
7078

7179

80+
------------------------------------------------------------------------------
81+
-- | Get the current feature set from the plugin config.
82+
getFeatureSet :: MonadLsp Plugin.Config m => m FeatureSet
83+
getFeatureSet = do
84+
pcfg <- getPluginConfig "tactics"
85+
pure $ case fromJSON $ Object $ plcConfig pcfg of
86+
Success cfg -> cfg_feature_set cfg
87+
Error _ -> defaultFeatures
88+
89+
7290
getIdeDynflags
7391
:: IdeState
7492
-> NormalizedFilePath
@@ -87,8 +105,9 @@ judgementForHole
87105
:: IdeState
88106
-> NormalizedFilePath
89107
-> Range
108+
-> FeatureSet
90109
-> MaybeT IO (Range, Judgement, Context, DynFlags)
91-
judgementForHole state nfp range = do
110+
judgementForHole state nfp range features = do
92111
(asts, amapping) <- runStaleIde state nfp GetHieAst
93112
case asts of
94113
HAR _ _ _ _ (HieFromDisk _) -> fail "Need a fresh hie file"
@@ -97,21 +116,22 @@ judgementForHole state nfp range = do
97116
(tcmod, _) <- runStaleIde state nfp TypeCheck
98117
(rss, g) <- liftMaybe $ getSpanAndTypeAtHole amapping range hf
99118
resulting_range <- liftMaybe $ toCurrentRange amapping $ realSrcSpanToRange rss
100-
let (jdg, ctx) = mkJudgementAndContext g binds rss tcmod
119+
let (jdg, ctx) = mkJudgementAndContext features g binds rss tcmod
101120
dflags <- getIdeDynflags state nfp
102121
pure (resulting_range, jdg, ctx, dflags)
103122

104123

105124
mkJudgementAndContext
106-
:: Type
125+
:: FeatureSet
126+
-> Type
107127
-> Bindings
108128
-> RealSrcSpan
109129
-> TcModuleResult
110130
-> (Judgement, Context)
111-
mkJudgementAndContext g binds rss tcmod = do
131+
mkJudgementAndContext features g binds rss tcmod = do
112132
let tcg = tmrTypechecked tcmod
113133
tcs = tcg_binds tcg
114-
ctx = mkContext
134+
ctx = mkContext features
115135
(mapMaybe (sequenceA . (occName *** coerce))
116136
$ getDefiningBindings binds rss)
117137
tcg

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/LanguageServer/TacticProviders.hs

+19-8
Original file line numberDiff line numberDiff line change
@@ -21,9 +21,10 @@ import Data.Monoid
2121
import qualified Data.Text as T
2222
import Data.Traversable
2323
import Development.IDE.GHC.Compat
24-
import GHC.Generics (Generic)
24+
import GHC.Generics
2525
import GHC.LanguageExtensions.Type (Extension (LambdaCase))
2626
import Ide.Plugin.Tactic.Auto
27+
import Ide.Plugin.Tactic.FeatureSet
2728
import Ide.Plugin.Tactic.GHC
2829
import Ide.Plugin.Tactic.Judgements
2930
import Ide.Plugin.Tactic.Tactics
@@ -77,6 +78,7 @@ commandProvider HomomorphismLambdaCase =
7778
-- UI.
7879
type TacticProvider
7980
= DynFlags
81+
-> FeatureSet
8082
-> PluginId
8183
-> Uri
8284
-> Range
@@ -93,23 +95,32 @@ data TacticParams = TacticParams
9395
deriving anyclass (ToJSON, FromJSON)
9496

9597

98+
------------------------------------------------------------------------------
99+
-- | Restrict a 'TacticProvider', making sure it appears only when the given
100+
-- 'Feature' is in the feature set.
101+
requireFeature :: Feature -> TacticProvider -> TacticProvider
102+
requireFeature f tp dflags fs plId uri range jdg = do
103+
guard $ hasFeature f fs
104+
tp dflags fs plId uri range jdg
105+
106+
96107
------------------------------------------------------------------------------
97108
-- | Restrict a 'TacticProvider', making sure it appears only when the given
98109
-- predicate holds for the goal.
99110
requireExtension :: Extension -> TacticProvider -> TacticProvider
100-
requireExtension ext tp dflags plId uri range jdg =
111+
requireExtension ext tp dflags fs plId uri range jdg =
101112
case xopt ext dflags of
102-
True -> tp dflags plId uri range jdg
113+
True -> tp dflags fs plId uri range jdg
103114
False -> pure []
104115

105116

106117
------------------------------------------------------------------------------
107118
-- | Restrict a 'TacticProvider', making sure it appears only when the given
108119
-- predicate holds for the goal.
109120
filterGoalType :: (Type -> Bool) -> TacticProvider -> TacticProvider
110-
filterGoalType p tp dflags plId uri range jdg =
121+
filterGoalType p tp dflags fs plId uri range jdg =
111122
case p $ unCType $ jGoal jdg of
112-
True -> tp dflags plId uri range jdg
123+
True -> tp dflags fs plId uri range jdg
113124
False -> pure []
114125

115126

@@ -120,13 +131,13 @@ filterBindingType
120131
:: (Type -> Type -> Bool) -- ^ Goal and then binding types.
121132
-> (OccName -> Type -> TacticProvider)
122133
-> TacticProvider
123-
filterBindingType p tp dflags plId uri range jdg =
134+
filterBindingType p tp dflags fs plId uri range jdg =
124135
let hy = jHypothesis jdg
125136
g = jGoal jdg
126137
in fmap join $ for (unHypothesis hy) $ \hi ->
127138
let ty = unCType $ hi_type hi
128139
in case p (unCType g) ty of
129-
True -> tp (hi_name hi) ty dflags plId uri range jdg
140+
True -> tp (hi_name hi) ty dflags fs plId uri range jdg
130141
False -> pure []
131142

132143

@@ -146,7 +157,7 @@ useNameFromHypothesis f name = do
146157
-- | Terminal constructor for providing context-sensitive tactics. Tactics
147158
-- given by 'provide' are always available.
148159
provide :: TacticCommand -> T.Text -> TacticProvider
149-
provide tc name _ plId uri range _ = do
160+
provide tc name _ _ plId uri range _ = do
150161
let title = tacticTitle tc name
151162
params = TacticParams { tp_file = uri , tp_range = range , tp_var_name = name }
152163
cmd = mkLspCommand plId (tcCommandId tc) title (Just [toJSON params])

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/TestTypes.hs

+23
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33
module Ide.Plugin.Tactic.TestTypes where
44

55
import qualified Data.Text as T
6+
import Data.Aeson
7+
import Ide.Plugin.Tactic.FeatureSet
68

79
------------------------------------------------------------------------------
810
-- | The list of tactics exposed to the outside world. These are attached to
@@ -25,3 +27,24 @@ tacticTitle Destruct var = "Case split on " <> var
2527
tacticTitle Homomorphism var = "Homomorphic case split on " <> var
2628
tacticTitle DestructLambdaCase _ = "Lambda case split"
2729
tacticTitle HomomorphismLambdaCase _ = "Homomorphic lambda case split"
30+
31+
32+
------------------------------------------------------------------------------
33+
-- | Plugin configuration for tactics
34+
newtype Config = Config
35+
{ cfg_feature_set :: FeatureSet
36+
}
37+
38+
emptyConfig :: Config
39+
emptyConfig = Config defaultFeatures
40+
41+
instance ToJSON Config where
42+
toJSON (Config features) = object
43+
[ "features" .= prettyFeatureSet features
44+
]
45+
46+
instance FromJSON Config where
47+
parseJSON = withObject "Config" $ \obj -> do
48+
features <- parseFeatureSet <$> obj .: "features"
49+
pure $ Config features
50+

0 commit comments

Comments
 (0)