Skip to content

Commit a8fd672

Browse files
committed
Miscellaneous Code Fixes.
- Remove unneeded imports/functions. - Export only specified functions from each module (and add Haddock Comment if necessary) - Minor text changes for accuracy
1 parent ffa9259 commit a8fd672

File tree

4 files changed

+46
-58
lines changed

4 files changed

+46
-58
lines changed

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs

Lines changed: 34 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -1,41 +1,33 @@
1-
{-# LANGUAGE DataKinds #-}
2-
{-# LANGUAGE DeriveGeneric #-}
3-
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4-
{-# LANGUAGE TypeFamilies #-}
5-
{-# LANGUAGE TypeOperators #-}
6-
7-
module Ide.Plugin.AlternateNumberFormat where
8-
9-
import Control.Lens ((^.))
10-
import Control.Monad.Except (ExceptT, MonadIO, liftIO)
11-
import qualified Data.HashMap.Strict as HashMap
12-
import Data.Maybe (fromMaybe, isJust)
13-
import Data.Text (Text)
14-
import qualified Data.Text as T
15-
import Debug.Trace (traceM)
16-
import Development.IDE (GetParsedModule (GetParsedModule),
17-
IdeState, RuleResult,
18-
Rules, define, ideLogger,
19-
realSrcSpanToRange,
20-
runAction, use,
21-
useWithStale)
22-
import Development.IDE.Core.PositionMapping (PositionMapping)
23-
import Development.IDE.GHC.Compat hiding (getSrcSpan)
24-
import Development.IDE.GHC.Compat.Util (toList)
25-
import Development.IDE.Graph.Classes (Hashable, NFData)
26-
import Development.IDE.Types.Logger as Logger
27-
import GHC.Generics (Generic)
28-
import Ide.Plugin.Conversion (FormatType,
29-
alternateFormat,
30-
toFormatTypes)
31-
import Ide.Plugin.Literals (Literal (..),
32-
collectLiterals,
33-
getSrcSpan, getSrcText)
34-
import Ide.Plugin.Retrie (handleMaybe,
35-
handleMaybeM, response)
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE DeriveGeneric #-}
3+
{-# LANGUAGE TypeFamilies #-}
4+
{-# LANGUAGE TypeOperators #-}
5+
module Ide.Plugin.AlternateNumberFormat (descriptor) where
6+
7+
import Control.Lens ((^.))
8+
import Control.Monad.Except (ExceptT, MonadIO, liftIO)
9+
import qualified Data.HashMap.Strict as HashMap
10+
import Data.Text (Text)
11+
import qualified Data.Text as T
12+
import Development.IDE (GetParsedModule (GetParsedModule),
13+
IdeState, RuleResult, Rules,
14+
define, ideLogger,
15+
realSrcSpanToRange, runAction,
16+
use)
17+
import Development.IDE.GHC.Compat hiding (getSrcSpan)
18+
import Development.IDE.GHC.Compat.Util (toList)
19+
import Development.IDE.Graph.Classes (Hashable, NFData)
20+
import Development.IDE.Types.Logger as Logger
21+
import GHC.Generics (Generic)
22+
import Ide.Plugin.Conversion (FormatType, alternateFormat,
23+
toFormatTypes)
24+
import Ide.Plugin.Literals (Literal (..), collectLiterals,
25+
getSrcSpan, getSrcText)
26+
import Ide.Plugin.Retrie (handleMaybe, handleMaybeM,
27+
response)
3628
import Ide.Types
3729
import Language.LSP.Types
38-
import Language.LSP.Types.Lens (uri)
30+
import Language.LSP.Types.Lens (uri)
3931

4032
descriptor :: PluginId -> PluginDescriptor IdeState
4133
descriptor plId = (defaultPluginDescriptor plId)
@@ -51,8 +43,8 @@ instance NFData CollectLiterals
5143

5244
type instance RuleResult CollectLiterals = CollectLiteralsResult
5345

54-
data CollectLiteralsResult = CLR {
55-
literals :: [Literal]
46+
data CollectLiteralsResult = CLR
47+
{ literals :: [Literal]
5648
, formatTypes :: [FormatType]
5749
} deriving (Generic)
5850

@@ -94,10 +86,9 @@ codeActionHandler state _ (CodeActionParams _ _ docId currRange _) = response $
9486
mkCodeAction :: NormalizedFilePath -> Literal -> Text -> Command |? CodeAction
9587
mkCodeAction nfp lit alt = InR CodeAction {
9688
_title = "Convert " <> getSrcText lit <> " into " <> alt
97-
-- what should this actually be?
98-
, _kind = Just $ CodeActionUnknown "alternate.style"
89+
, _kind = Just $ CodeActionUnknown "quickfix.literals.style"
9990
, _diagnostics = Nothing
100-
, _isPreferred = Just True
91+
, _isPreferred = Nothing
10192
, _disabled = Nothing
10293
, _edit = Just $ mkWorkspaceEdit nfp lit alt
10394
, _command = Nothing
@@ -123,12 +114,12 @@ getNormalizedFilePath docId = handleMaybe "Error: converting to NormalizedFilePa
123114
$ toNormalizedUri (docId ^. uri)
124115

125116
requestLiterals :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m CollectLiteralsResult
126-
requestLiterals state = handleMaybeM "Error: Could not get ParsedModule"
117+
requestLiterals state = handleMaybeM "Error: Could not Collect Literals"
127118
. liftIO
128119
. runAction "AlternateNumberFormat.CollectLiterals" state
129120
. use CollectLiterals
130121

131122

132123
logIO :: (MonadIO m, Show a) => IdeState -> a -> m ()
133-
logIO state = liftIO . Logger.logInfo (ideLogger state) . T.pack . show
124+
logIO state = liftIO . Logger.logDebug (ideLogger state) . T.pack . show
134125

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Conversion.hs

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -143,21 +143,12 @@ toFormatTypes = (<>) baseFormatTypes . mapMaybe (`lookup` numericPairs)
143143
numericPairs :: [(Extension, FormatType)]
144144
numericPairs = [(NumericUnderscores, NoFormat), (NegativeLiterals, NoFormat)] <> intPairs <> fracPairs
145145

146-
numericFormats :: [FormatType]
147-
numericFormats = map snd numericPairs
148-
149146
intPairs :: [(Extension, FormatType)]
150147
intPairs = [(BinaryLiterals, IntFormat BinaryFormat), (NumDecimals, IntFormat NumDecimalFormat)]
151148

152-
intFormats :: [FormatType]
153-
intFormats = map snd intPairs
154-
155149
fracPairs :: [(Extension, FormatType)]
156150
fracPairs = [(HexFloatLiterals, FracFormat HexFloatFormat)]
157151

158-
fracFormats :: [FormatType]
159-
fracFormats = map snd fracPairs
160-
161152
-- Generate up to 3 possible choices where:
162153
-- dropWhile (\d -> val `div` d) > 1000) implies we want at MOST 3 digits to left of decimal
163154
-- takeWhile (val >) implies we want to stop once we start to get numbers like: 0.1e[N]

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Literals.hs

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,18 @@
22
{-# LANGUAGE DerivingVia #-}
33
{-# LANGUAGE FlexibleInstances #-}
44
{-# LANGUAGE RankNTypes #-}
5-
module Ide.Plugin.Literals where
6-
import Data.Maybe (fromMaybe, maybeToList)
5+
module Ide.Plugin.Literals (
6+
collectLiterals
7+
, Literal(..)
8+
, getSrcText
9+
, getSrcSpan
10+
) where
11+
712
import Data.Set (Set)
813
import qualified Data.Set as S
914
import Data.Text (Text)
1015
import qualified Data.Text as T
11-
import Development.IDE.GHC.Compat
16+
import Development.IDE.GHC.Compat hiding (getSrcSpan)
1217
import Development.IDE.GHC.Util (unsafePrintSDoc)
1318
import Development.IDE.Graph.Classes (NFData (rnf))
1419
import qualified GHC.Generics as GHC
@@ -18,6 +23,7 @@ import Generics.SYB (Data, Typeable, cast,
1823
-- data type to capture what type of literal we are dealing with
1924
-- provides location and possibly source text (for OverLits) as well as it's value
2025
-- we currently don't have any use for PrimLiterals. They never have source text so we always drop them
26+
-- | Captures a Numeric Literals Location, Source Text, and Value.
2127
data Literal = IntLiteral RealSrcSpan Text Integer
2228
| FracLiteral RealSrcSpan Text Rational
2329
deriving (GHC.Generic, Show, Ord, Eq)
@@ -27,11 +33,13 @@ instance NFData RealSrcSpan where
2733

2834
instance NFData Literal
2935

36+
-- | Return a Literal's Source representation
3037
getSrcText :: Literal -> Text
3138
getSrcText = \case
3239
IntLiteral _ txt _ -> txt
3340
FracLiteral _ txt _ -> txt
3441

42+
-- | Return a Literal's Real Source location
3543
getSrcSpan :: Literal -> RealSrcSpan
3644
getSrcSpan = \case
3745
IntLiteral ss _ _ -> ss
@@ -87,8 +95,6 @@ getLiteralAsList' lit = maybe S.empty S.singleton . flip getLiteral lit
8795
getLiteral :: RealSrcSpan -> HsLit GhcPs -> Maybe Literal
8896
getLiteral sSpan = \case
8997
HsInt _ val -> fromIntegralLit sSpan val
90-
-- Ignore this case for now
91-
-- HsInteger _ val _ -> Just $ IntLiteral sSpan Nothing val
9298
HsRat _ val _ -> fromFractionalLit sSpan val
9399
_ -> Nothing
94100

plugins/hls-alternate-number-format-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ findAlternateNumberActions = pure . filter isAlternateNumberCodeAction . rights
8484
isAlternateNumberCodeAction CodeAction{_kind} = case _kind of
8585
Nothing -> False
8686
Just kind -> case kind of
87-
CodeActionUnknown txt -> txt == "alternate.style"
87+
CodeActionUnknown txt -> txt == "quickfix.literals.style"
8888
_ -> False
8989

9090
-- most helpers derived from explicit-imports-plugin Main Test file

0 commit comments

Comments
 (0)