@@ -5,6 +5,9 @@ module Development.IDE.Types.Exports
5
5
(
6
6
IdentInfo (.. ),
7
7
ExportsMap (.. ),
8
+ rendered,
9
+ moduleNameText,
10
+ occNameText,
8
11
createExportsMap,
9
12
createExportsMapMg,
10
13
createExportsMapTc,
@@ -24,6 +27,7 @@ import Data.HashSet (HashSet)
24
27
import qualified Data.HashSet as Set
25
28
import Data.List (foldl' , isSuffixOf )
26
29
import Data.Text (Text , pack )
30
+ import Data.Text.Encoding (decodeUtf8 )
27
31
import Development.IDE.GHC.Compat
28
32
import Development.IDE.GHC.Orphans ()
29
33
import Development.IDE.GHC.Util
@@ -61,12 +65,30 @@ instance Monoid ExportsMap where
61
65
type IdentifierText = Text
62
66
type ModuleNameText = Text
63
67
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
+
64
87
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
70
92
}
71
93
deriving (Generic , Show )
72
94
deriving anyclass Hashable
@@ -82,34 +104,23 @@ instance NFData IdentInfo where
82
104
-- deliberately skip the rendered field
83
105
rnf name `seq` rnf parent `seq` rnf isDatacon `seq` rnf moduleNameText
84
106
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 ]
95
108
mkIdentInfos mod (AvailName n) =
96
- [IdentInfo (nameOccName n) (renderIEWrapped n) Nothing (isDataConName n) mod ]
109
+ [IdentInfo (nameOccName n) Nothing (isDataConName n) mod ]
97
110
mkIdentInfos mod (AvailFL fl) =
98
- [IdentInfo (nameOccName n) (renderIEWrapped n) Nothing (isDataConName n) mod ]
111
+ [IdentInfo (nameOccName n) Nothing (isDataConName n) mod ]
99
112
where
100
113
n = flSelector fl
101
114
mkIdentInfos mod (AvailTC parent (n: nn) flds)
102
115
-- Following the GHC convention that parent == n if parent is exported
103
116
| n == parent
104
- = [ IdentInfo (nameOccName n) (renderIEWrapped n) ( Just $! parentP ) (isDataConName n) mod
117
+ = [ IdentInfo (nameOccName n) (Just $! nameOccName parent ) (isDataConName n) mod
105
118
| n <- nn ++ map flSelector flds
106
119
] ++
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 ]
110
121
111
122
mkIdentInfos mod (AvailTC _ nn flds)
112
- = [ IdentInfo (nameOccName n) (renderIEWrapped n) Nothing (isDataConName n) mod
123
+ = [ IdentInfo (nameOccName n) Nothing (isDataConName n) mod
113
124
| n <- nn ++ map flSelector flds
114
125
]
115
126
@@ -160,25 +171,20 @@ createExportsMapHieDb withHieDb = do
160
171
mods <- withHieDb getAllIndexedMods
161
172
idents <- forM (filter (nonInternalModules . modInfoName . hieModInfo) mods) $ \ m -> do
162
173
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)
165
175
let exportsMap = Map. fromListWith (<>) (concat idents)
166
- return $ ExportsMap exportsMap $ buildModuleExportMap (concat idents)
176
+ return $! ExportsMap exportsMap $ buildModuleExportMap (concat idents)
167
177
where
168
178
wrap identInfo = (rendered identInfo, Set. fromList [identInfo])
169
179
-- 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
174
181
175
182
unpackAvail :: ModuleName -> IfaceExport -> [(Text , Text , [IdentInfo ])]
176
183
unpackAvail mn
177
- | nonInternalModules mn = map f . mkIdentInfos mod
184
+ | nonInternalModules mn = map f . mkIdentInfos mn
178
185
| otherwise = const []
179
186
where
180
- ! mod = pack $ moduleNameString mn
181
- f id @ IdentInfo {.. } = (printOutputable name, moduleNameText,[id ])
187
+ f id @ IdentInfo {.. } = (printOutputable name, moduleNameText id ,[id ])
182
188
183
189
184
190
identInfoToKeyVal :: IdentInfo -> (ModuleNameText , IdentInfo )
@@ -198,9 +204,9 @@ buildModuleExportMapFrom modIfaces = do
198
204
199
205
extractModuleExports :: ModIface -> (Text , HashSet IdentInfo )
200
206
extractModuleExports modIFace = do
201
- let modName = pack $ moduleNameString $ moduleName $ mi_module modIFace
207
+ let modName = moduleName $ mi_module modIFace
202
208
let functionSet = Set. fromList $ concatMap (mkIdentInfos modName) $ mi_exports modIFace
203
- (modName, functionSet)
209
+ (moduleNameText' modName, functionSet)
204
210
205
211
sortAndGroup :: [(ModuleNameText , IdentInfo )] -> Map. HashMap ModuleNameText (HashSet IdentInfo )
206
212
sortAndGroup assocs = Map. fromListWith (<>) [(k, Set. fromList [v]) | (k, v) <- assocs]
0 commit comments