Safe Haskell | None |
---|---|
Language | Haskell98 |
- data ExportPart
- = ExportNothing
- | ExportAll
- | ExportWith [Text]
- data Export
- = ExportName { }
- | ExportModule { }
- data ImportList = ImportList {
- _hidingList :: Bool
- _importSpec :: [Text]
- data Import = Import {}
- data ModuleId = ModuleId {}
- data Module = Module {}
- moduleContents :: Module -> [String]
- moduleId :: Simple Lens Module ModuleId
- data Declaration = Declaration {}
- minimalDecl :: Lens' Declaration Declaration
- data TypeInfo = TypeInfo {}
- showTypeInfo :: TypeInfo -> String -> String -> String
- data DeclarationInfo
- declarationInfo :: DeclarationInfo -> Either (Maybe Text, [Declaration], Maybe Text) TypeInfo
- declarationTypeCtor :: String -> TypeInfo -> DeclarationInfo
- declarationTypeName :: DeclarationInfo -> Maybe String
- data ModuleDeclaration = ModuleDeclaration {}
- data ExportedDeclaration = ExportedDeclaration {}
- data Inspection
- = InspectionNone
- | InspectionAt { }
- data Inspected i a = Inspected {
- _inspection :: Inspection
- _inspectedId :: i
- _inspectionResult :: Either String a
- type InspectedModule = Inspected ModuleLocation Module
- exportQualified :: Traversal' Export (Maybe Text)
- exportName :: Traversal' Export Text
- exportPart :: Traversal' Export ExportPart
- exportModule :: Traversal' Export Text
- hidingList :: Lens' ImportList Bool
- importSpec :: Lens' ImportList [Text]
- importModuleName :: Lens' Import Text
- importIsQualified :: Lens' Import Bool
- importAs :: Lens' Import (Maybe Text)
- importList :: Lens' Import (Maybe ImportList)
- importPosition :: Lens' Import (Maybe Position)
- moduleIdName :: Lens' ModuleId Text
- moduleIdLocation :: Lens' ModuleId ModuleLocation
- moduleName :: Lens' Module Text
- moduleDocs :: Lens' Module (Maybe Text)
- moduleLocation :: Lens' Module ModuleLocation
- moduleExports :: Lens' Module (Maybe [Export])
- moduleImports :: Lens' Module [Import]
- moduleDeclarations :: Lens' Module [Declaration]
- declarationName :: Lens' Declaration Text
- declarationDefined :: Lens' Declaration (Maybe ModuleId)
- declarationImported :: Lens' Declaration (Maybe [Import])
- declarationDocs :: Lens' Declaration (Maybe Text)
- declarationPosition :: Lens' Declaration (Maybe Position)
- declaration :: Lens' Declaration DeclarationInfo
- typeInfoContext :: Lens' TypeInfo (Maybe Text)
- typeInfoArgs :: Lens' TypeInfo [Text]
- typeInfoDefinition :: Lens' TypeInfo (Maybe Text)
- typeInfoFunctions :: Lens' TypeInfo [Text]
- functionType :: Traversal' DeclarationInfo (Maybe Text)
- localDeclarations :: Traversal' DeclarationInfo [Declaration]
- related :: Traversal' DeclarationInfo (Maybe Text)
- typeInfo :: Traversal' DeclarationInfo TypeInfo
- declarationModuleId :: Lens' ModuleDeclaration ModuleId
- moduleDeclaration :: Lens' ModuleDeclaration Declaration
- exportedBy :: Lens' ExportedDeclaration [ModuleId]
- exportedDeclaration :: Lens' ExportedDeclaration Declaration
- inspectionAt :: Traversal' Inspection POSIXTime
- inspectionOpts :: Traversal' Inspection [String]
- inspection :: forall i a. Lens' (Inspected i a) Inspection
- inspectedId :: forall i a i. Lens (Inspected i a) (Inspected i a) i i
- inspectionResult :: forall i a a. Lens (Inspected i a) (Inspected i a) (Either String a) (Either String a)
- module HsDev.Cabal
- module HsDev.Project
- module HsDev.Symbols.Class
- module HsDev.Symbols.Documented
Documentation
data ExportPart Source
What to export for data/class etc
Module export
Module import
Module id
Module
Module | |
|
moduleContents :: Module -> [String] Source
Module contents
data Declaration Source
Declaration
Declaration | |
|
minimalDecl :: Lens' Declaration Declaration Source
Minimal declaration info without defined, docs and position
Common info for type, newtype, data and class
TypeInfo | |
|
data DeclarationInfo Source
Declaration info
declarationInfo :: DeclarationInfo -> Either (Maybe Text, [Declaration], Maybe Text) TypeInfo Source
Get function type of type info
data ModuleDeclaration Source
Symbol in context of some module
data ExportedDeclaration Source
Symbol exported with
data Inspection Source
Inspection data
InspectionNone | No inspection |
InspectionAt | Time and flags of inspection |
|
Inspected entity
Inspected | |
|
Show InspectedModule Source | |
ToJSON InspectedModule Source | |
FromJSON InspectedModule Source | |
Functor (Inspected i) Source | |
Foldable (Inspected i) Source | |
Traversable (Inspected i) Source | |
(Eq i, Eq a) => Eq (Inspected i a) Source | |
(Ord i, Ord a) => Ord (Inspected i a) Source | |
(NFData i, NFData a) => NFData (Inspected i a) Source |
type InspectedModule = Inspected ModuleLocation Module Source
Inspected module
importSpec :: Lens' ImportList [Text] Source
moduleImports :: Lens' Module [Import] Source
typeInfoArgs :: Lens' TypeInfo [Text] Source
inspection :: forall i a. Lens' (Inspected i a) Inspection Source
inspectedId :: forall i a i. Lens (Inspected i a) (Inspected i a) i i Source
inspectionResult :: forall i a a. Lens (Inspected i a) (Inspected i a) (Either String a) (Either String a) Source
module HsDev.Cabal
module HsDev.Project
module HsDev.Symbols.Class
module HsDev.Symbols.Documented