Skip to content

Commit 64ef035

Browse files
committed
improve memory usage of ExportsMap
Storing rendered names as `Text`, especially for parents, adds a lot of duplication to the ExportsMap. Instead we store the `OccName`s directly, which have hash-consed symbols due stored as `FastStrings` and render it out on demand (which is just decoding the UTF-8 FastString to UTF-16 text for text <2.0, and essentially free on text >2.0).
1 parent f91edea commit 64ef035

File tree

4 files changed

+71
-56
lines changed

4 files changed

+71
-56
lines changed

ghcide/src/Development/IDE/GHC/Compat.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,8 @@ module Development.IDE.GHC.Compat(
4343
#endif
4444

4545
FastStringCompat,
46+
bytesFS,
47+
mkFastStringByteString,
4648
nodeInfo',
4749
getNodeIds,
4850
sourceNodeInfo,
@@ -206,6 +208,7 @@ import VarEnv (emptyInScopeSet,
206208
#endif
207209

208210
#if MIN_VERSION_ghc(9,0,0)
211+
import GHC.Data.FastString
209212
import GHC.Core
210213
import GHC.Data.StringBuffer
211214
import GHC.Driver.Session hiding (ExposePackage)
@@ -224,6 +227,7 @@ import GHC.Iface.Make (mkIfaceExports)
224227
import qualified GHC.SysTools.Tasks as SysTools
225228
import qualified GHC.Types.Avail as Avail
226229
#else
230+
import FastString
227231
import qualified Avail
228232
import DynFlags hiding (ExposePackage)
229233
import HscTypes

ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -284,24 +284,26 @@ mkExtCompl label =
284284

285285

286286
fromIdentInfo :: Uri -> IdentInfo -> Maybe T.Text -> CompItem
287-
fromIdentInfo doc IdentInfo{..} q = CI
287+
fromIdentInfo doc id@IdentInfo{..} q = CI
288288
{ compKind= occNameToComKind name
289-
, insertText=rendered
290-
, provenance = DefinedIn moduleNameText
291-
, label=rendered
289+
, insertText=rend
290+
, provenance = DefinedIn mod
291+
, label=rend
292292
, isInfix=Nothing
293-
, isTypeCompl= not isDatacon && isUpper (T.head rendered)
293+
, isTypeCompl= not isDatacon && isUpper (T.head rend)
294294
, additionalTextEdits= Just $
295295
ExtendImport
296296
{ doc,
297-
thingParent = parent,
298-
importName = moduleNameText,
297+
thingParent = occNameText <$> parent,
298+
importName = mod,
299299
importQual = q,
300-
newThing = rendered
300+
newThing = rend
301301
}
302302
, nameDetails = Nothing
303303
, isLocalCompletion = False
304304
}
305+
where rend = rendered id
306+
mod = moduleNameText id
305307

306308
cacheDataProducer :: Uri -> [ModuleName] -> Module -> GlobalRdrEnv-> GlobalRdrEnv -> [LImportDecl GhcPs] -> CachedCompletions
307309
cacheDataProducer uri visibleMods curMod globalEnv inScopeEnv limports =

ghcide/src/Development/IDE/Types/Exports.hs

Lines changed: 40 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,9 @@ module Development.IDE.Types.Exports
55
(
66
IdentInfo(..),
77
ExportsMap(..),
8+
rendered,
9+
moduleNameText,
10+
occNameText,
811
createExportsMap,
912
createExportsMapMg,
1013
createExportsMapTc,
@@ -24,6 +27,7 @@ import Data.HashSet (HashSet)
2427
import qualified Data.HashSet as Set
2528
import Data.List (foldl', isSuffixOf)
2629
import Data.Text (Text, pack)
30+
import Data.Text.Encoding (decodeUtf8)
2731
import Development.IDE.GHC.Compat
2832
import Development.IDE.GHC.Orphans ()
2933
import Development.IDE.GHC.Util
@@ -61,12 +65,30 @@ instance Monoid ExportsMap where
6165
type IdentifierText = Text
6266
type ModuleNameText = Text
6367

68+
69+
rendered :: IdentInfo -> IdentifierText
70+
rendered = occNameText . name
71+
72+
-- | Render an identifier as imported or exported style.
73+
-- TODO: pattern synonymoccNameText :: OccName -> Text
74+
occNameText :: OccName -> IdentifierText
75+
occNameText name
76+
| isTcOcc name && isSymOcc name = "type " <> renderOcc
77+
| otherwise = renderOcc
78+
where
79+
renderOcc = decodeUtf8 . bytesFS . occNameFS $ name
80+
81+
moduleNameText :: IdentInfo -> ModuleNameText
82+
moduleNameText = moduleNameText' . identModuleName
83+
84+
moduleNameText' :: ModuleName -> ModuleNameText
85+
moduleNameText' = decodeUtf8 . bytesFS . moduleNameFS
86+
6487
data IdentInfo = IdentInfo
65-
{ name :: !OccName
66-
, rendered :: Text
67-
, parent :: !(Maybe Text)
68-
, isDatacon :: !Bool
69-
, moduleNameText :: !Text
88+
{ name :: !OccName
89+
, parent :: !(Maybe OccName)
90+
, isDatacon :: !Bool
91+
, identModuleName :: !ModuleName
7092
}
7193
deriving (Generic, Show)
7294
deriving anyclass Hashable
@@ -82,34 +104,23 @@ instance NFData IdentInfo where
82104
-- deliberately skip the rendered field
83105
rnf name `seq` rnf parent `seq` rnf isDatacon `seq` rnf moduleNameText
84106

85-
-- | Render an identifier as imported or exported style.
86-
-- TODO: pattern synonym
87-
renderIEWrapped :: Name -> Text
88-
renderIEWrapped n
89-
| isTcOcc occ && isSymOcc occ = "type " <> pack (printName n)
90-
| otherwise = pack $ printName n
91-
where
92-
occ = occName n
93-
94-
mkIdentInfos :: Text -> AvailInfo -> [IdentInfo]
107+
mkIdentInfos :: ModuleName -> AvailInfo -> [IdentInfo]
95108
mkIdentInfos mod (AvailName n) =
96-
[IdentInfo (nameOccName n) (renderIEWrapped n) Nothing (isDataConName n) mod]
109+
[IdentInfo (nameOccName n) Nothing (isDataConName n) mod]
97110
mkIdentInfos mod (AvailFL fl) =
98-
[IdentInfo (nameOccName n) (renderIEWrapped n) Nothing (isDataConName n) mod]
111+
[IdentInfo (nameOccName n) Nothing (isDataConName n) mod]
99112
where
100113
n = flSelector fl
101114
mkIdentInfos mod (AvailTC parent (n:nn) flds)
102115
-- Following the GHC convention that parent == n if parent is exported
103116
| n == parent
104-
= [ IdentInfo (nameOccName n) (renderIEWrapped n) (Just $! parentP) (isDataConName n) mod
117+
= [ IdentInfo (nameOccName n) (Just $! nameOccName parent) (isDataConName n) mod
105118
| n <- nn ++ map flSelector flds
106119
] ++
107-
[ IdentInfo (nameOccName n) (renderIEWrapped n) Nothing (isDataConName n) mod]
108-
where
109-
parentP = pack $ printName parent
120+
[ IdentInfo (nameOccName n) Nothing (isDataConName n) mod]
110121

111122
mkIdentInfos mod (AvailTC _ nn flds)
112-
= [ IdentInfo (nameOccName n) (renderIEWrapped n) Nothing (isDataConName n) mod
123+
= [ IdentInfo (nameOccName n) Nothing (isDataConName n) mod
113124
| n <- nn ++ map flSelector flds
114125
]
115126

@@ -160,25 +171,20 @@ createExportsMapHieDb withHieDb = do
160171
mods <- withHieDb getAllIndexedMods
161172
idents <- forM (filter (nonInternalModules . modInfoName . hieModInfo) mods) $ \m -> do
162173
let mn = modInfoName $ hieModInfo m
163-
mText = pack $ moduleNameString mn
164-
fmap (wrap . unwrap mText) <$> withHieDb (\hieDb -> getExportsForModule hieDb mn)
174+
fmap (wrap . unwrap mn) <$> withHieDb (\hieDb -> getExportsForModule hieDb mn)
165175
let exportsMap = Map.fromListWith (<>) (concat idents)
166-
return $ ExportsMap exportsMap $ buildModuleExportMap (concat idents)
176+
return $! ExportsMap exportsMap $ buildModuleExportMap (concat idents)
167177
where
168178
wrap identInfo = (rendered identInfo, Set.fromList [identInfo])
169179
-- unwrap :: ExportRow -> IdentInfo
170-
unwrap m ExportRow{..} = IdentInfo exportName n p exportIsDatacon m
171-
where
172-
n = pack (occNameString exportName)
173-
p = pack . occNameString <$> exportParent
180+
unwrap m ExportRow{..} = IdentInfo exportName exportParent exportIsDatacon m
174181

175182
unpackAvail :: ModuleName -> IfaceExport -> [(Text, Text, [IdentInfo])]
176183
unpackAvail mn
177-
| nonInternalModules mn = map f . mkIdentInfos mod
184+
| nonInternalModules mn = map f . mkIdentInfos mn
178185
| otherwise = const []
179186
where
180-
!mod = pack $ moduleNameString mn
181-
f id@IdentInfo {..} = (printOutputable name, moduleNameText,[id])
187+
f id@IdentInfo {..} = (printOutputable name, moduleNameText id,[id])
182188

183189

184190
identInfoToKeyVal :: IdentInfo -> (ModuleNameText, IdentInfo)
@@ -198,9 +204,9 @@ buildModuleExportMapFrom modIfaces = do
198204

199205
extractModuleExports :: ModIface -> (Text, HashSet IdentInfo)
200206
extractModuleExports modIFace = do
201-
let modName = pack $ moduleNameString $ moduleName $ mi_module modIFace
207+
let modName = moduleName $ mi_module modIFace
202208
let functionSet = Set.fromList $ concatMap (mkIdentInfos modName) $ mi_exports modIFace
203-
(modName, functionSet)
209+
(moduleNameText' modName, functionSet)
204210

205211
sortAndGroup :: [(ModuleNameText, IdentInfo)] -> Map.HashMap ModuleNameText (HashSet IdentInfo)
206212
sortAndGroup assocs = Map.fromListWith (<>) [(k, Set.fromList [v]) | (k, v) <- assocs]

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 17 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ import Data.Maybe
3737
import Data.Ord (comparing)
3838
import qualified Data.Set as S
3939
import qualified Data.Text as T
40+
import qualified Data.Text.Encoding as T
4041
import qualified Data.Text.Utf16.Rope as Rope
4142
import Data.Tuple.Extra (fst3)
4243
import Development.IDE.Core.Rules
@@ -1048,11 +1049,10 @@ suggestExtendImport exportsMap (L _ HsModule {hsmodImports}) Diagnostic{_range=_
10481049
-- fallback to using GHC suggestion even though it is not always correct
10491050
| otherwise
10501051
= Just IdentInfo
1051-
{ name = mkVarOcc $ T.unpack binding
1052-
, rendered = binding
1052+
{ name = mkVarOccFS $ mkFastStringByteString $ T.encodeUtf8 binding
10531053
, parent = Nothing
10541054
, isDatacon = False
1055-
, moduleNameText = mod}
1055+
, identModuleName = mkModuleNameFS $ mkFastStringByteString $ T.encodeUtf8 mod}
10561056
#endif
10571057

10581058
data HidingMode
@@ -1452,18 +1452,18 @@ suggestNewOrExtendImportForClassMethod packageExportsMap ps fileContents Diagnos
14521452
_message
14531453
"‘([^’]*)’ is not a \\(visible\\) method of class ‘([^’]*)’",
14541454
idents <-
1455-
maybe [] (Set.toList . Set.filter (\x -> parent x == Just className)) $
1455+
maybe [] (Set.toList . Set.filter (\x -> fmap occNameText (parent x) == Just className)) $
14561456
Map.lookup methodName $ getExportsMap packageExportsMap =
14571457
mconcat $ suggest <$> idents
14581458
| otherwise = []
14591459
where
1460-
suggest identInfo@IdentInfo {moduleNameText}
1460+
suggest identInfo
14611461
| importStyle <- NE.toList $ importStyles identInfo,
1462-
mImportDecl <- findImportDeclByModuleName (hsmodImports . unLoc . astA $ ps) (T.unpack moduleNameText) =
1462+
mImportDecl <- findImportDeclByModuleName (hsmodImports . unLoc . astA $ ps) (T.unpack moduleText) =
14631463
case mImportDecl of
14641464
-- extend
14651465
Just decl ->
1466-
[ ( "Add " <> renderImportStyle style <> " to the import list of " <> moduleNameText,
1466+
[ ( "Add " <> renderImportStyle style <> " to the import list of " <> moduleText,
14671467
quickFixImportKind' "extend" style,
14681468
[Right $ uncurry extendImport (unImportStyle style) decl]
14691469
)
@@ -1474,12 +1474,13 @@ suggestNewOrExtendImportForClassMethod packageExportsMap ps fileContents Diagnos
14741474
| Just (range, indent) <- newImportInsertRange ps fileContents
14751475
->
14761476
(\(kind, unNewImport -> x) -> (x, kind, [Left $ TextEdit range (x <> "\n" <> T.replicate indent " ")])) <$>
1477-
[ (quickFixImportKind' "new" style, newUnqualImport moduleNameText rendered False)
1477+
[ (quickFixImportKind' "new" style, newUnqualImport moduleText rendered False)
14781478
| style <- importStyle,
14791479
let rendered = renderImportStyle style
14801480
]
1481-
<> [(quickFixImportKind "new.all", newImportAll moduleNameText)]
1481+
<> [(quickFixImportKind "new.all", newImportAll moduleText)]
14821482
| otherwise -> []
1483+
where moduleText = moduleNameText identInfo
14831484
#endif
14841485

14851486
suggestNewImport :: ExportsMap -> Annotated ParsedSource -> T.Text -> Diagnostic -> [(T.Text, CodeActionKind, TextEdit)]
@@ -2039,16 +2040,18 @@ data ImportStyle
20392040
deriving Show
20402041

20412042
importStyles :: IdentInfo -> NonEmpty ImportStyle
2042-
importStyles IdentInfo {parent, rendered, isDatacon}
2043-
| Just p <- parent
2043+
importStyles i@IdentInfo {parent, isDatacon}
2044+
| Just p <- pr
20442045
-- Constructors always have to be imported via their parent data type, but
20452046
-- methods and associated type/data families can also be imported as
20462047
-- top-level exports.
2047-
= ImportViaParent rendered p
2048-
:| [ImportTopLevel rendered | not isDatacon]
2048+
= ImportViaParent rend p
2049+
:| [ImportTopLevel rend | not isDatacon]
20492050
<> [ImportAllConstructors p]
20502051
| otherwise
2051-
= ImportTopLevel rendered :| []
2052+
= ImportTopLevel rend :| []
2053+
where rend = rendered i
2054+
pr = occNameText <$> parent
20522055

20532056
-- | Used for adding new imports
20542057
renderImportStyle :: ImportStyle -> T.Text

0 commit comments

Comments
 (0)