Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Export
- = ExportName (Maybe Text) Text
- | ExportModule Text
- export :: Export -> Text
- data ImportList = ImportList {
- hidingList :: Bool
- importSpec :: [Text]
- passImportList :: ImportList -> Text -> Bool
- data Import = Import {}
- importName :: Import -> Text
- import_ :: Text -> Import
- class Symbol a where
- symbolName :: a -> Text
- symbolQualifiedName :: a -> Text
- symbolDocs :: a -> Maybe Text
- symbolLocation :: a -> Location
- data ModuleId = ModuleId {}
- unnamedModuleId :: ModuleLocation -> ModuleId
- data Module = Module {}
- sortDeclarations :: [Declaration] -> [Declaration]
- moduleLocals :: Module -> Module
- setDefinedIn :: Module -> Module
- dropExternals :: Module -> Module
- clearDefinedIn :: Module -> Module
- moduleLocalDeclarations :: Module -> [Declaration]
- moduleModuleDeclarations :: Module -> [ModuleDeclaration]
- moduleId :: Module -> ModuleId
- class Locals a where
- locals :: a -> [Declaration]
- where_ :: a -> [Declaration] -> a
- data Declaration = Declaration {}
- decl :: Text -> DeclarationInfo -> Declaration
- definedIn :: Declaration -> ModuleId -> Declaration
- declarationLocals :: Declaration -> [Declaration]
- scopes :: Declaration -> [Maybe Text]
- data TypeInfo = TypeInfo {}
- data DeclarationInfo
- data ModuleDeclaration = ModuleDeclaration {}
- data ExportedDeclaration = ExportedDeclaration {}
- mergeExported :: [ModuleDeclaration] -> [ExportedDeclaration]
- data Inspection
- inspectionOpts :: Inspection -> [String]
- data Inspected i a = Inspected {
- inspection :: Inspection
- inspectedId :: i
- inspectionResult :: Either String a
- type InspectedModule = Inspected ModuleLocation Module
- showTypeInfo :: TypeInfo -> String -> String -> String
- declarationInfo :: DeclarationInfo -> Either (Maybe Text, [Declaration]) TypeInfo
- declarationTypeInfo :: DeclarationInfo -> Maybe TypeInfo
- declarationTypeCtor :: String -> TypeInfo -> DeclarationInfo
- declarationTypeName :: DeclarationInfo -> Maybe String
- qualifiedName :: ModuleId -> Declaration -> Text
- importQualifier :: Maybe Text -> Import -> Bool
- class Canonicalize a where
- canonicalize :: a -> IO a
- locateProject :: FilePath -> IO (Maybe Project)
- searchProject :: FilePath -> IO (Maybe Project)
- locateSourceDir :: FilePath -> IO (Maybe FilePath)
- sourceModuleRoot :: Text -> FilePath -> FilePath
- importedModulePath :: Text -> FilePath -> Text -> FilePath
- addDeclaration :: Declaration -> Module -> Module
- unalias :: Module -> Text -> [Text]
- moduleContents :: Module -> [String]
- module HsDev.Symbols.Class
- module HsDev.Symbols.Documented
Information
Module export
passImportList :: ImportList -> Text -> Bool Source
Check whether name pass import list
Module import
importName :: Import -> Text Source
Get import module name
symbolName :: a -> Text Source
symbolQualifiedName :: a -> Text Source
symbolDocs :: a -> Maybe Text Source
symbolLocation :: a -> Location Source
Module id
Module
Module | |
|
sortDeclarations :: [Declaration] -> [Declaration] Source
moduleLocals :: Module -> Module Source
Bring locals to top
setDefinedIn :: Module -> Module Source
Set all declaration definedIn
to this module
dropExternals :: Module -> Module Source
Drop all declarations, that not defined in this module
clearDefinedIn :: Module -> Module Source
Clear definedIn
information
moduleLocalDeclarations :: Module -> [Declaration] Source
Get declarations with locals
moduleModuleDeclarations :: Module -> [ModuleDeclaration] Source
Get list of declarations as ModuleDeclaration
locals :: a -> [Declaration] Source
where_ :: a -> [Declaration] -> a Source
data Declaration Source
Declaration
Declaration | |
|
decl :: Text -> DeclarationInfo -> Declaration Source
definedIn :: Declaration -> ModuleId -> Declaration Source
scopes :: Declaration -> [Maybe Text] Source
Get scopes of Declaration
, where Nothing
is global scope
Common info for type, newtype, data and class
TypeInfo | |
|
data ModuleDeclaration Source
Symbol in context of some module
data ExportedDeclaration Source
Symbol exported with
mergeExported :: [ModuleDeclaration] -> [ExportedDeclaration] Source
Merge ModuleDeclaration
into ExportedDeclaration
data Inspection Source
Inspection data
InspectionNone | No inspection |
InspectionAt POSIXTime [String] | Time and flags of inspection |
inspectionOpts :: Inspection -> [String] Source
Get inspection opts
Inspected entity
Inspected | |
|
type InspectedModule = Inspected ModuleLocation Module Source
Inspected module
Functions
declarationInfo :: DeclarationInfo -> Either (Maybe Text, [Declaration]) TypeInfo Source
Get function type of type info
declarationTypeInfo :: DeclarationInfo -> Maybe TypeInfo Source
Get type info of declaration
qualifiedName :: ModuleId -> Declaration -> Text Source
Returns qualified name of symbol
Utility
class Canonicalize a where Source
Canonicalize all paths within something
canonicalize :: a -> IO a Source
sourceModuleRoot :: Text -> FilePath -> FilePath Source
Get source module root directory, i.e. for "...srcFooBar.hs" with module Bar
will return "...src"
Modifiers
addDeclaration :: Declaration -> Module -> Module Source
Add declaration to module
Other
moduleContents :: Module -> [String] Source
Module contents
Reexports
module HsDev.Symbols.Class
module HsDev.Symbols.Documented