Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Gives information about symbols at a given point in DAML files. These are all pure functions that should execute quickly.
Synopsis
- atPoint :: IdeOptions -> HieAstResult -> DocAndTyThingMap -> HscEnv -> Position -> IO (Maybe (Maybe Range, [Text]))
- gotoDefinition :: MonadIO m => WithHieDb -> LookupModule m -> IdeOptions -> Map ModuleName NormalizedFilePath -> HieASTs a -> Position -> MaybeT m [Location]
- gotoTypeDefinition :: MonadIO m => WithHieDb -> LookupModule m -> IdeOptions -> HieAstResult -> Position -> MaybeT m [Location]
- documentHighlight :: Monad m => HieASTs a -> RefMap a -> Position -> MaybeT m [DocumentHighlight]
- pointCommand :: HieASTs t -> Position -> (HieAST t -> a) -> [a]
- referencesAtPoint :: MonadIO m => WithHieDb -> NormalizedFilePath -> Position -> FOIReferences -> m [Location]
- computeTypeReferences :: Foldable f => f (HieAST Type) -> Map Name [Span]
- newtype FOIReferences = FOIReferences (HashMap NormalizedFilePath (HieAstResult, PositionMapping))
- defRowToSymbolInfo :: Res DefRow -> Maybe SymbolInformation
- getNamesAtPoint :: HieASTs a -> Position -> PositionMapping -> [Name]
- toCurrentLocation :: PositionMapping -> Location -> Maybe Location
- rowToLoc :: Res RefRow -> Maybe Location
- nameToLocation :: MonadIO m => WithHieDb -> LookupModule m -> Name -> m (Maybe [Location])
- type LookupModule m = FilePath -> ModuleName -> Unit -> Bool -> MaybeT m Uri
Documentation
atPoint :: IdeOptions -> HieAstResult -> DocAndTyThingMap -> HscEnv -> Position -> IO (Maybe (Maybe Range, [Text])) Source #
Synopsis for the name at a given position.
gotoDefinition :: MonadIO m => WithHieDb -> LookupModule m -> IdeOptions -> Map ModuleName NormalizedFilePath -> HieASTs a -> Position -> MaybeT m [Location] Source #
Locate the definition of the name at a given position.
gotoTypeDefinition :: MonadIO m => WithHieDb -> LookupModule m -> IdeOptions -> HieAstResult -> Position -> MaybeT m [Location] Source #
documentHighlight :: Monad m => HieASTs a -> RefMap a -> Position -> MaybeT m [DocumentHighlight] Source #
:: MonadIO m | |
=> WithHieDb | |
-> NormalizedFilePath | The file the cursor is in |
-> Position | position in the file |
-> FOIReferences | references data for FOIs |
-> m [Location] |
newtype FOIReferences Source #
HieFileResult for files of interest, along with the position mappings
getNamesAtPoint :: HieASTs a -> Position -> PositionMapping -> [Name] Source #
toCurrentLocation :: PositionMapping -> Location -> Maybe Location Source #
nameToLocation :: MonadIO m => WithHieDb -> LookupModule m -> Name -> m (Maybe [Location]) Source #
Given a Name
attempt to find the location where it is defined.
type LookupModule m = FilePath -> ModuleName -> Unit -> Bool -> MaybeT m Uri Source #
Gives a Uri for the module, given the .hie file location and the the module info The Bool denotes if it is a boot module