Skip to content

Commit 88795f6

Browse files
authored
Remove FeatureSet (#1902)
It's what Hamming would have wanted
1 parent 0cc89d2 commit 88795f6

File tree

12 files changed

+32
-204
lines changed

12 files changed

+32
-204
lines changed

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,6 @@ library
3434
Wingman.Context
3535
Wingman.Debug
3636
Wingman.EmptyCase
37-
Wingman.FeatureSet
3837
Wingman.GHC
3938
Wingman.Judgements
4039
Wingman.Judgements.SYB

plugins/hls-tactics-plugin/src/Wingman/EmptyCase.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,6 @@ import Prelude hiding (span)
3232
import Prelude hiding (span)
3333
import TcRnTypes (tcg_binds)
3434
import Wingman.CodeGen (destructionFor)
35-
import Wingman.FeatureSet
3635
import Wingman.GHC
3736
import Wingman.Judgements
3837
import Wingman.LanguageServer
@@ -63,8 +62,6 @@ codeLensProvider state plId (CodeLensParams _ _ (TextDocumentIdentifier uri))
6362
cfg <- getTacticConfig plId
6463
ccs <- getClientCapabilities
6564
liftIO $ fromMaybeT (Right $ List []) $ do
66-
guard $ hasFeature FeatureEmptyCase $ cfg_feature_set cfg
67-
6865
dflags <- getIdeDynflags state nfp
6966
TrackedStale pm _ <- stale GetAnnotatedParsedSource
7067
TrackedStale binds bind_map <- stale GetBindings

plugins/hls-tactics-plugin/src/Wingman/FeatureSet.hs

Lines changed: 0 additions & 99 deletions
This file was deleted.

plugins/hls-tactics-plugin/src/Wingman/KnownStrategies.hs

Lines changed: 6 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,40 +1,29 @@
11
module Wingman.KnownStrategies where
22

3+
import Control.Applicative (empty)
34
import Control.Monad.Error.Class
5+
import Control.Monad.Reader.Class (asks)
6+
import Data.Foldable (for_)
47
import OccName (mkVarOcc)
58
import Refinery.Tactic
69
import Wingman.Context (getCurrentDefinitions, getKnownInstance)
10+
import Wingman.Judgements (jGoal)
711
import Wingman.KnownStrategies.QuickCheck (deriveArbitrary)
812
import Wingman.Machinery (tracing)
913
import Wingman.Tactics
1014
import Wingman.Types
11-
import Wingman.Judgements (jGoal)
12-
import Data.Foldable (for_)
13-
import Wingman.FeatureSet
14-
import Control.Applicative (empty)
15-
import Control.Monad.Reader.Class (asks)
1615

1716

1817
knownStrategies :: TacticsM ()
1918
knownStrategies = choice
2019
[ known "fmap" deriveFmap
2120
, known "mempty" deriveMempty
2221
, known "arbitrary" deriveArbitrary
23-
, featureGuard FeatureKnownMonoid $ known "<>" deriveMappend
24-
, featureGuard FeatureKnownMonoid $ known "mappend" deriveMappend
22+
, known "<>" deriveMappend
23+
, known "mappend" deriveMappend
2524
]
2625

2726

28-
------------------------------------------------------------------------------
29-
-- | Guard a tactic behind a feature.
30-
featureGuard :: Feature -> TacticsM a -> TacticsM a
31-
featureGuard feat t = do
32-
fs <- asks $ cfg_feature_set . ctxConfig
33-
case hasFeature feat fs of
34-
True -> t
35-
False -> empty
36-
37-
3827
known :: String -> TacticsM () -> TacticsM ()
3928
known name t = do
4029
getCurrentDefinitions >>= \case

plugins/hls-tactics-plugin/src/Wingman/LanguageServer.hs

Lines changed: 1 addition & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,6 @@ import Retrie (transformA)
6161
import SrcLoc (containsSpan)
6262
import TcRnTypes (tcg_binds, TcGblEnv (tcg_rdr_env))
6363
import Wingman.Context
64-
import Wingman.FeatureSet
6564
import Wingman.GHC
6665
import Wingman.Judgements
6766
import Wingman.Judgements.SYB (everythingContaining, metaprogramQ)
@@ -137,7 +136,6 @@ unsafeRunStaleIde herald state nfp a = do
137136
properties :: Properties
138137
'[ 'PropertyKey "hole_severity" ('TEnum (Maybe DiagnosticSeverity))
139138
, 'PropertyKey "max_use_ctor_actions" 'TInteger
140-
, 'PropertyKey "features" 'TString
141139
, 'PropertyKey "timeout_duration" 'TInteger
142140
, 'PropertyKey "auto_gas" 'TInteger
143141
]
@@ -146,8 +144,6 @@ properties = emptyProperties
146144
"The depth of the search tree when performing \"Attempt to fill hole\". Bigger values will be able to derive more solutions, but will take exponentially more time." 4
147145
& defineIntegerProperty #timeout_duration
148146
"The timeout for Wingman actions, in seconds" 2
149-
& defineStringProperty #features
150-
"Feature set used by Wingman" ""
151147
& defineIntegerProperty #max_use_ctor_actions
152148
"Maximum number of `Use constructor <x>` code actions that can appear" 5
153149
& defineEnumProperty #hole_severity
@@ -165,16 +161,10 @@ properties = emptyProperties
165161
getTacticConfig :: MonadLsp Plugin.Config m => PluginId -> m Config
166162
getTacticConfig pId =
167163
Config
168-
<$> (parseFeatureSet <$> usePropertyLsp #features pId properties)
169-
<*> usePropertyLsp #max_use_ctor_actions pId properties
164+
<$> usePropertyLsp #max_use_ctor_actions pId properties
170165
<*> usePropertyLsp #timeout_duration pId properties
171166
<*> usePropertyLsp #auto_gas pId properties
172167

173-
------------------------------------------------------------------------------
174-
-- | Get the current feature set from the plugin config.
175-
getFeatureSet :: MonadLsp Plugin.Config m => PluginId -> m FeatureSet
176-
getFeatureSet = fmap cfg_feature_set . getTacticConfig
177-
178168

179169
getIdeDynflags
180170
:: IdeState

plugins/hls-tactics-plugin/src/Wingman/LanguageServer/Metaprogram.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,8 +45,6 @@ hoverProvider state plId (HoverParams (TextDocumentIdentifier uri) (unsafeMkCurr
4545

4646
cfg <- getTacticConfig plId
4747
liftIO $ fromMaybeT (Right Nothing) $ do
48-
-- guard $ hasFeature FeatureEmptyCase $ cfg_feature_set cfg
49-
5048
holes <- getMetaprogramsAtSpan state nfp $ RealSrcSpan $ unTrack loc
5149

5250
fmap (Right . Just) $

plugins/hls-tactics-plugin/src/Wingman/LanguageServer/TacticProviders.hs

Lines changed: 12 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Wingman.LanguageServer.TacticProviders
1212
) where
1313

1414
import Control.Monad
15+
import Control.Monad.Reader (runReaderT)
1516
import Data.Aeson
1617
import Data.Bool (bool)
1718
import Data.Coerce
@@ -30,15 +31,13 @@ import Language.LSP.Types
3031
import OccName
3132
import Prelude hiding (span)
3233
import Wingman.Auto
33-
import Wingman.FeatureSet
3434
import Wingman.GHC
3535
import Wingman.Judgements
3636
import Wingman.Machinery (useNameFromHypothesis)
3737
import Wingman.Metaprogramming.Lexer (ParserContext)
3838
import Wingman.Metaprogramming.Parser (parseMetaprogram)
3939
import Wingman.Tactics
4040
import Wingman.Types
41-
import Control.Monad.Reader (runReaderT)
4241

4342

4443
------------------------------------------------------------------------------
@@ -115,7 +114,6 @@ commandProvider Destruct =
115114
provide Destruct $ T.pack $ occNameString occ
116115
commandProvider DestructPun =
117116
requireHoleSort (== Hole) $
118-
requireFeature FeatureDestructPun $
119117
filterBindingType destructPunFilter $ \occ _ ->
120118
provide DestructPun $ T.pack $ occNameString occ
121119
commandProvider Homomorphism =
@@ -134,38 +132,33 @@ commandProvider HomomorphismLambdaCase =
134132
provide HomomorphismLambdaCase ""
135133
commandProvider DestructAll =
136134
requireHoleSort (== Hole) $
137-
requireFeature FeatureDestructAll $
138135
withJudgement $ \jdg ->
139136
case _jIsTopHole jdg && jHasBoundArgs jdg of
140137
True -> provide DestructAll ""
141138
False -> mempty
142139
commandProvider UseDataCon =
143140
requireHoleSort (== Hole) $
144141
withConfig $ \cfg ->
145-
requireFeature FeatureUseDataCon $
146-
filterTypeProjection
147-
( guardLength (<= cfg_max_use_ctor_actions cfg)
148-
. fromMaybe []
149-
. fmap fst
150-
. tacticsGetDataCons
151-
) $ \dcon ->
152-
provide UseDataCon
153-
. T.pack
154-
. occNameString
155-
. occName
156-
$ dataConName dcon
142+
filterTypeProjection
143+
( guardLength (<= cfg_max_use_ctor_actions cfg)
144+
. fromMaybe []
145+
. fmap fst
146+
. tacticsGetDataCons
147+
) $ \dcon ->
148+
provide UseDataCon
149+
. T.pack
150+
. occNameString
151+
. occName
152+
$ dataConName dcon
157153
commandProvider Refine =
158154
requireHoleSort (== Hole) $
159-
requireFeature FeatureRefineHole $
160155
provide Refine ""
161156
commandProvider BeginMetaprogram =
162157
requireGHC88OrHigher $
163-
requireFeature FeatureMetaprogram $
164158
requireHoleSort (== Hole) $
165159
provide BeginMetaprogram ""
166160
commandProvider RunMetaprogram =
167161
requireGHC88OrHigher $
168-
requireFeature FeatureMetaprogram $
169162
withMetaprogram $ \mp ->
170163
provide RunMetaprogram mp
171164

@@ -213,16 +206,6 @@ data TacticParams = TacticParams
213206
deriving anyclass (ToJSON, FromJSON)
214207

215208

216-
------------------------------------------------------------------------------
217-
-- | Restrict a 'TacticProvider', making sure it appears only when the given
218-
-- 'Feature' is in the feature set.
219-
requireFeature :: Feature -> TacticProvider -> TacticProvider
220-
requireFeature f tp tpd =
221-
case hasFeature f $ cfg_feature_set $ tpd_config tpd of
222-
True -> tp tpd
223-
False -> pure []
224-
225-
226209
requireHoleSort :: (HoleSort -> Bool) -> TacticProvider -> TacticProvider
227210
requireHoleSort p tp tpd =
228211
case p $ tpd_hole_sort tpd of

plugins/hls-tactics-plugin/src/Wingman/Types.hs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,6 @@ import Type (TCvSubst, Var, eqType, nonDetCmpType, emptyTCvSubst)
4141
import UniqSupply (takeUniqFromSupply, mkSplitUniqSupply, UniqSupply)
4242
import Unique (nonDetCmpUnique, Uniquable, getUnique, Unique)
4343
import Wingman.Debug
44-
import Wingman.FeatureSet
4544

4645

4746
------------------------------------------------------------------------------
@@ -84,17 +83,15 @@ tacticTitle = (mappend "Wingman: " .) . go
8483
------------------------------------------------------------------------------
8584
-- | Plugin configuration for tactics
8685
data Config = Config
87-
{ cfg_feature_set :: FeatureSet
88-
, cfg_max_use_ctor_actions :: Int
86+
{ cfg_max_use_ctor_actions :: Int
8987
, cfg_timeout_seconds :: Int
9088
, cfg_auto_gas :: Int
9189
}
9290
deriving (Eq, Ord, Show)
9391

9492
emptyConfig :: Config
9593
emptyConfig = Config
96-
{ cfg_feature_set = mempty
97-
, cfg_max_use_ctor_actions = 5
94+
{ cfg_max_use_ctor_actions = 5
9895
, cfg_timeout_seconds = 2
9996
, cfg_auto_gas = 4
10097
}

plugins/hls-tactics-plugin/test/CodeAction/AutoSpec.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@ module CodeAction.AutoSpec where
55
import Wingman.Types
66
import Test.Hspec
77
import Utils
8-
import Wingman.FeatureSet (allFeatures)
98

109

1110
spec :: Spec
@@ -83,6 +82,6 @@ spec = do
8382

8483

8584
describe "messages" $ do
86-
mkShowMessageTest allFeatures Auto "" 2 8 "MessageForallA" TacticErrors
87-
mkShowMessageTest allFeatures Auto "" 7 8 "MessageCantUnify" TacticErrors
85+
mkShowMessageTest Auto "" 2 8 "MessageForallA" TacticErrors
86+
mkShowMessageTest Auto "" 7 8 "MessageCantUnify" TacticErrors
8887

plugins/hls-tactics-plugin/test/CodeAction/RefineSpec.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@ module CodeAction.RefineSpec where
55
import Wingman.Types
66
import Test.Hspec
77
import Utils
8-
import Wingman.FeatureSet (allFeatures)
98

109

1110
spec :: Spec
@@ -19,5 +18,5 @@ spec = do
1918
refineTest 8 10 "RefineGADT"
2019

2120
describe "messages" $ do
22-
mkShowMessageTest allFeatures Refine "" 2 8 "MessageForallA" TacticErrors
21+
mkShowMessageTest Refine "" 2 8 "MessageForallA" TacticErrors
2322

plugins/hls-tactics-plugin/test/CodeLens/EmptyCaseSpec.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,11 @@ module CodeLens.EmptyCaseSpec where
44

55
import Test.Hspec
66
import Utils
7-
import Wingman.FeatureSet (allFeatures)
87

98

109
spec :: Spec
1110
spec = do
12-
let test = mkCodeLensTest allFeatures
11+
let test = mkCodeLensTest
1312

1413
describe "golden" $ do
1514
test "EmptyCaseADT"

0 commit comments

Comments
 (0)