@@ -41,27 +41,35 @@ hsimportDescriptor plId = PluginDescriptor
4141 , pluginFormattingProvider = Nothing
4242 }
4343
44+ -- | Type of the symbol to import.
45+ -- Important to offer the correct import list, or hiding code action.
4446data SymbolType
45- = Symbol
46- | Constructor
47- | Type
47+ = Symbol -- ^ Symbol is a simple function
48+ | Constructor -- ^ Symbol is a constructor
49+ | Type -- ^ Symbol is a type
4850 deriving (Show , Eq , Generics.Generic , ToJSON , FromJSON )
4951
5052
5153-- | What of the symbol should be taken.
54+ -- Import a simple symbol, or a value constructor.
5255data SymbolKind
53- = Only SymbolName -- ^ only the symbol should be taken
54- | AllOf DatatypeName -- ^ all constructors or methods of the symbol should be taken: Symbol(.. )
55- | OneOf DatatypeName SymbolName -- ^ some constructors or methods of the symbol should be taken: Symbol(X, Y )
56+ = Only SymbolName -- ^ Only the symbol should be taken
57+ | OneOf DatatypeName SymbolName -- ^ Some constructors or methods of the symbol should be taken: Symbol(X )
58+ | AllOf DatatypeName -- ^ All constructors or methods of the symbol should be taken: Symbol(.. )
5659 deriving (Show , Eq , Generics.Generic , ToJSON , FromJSON )
5760
58- -- | The imported or from the import hidden symbol.
61+ -- | Disambiguates between an import action and an hiding action.
62+ -- Can be used to determine suggestion tpye from ghc-mod,
63+ -- e.g. whether ghc-mod suggests to hide an identifier or to import an identifier.
64+ -- Also important later, to know how the symbol shall be imported.
5965data SymbolImport a
6066 = Import a -- ^ the symbol to import
6167 | Hiding a -- ^ the symbol to hide from the import
6268 deriving (Show , Eq , Generics.Generic , ToJSON , FromJSON )
6369
6470
71+ -- | Utility to retrieve the contents of the 'SymbolImport'.
72+ -- May never fail.
6573extractSymbolImport :: SymbolImport a -> a
6674extractSymbolImport (Hiding s) = s
6775extractSymbolImport (Import s) = s
@@ -70,19 +78,26 @@ type ModuleName = T.Text
7078type SymbolName = T. Text
7179type DatatypeName = T. Text
7280
81+ -- | How to import a module.
82+ -- Can be used to express to import a whole module or only specific symbols
83+ -- from a module.
84+ -- Is used to either hide symbols from an import or use an import-list to
85+ -- import only a specific symbol.
7386data ImportStyle
7487 = Simple -- ^ Import the whole module
7588 | Complex (SymbolImport SymbolKind ) -- ^ Complex operation, import module hiding symbols or import only selected symbols.
7689 deriving (Show , Eq , Generics.Generic , ToJSON , FromJSON )
7790
91+ -- | Contains information about the diagnostic, the symbol ghc-mod
92+ -- complained about and what the kind of the symbol is and whether
93+ -- to import or hide the symbol as suggested by ghc-mod.
7894data ImportDiagnostic = ImportDiagnostic
7995 { diagnostic :: J. Diagnostic
8096 , term :: SymbolName
8197 , termType :: SymbolImport SymbolType
8298 }
8399 deriving (Show , Eq , Generics.Generic , ToJSON , FromJSON )
84100
85-
86101-- | Import Parameters for Modules.
87102-- Can be used to import every symbol from a module,
88103-- or to import only a specific function from a module.
@@ -189,23 +204,31 @@ importModule uri impStyle modName =
189204 $ IdeResultOk (J. WorkspaceEdit newChanges newDocChanges)
190205 else return $ IdeResultOk (J. WorkspaceEdit mChanges mDocChanges)
191206
207+ -- | Convert the import style arguments into HsImport arguments.
208+ -- Takes an input and an output file as well as a module name.
192209importStyleToHsImportArgs
193210 :: FilePath -> FilePath -> ModuleName -> ImportStyle -> HsImport. HsImportArgs
194211importStyleToHsImportArgs input output modName style =
195- let defaultArgs =
212+ let defaultArgs = -- Default args, must be set every time.
196213 HsImport. defaultArgs { HsImport. moduleName = T. unpack modName
197214 , HsImport. inputSrcFile = input
198215 , HsImport. outputSrcFile = output
199216 }
217+
218+ kindToArgs :: SymbolKind -> HsImport. HsImportArgs
200219 kindToArgs kind = case kind of
220+ -- Only import a single symbol e.g. Data.Text (isPrefixOf)
201221 Only sym -> defaultArgs { HsImport. symbolName = T. unpack sym }
222+ -- Import a constructor e.g. Data.Mabye (Maybe(Just))
202223 OneOf dt sym -> defaultArgs { HsImport. symbolName = T. unpack dt
203224 , HsImport. with = [T. unpack sym]
204225 }
226+ -- Import all constructors e.g. Data.Maybe (Maybe(..))
205227 AllOf dt -> defaultArgs { HsImport. symbolName = T. unpack dt
206228 , HsImport. all = True
207229 }
208230 in case style of
231+ -- If the import style is simple, import thw whole module
209232 Simple -> defaultArgs
210233 Complex s -> case s of
211234 Hiding kind -> kindToArgs kind {- TODO: wait for hsimport version bump -}
@@ -265,8 +288,8 @@ codeActionProvider plId docId _ context = do
265288 (x : _) -> " is:exact " <> x
266289 applySearchStyle (Relax relax) termName = relax termName
267290
268- -- | Turn a search term with function name into Import Actions.
269- -- Function name may be of only the exact phrase to import.
291+ -- | Turn a search term with function name into an Import Actions.
292+ -- The function name may be of only the exact phrase to import.
270293 -- The resulting CodeAction's contain a general import of a module or
271294 -- uses an Import-List.
272295 --
@@ -282,20 +305,35 @@ codeActionProvider plId docId _ context = do
282305 termToActions style modules impDiagnostic =
283306 concat <$> mapM (importModuleAction style impDiagnostic) modules
284307
308+ -- | Creates various import actions for a module and the diagnostic.
309+ -- Possible import actions depend on the type of the symbol to import.
310+ -- It may be a 'Constructor', so the import actions need to be different
311+ -- to a simple function symbol.
312+ -- Thus, it may return zero, one or multiple import actions for a module.
313+ -- List of import actions does contain no duplicates.
285314 importModuleAction
286315 :: SearchStyle -> ImportDiagnostic -> ModuleName -> IdeM [J. CodeAction ]
287316 importModuleAction searchStyle impDiagnostic moduleName =
288317 catMaybes <$> sequenceA codeActions
289318 where
290319 importListActions :: [IdeM (Maybe J. CodeAction )]
291320 importListActions = case searchStyle of
321+ -- If the search has been relaxed by a custom function,
322+ -- we cant know how much the search query has been altered
323+ -- and how close the result terms are to the initial diagnostic.
324+ -- Thus, we cant offer more specific imports.
292325 Relax _ -> []
293326 _ -> catMaybes
294327 $ case extractSymbolImport $ termType impDiagnostic of
328+ -- If the term to import is a simple symbol, such as a function,
329+ -- import only this function
295330 Symbol
296331 -> [ mkImportAction moduleName impDiagnostic . Just . Only
297332 <$> symName (term impDiagnostic)
298333 ]
334+ -- Constructors can be imported in two ways, either all
335+ -- constructors of a type or only a subset.
336+ -- We can only import a single constructor at a time though.
299337 Constructor
300338 -> [ mkImportAction moduleName impDiagnostic . Just . AllOf
301339 <$> datatypeName (term impDiagnostic)
@@ -304,22 +342,43 @@ codeActionProvider plId docId _ context = do
304342 <$> datatypeName (term impDiagnostic)
305343 <*> symName (term impDiagnostic)
306344 ]
345+ -- If we are looking for a type, import it as just a symbol
307346 Type
308347 -> [ mkImportAction moduleName impDiagnostic . Just . Only
309348 <$> symName (term impDiagnostic)]
310349
350+ -- | All code actions that may be available
351+ -- Currently, omits all
311352 codeActions :: [IdeM (Maybe J. CodeAction )]
312353 codeActions = case termType impDiagnostic of
313- Hiding _ -> []
354+ Hiding _ -> [] {- If we are hiding an import, we can not import
355+ a module hiding everything from it. -}
314356 Import _ -> [mkImportAction moduleName impDiagnostic Nothing ]
357+ -- ^ Simple import, import the whole module
315358 ++ importListActions
316359
360+ -- | Retrieve the function signature of a term such as
361+ -- >>> signatureOf "take :: Int -> [a] -> [a]"
362+ -- Just " Int -> [a] -> [a]"
317363 signatureOf :: T. Text -> Maybe T. Text
318364 signatureOf sig = do
319365 let parts = T. splitOn " ::" sig
320366 typeSig <- S. tailMay parts
321367 S. headMay typeSig
322368
369+ -- | Retrieve the datatype name of a Constructor.
370+ --
371+ -- >>> datatypeName "Null :: Data.Aeson.Internal.Types.Value"
372+ -- Just "Value"
373+ --
374+ -- >>> datatypeName "take :: Int -> [a] -> [a]" -- Not a constructor
375+ -- Just "[a]"
376+ --
377+ -- >>> datatypeName "Just :: a -> Maybe a"
378+ -- Just "Maybe"
379+ --
380+ -- Thus, the result of this function only makes sense,
381+ -- if the symbol kind of the diagnostic term is of type 'Constructor'
323382 datatypeName :: T. Text -> Maybe T. Text
324383 datatypeName sig = do
325384 sig_ <- signatureOf sig
@@ -330,6 +389,10 @@ codeActionProvider plId docId _ context = do
330389 let qualifiedDtNameParts = T. splitOn " ." qualifiedDtName
331390 S. lastMay qualifiedDtNameParts
332391
392+ -- | Name of a symbol. May contain a function signature.
393+ --
394+ -- >>> symName "take :: Int -> [a] -> [a]"
395+ -- Just "take"
333396 symName :: T. Text -> Maybe SymbolName
334397 symName = S. headMay . T. words
335398
0 commit comments