Safe Haskell | None |
---|---|
Language | Haskell98 |
- findDeclaration :: Database -> String -> ExceptT String IO [ModuleDeclaration]
- findModule :: Database -> String -> ExceptT String IO [Module]
- fileModule :: Database -> FilePath -> ExceptT String IO Module
- lookupSymbol :: Database -> Cabal -> FilePath -> String -> ExceptT String IO [ModuleDeclaration]
- whois :: Database -> Cabal -> FilePath -> String -> ExceptT String IO [Declaration]
- scopeModules :: Database -> Cabal -> FilePath -> ExceptT String IO [Module]
- scope :: Database -> Cabal -> FilePath -> Bool -> ExceptT String IO [Declaration]
- completions :: Database -> Cabal -> FilePath -> String -> Bool -> ExceptT String IO [Declaration]
- moduleCompletions :: Database -> [Module] -> String -> ExceptT String IO [String]
- checkModule :: (ModuleId -> Bool) -> ModuleDeclaration -> Bool
- checkDeclaration :: (Declaration -> Bool) -> ModuleDeclaration -> Bool
- restrictCabal :: Cabal -> ModuleId -> Bool
- visibleFrom :: Maybe Project -> Module -> ModuleId -> Bool
- splitIdentifier :: String -> (Maybe String, String)
- fileCtx :: Database -> FilePath -> ExceptT String IO (FilePath, Module, Maybe Project)
- fileCtxMaybe :: Database -> FilePath -> ExceptT String IO (FilePath, Maybe Module, Maybe Project)
- module HsDev.Database
- module HsDev.Symbols.Types
- module Control.Monad.Except
Commands
findDeclaration :: Database -> String -> ExceptT String IO [ModuleDeclaration] Source
Find declaration by name
lookupSymbol :: Database -> Cabal -> FilePath -> String -> ExceptT String IO [ModuleDeclaration] Source
Lookup visible within project symbol
whois :: Database -> Cabal -> FilePath -> String -> ExceptT String IO [Declaration] Source
Whois symbol in scope
scopeModules :: Database -> Cabal -> FilePath -> ExceptT String IO [Module] Source
Accessible modules
scope :: Database -> Cabal -> FilePath -> Bool -> ExceptT String IO [Declaration] Source
Symbols in scope
completions :: Database -> Cabal -> FilePath -> String -> Bool -> ExceptT String IO [Declaration] Source
Completions
moduleCompletions :: Database -> [Module] -> String -> ExceptT String IO [String] Source
Module completions
Filters
checkModule :: (ModuleId -> Bool) -> ModuleDeclaration -> Bool Source
Check module
checkDeclaration :: (Declaration -> Bool) -> ModuleDeclaration -> Bool Source
Check declaration
restrictCabal :: Cabal -> ModuleId -> Bool Source
Allow only selected cabal sandbox
visibleFrom :: Maybe Project -> Module -> ModuleId -> Bool Source
Check whether module is visible from source file
splitIdentifier :: String -> (Maybe String, String) Source
Split identifier into module name and identifier itself
Helpers
fileCtx :: Database -> FilePath -> ExceptT String IO (FilePath, Module, Maybe Project) Source
Get context file and project
fileCtxMaybe :: Database -> FilePath -> ExceptT String IO (FilePath, Maybe Module, Maybe Project) Source
Try get context file
Reexports
module HsDev.Database
module HsDev.Symbols.Types
module Control.Monad.Except