leksah-server-0.8.0.6: Metadata collection for leksahSource codeContentsIndex
IDE.Core.CTypes
Description
Synopsis
data PackageDescr = PackageDescr {
pdPackage :: PackageIdentifier
pdMbSourcePath :: Maybe FilePath
pdModules :: [ModuleDescr]
pdBuildDepends :: [PackageIdentifier]
}
data ModuleDescr = ModuleDescr {
mdModuleId :: PackModule
mdMbSourcePath :: Maybe FilePath
mdReferences :: Map ModuleName (Set String)
mdIdDescriptions :: [Descr]
}
data Descr
= Real RealDescr
| Reexported ReexportedDescr
data RealDescr = RealDescr {
dscName' :: String
dscMbTypeStr' :: Maybe ByteString
dscMbModu' :: Maybe PackModule
dscMbLocation' :: Maybe Location
dscMbComment' :: Maybe ByteString
dscTypeHint' :: TypeDescr
dscExported' :: Bool
}
data ReexportedDescr = ReexportedDescr {
dsrMbModu :: Maybe PackModule
dsrDescr :: Descr
}
newtype Present alpha = Present alpha
data TypeDescr
= VariableDescr
| FieldDescr Descr
| ConstructorDescr Descr
| DataDescr [SimpleDescr] [SimpleDescr]
| TypeDescr
| NewtypeDescr SimpleDescr (Maybe SimpleDescr)
| ClassDescr [String] [SimpleDescr]
| MethodDescr Descr
| InstanceDescr [String]
| KeywordDescr
| ExtensionDescr
| ModNameDescr
| QualModNameDescr
| ErrorDescr
data DescrType
= Variable
| Field
| Constructor
| Data
| Type
| Newtype
| Class
| Method
| Instance
| Keyword
| Extension
| ModName
| QualModName
| Error
data SimpleDescr = SimpleDescr {
sdName :: String
sdType :: Maybe ByteString
sdLocation :: Maybe Location
sdComment :: Maybe ByteString
sdExported :: Bool
}
data GenScope = forall alpha . SymbolTable alpha => GenScopeC (PackScope alpha)
dscName :: Descr -> String
dscMbTypeStr :: Descr -> Maybe ByteString
dscMbModu :: Descr -> Maybe PackModule
dsMbModu :: Descr -> Maybe PackModule
dscMbLocation :: Descr -> Maybe Location
dscMbComment :: Descr -> Maybe ByteString
dscTypeHint :: Descr -> TypeDescr
dscExported :: Descr -> Bool
descrType :: TypeDescr -> DescrType
isReexported :: Descr -> Bool
data PackScope alpha = SymbolTable alpha => PackScope (Map PackageIdentifier PackageDescr) alpha
class SymbolTable alpha where
symLookup :: String -> alpha -> [Descr]
symbols :: alpha -> Set String
symSplitLookup :: String -> alpha -> (alpha, Maybe [Descr], alpha)
symInsert :: String -> [Descr] -> alpha -> alpha
symEmpty :: alpha
symElems :: alpha -> [[Descr]]
symUnion :: alpha -> alpha -> alpha
data PackModule = PM {
pack :: PackageIdentifier
modu :: ModuleName
}
parsePackModule :: String -> PackModule
showPackModule :: PackModule -> String
packageIdentifierToString :: PackageIdentifier -> String
packageIdentifierFromString :: String -> Maybe PackageIdentifier
data Location = Location {
locationSLine :: Int
locationSCol :: Int
locationELine :: Int
locationECol :: Int
}
data SrcSpan = SrcSpan {
srcSpanFilename :: String
srcSpanStartLine :: Int
srcSpanStartColumn :: Int
srcSpanEndLine :: Int
srcSpanEndColumn :: Int
}
data Scope
= PackageScope Bool
| WorkspaceScope Bool
| SystemScope
data ServerCommand
= SystemCommand {
scRebuild :: Bool
scSources :: Bool
scExtract :: Bool
}
| WorkspaceCommand {
wcRebuild :: Bool
wcPackage :: PackageIdentifier
wcPath :: FilePath
wcModList :: [(String, FilePath)]
}
| ParseHeaderCommand {
hcFilePath :: FilePath
}
data ServerAnswer
= ServerOK
| ServerFailed String
| ServerHeader (Either [ImportDecl] Int)
leksahVersion :: String
configDirName :: String
metadataVersion :: Integer
data ImportDecl = ImportDecl {
importLoc :: Location
importModule :: String
importQualified :: Bool
importSrc :: Bool
importPkg :: Maybe String
importAs :: Maybe String
importSpecs :: Maybe ImportSpecList
}
data ImportSpecList = ImportSpecList Bool [ImportSpec]
data ImportSpec
= IVar String
| IAbs String
| IThingAll String
| IThingWith String [String]
getThisPackage :: PackageConfig -> PackageIdentifier
data RetrieveStrategy
= RetrieveThenBuild
| BuildThenRetrieve
| NeverRetrieve
Documentation
data PackageDescr Source
Constructors
PackageDescr
pdPackage :: PackageIdentifier
pdMbSourcePath :: Maybe FilePath
pdModules :: [ModuleDescr]
pdBuildDepends :: [PackageIdentifier]
show/hide Instances
data ModuleDescr Source
Constructors
ModuleDescr
mdModuleId :: PackModule
mdMbSourcePath :: Maybe FilePath
mdReferences :: Map ModuleName (Set String)
mdIdDescriptions :: [Descr]
show/hide Instances
data Descr Source
Constructors
Real RealDescr
Reexported ReexportedDescr
show/hide Instances
data RealDescr Source
Constructors
RealDescr
dscName' :: String
dscMbTypeStr' :: Maybe ByteString
dscMbModu' :: Maybe PackModule
dscMbLocation' :: Maybe Location
dscMbComment' :: Maybe ByteString
dscTypeHint' :: TypeDescr
dscExported' :: Bool
show/hide Instances
data ReexportedDescr Source
Constructors
ReexportedDescr
dsrMbModu :: Maybe PackModule
dsrDescr :: Descr
show/hide Instances
newtype Present alpha Source
Constructors
Present alpha
show/hide Instances
data TypeDescr Source
Constructors
VariableDescr
FieldDescr Descr
ConstructorDescr Descr
DataDescr [SimpleDescr] [SimpleDescr]first constructors, then fields
TypeDescr
NewtypeDescr SimpleDescr (Maybe SimpleDescr)first constructors, then maybe field
ClassDescr [String] [SimpleDescr]first super, then methods
MethodDescr DescrclassDescr
InstanceDescr [String]binds
KeywordDescr
ExtensionDescr
ModNameDescr
QualModNameDescr
ErrorDescr
show/hide Instances
data DescrType Source
Constructors
Variable
Field
Constructor
Data
Type
Newtype
Class
Method
Instance
Keyword
Extension
ModName
QualModName
Error
show/hide Instances
data SimpleDescr Source
Constructors
SimpleDescr
sdName :: String
sdType :: Maybe ByteString
sdLocation :: Maybe Location
sdComment :: Maybe ByteString
sdExported :: Bool
show/hide Instances
data GenScope Source
Constructors
forall alpha . SymbolTable alpha => GenScopeC (PackScope alpha)
dscName :: Descr -> StringSource
dscMbTypeStr :: Descr -> Maybe ByteStringSource
dscMbModu :: Descr -> Maybe PackModuleSource
The definition module
dsMbModu :: Descr -> Maybe PackModuleSource
The exporting module
dscMbLocation :: Descr -> Maybe LocationSource
dscMbComment :: Descr -> Maybe ByteStringSource
dscTypeHint :: Descr -> TypeDescrSource
dscExported :: Descr -> BoolSource
descrType :: TypeDescr -> DescrTypeSource
isReexported :: Descr -> BoolSource
data PackScope alpha Source
Constructors
SymbolTable alpha => PackScope (Map PackageIdentifier PackageDescr) alpha
class SymbolTable alpha whereSource
Methods
symLookup :: String -> alpha -> [Descr]Source
symbols :: alpha -> Set StringSource
symSplitLookup :: String -> alpha -> (alpha, Maybe [Descr], alpha)Source
symInsert :: String -> [Descr] -> alpha -> alphaSource
symEmpty :: alphaSource
symElems :: alpha -> [[Descr]]Source
symUnion :: alpha -> alpha -> alphaSource
show/hide Instances
data PackModule Source
Constructors
PM
pack :: PackageIdentifier
modu :: ModuleName
show/hide Instances
parsePackModule :: String -> PackModuleSource
showPackModule :: PackModule -> StringSource
packageIdentifierToString :: PackageIdentifier -> StringSource
packageIdentifierFromString :: String -> Maybe PackageIdentifierSource
data Location Source
Constructors
Location
locationSLine :: Int
locationSCol :: Int
locationELine :: Int
locationECol :: Int
show/hide Instances
data SrcSpan Source
A portion of the source, spanning one or more lines and zero or more columns.
Constructors
SrcSpan
srcSpanFilename :: String
srcSpanStartLine :: Int
srcSpanStartColumn :: Int
srcSpanEndLine :: Int
srcSpanEndColumn :: Int
show/hide Instances
data Scope Source
Constructors
PackageScope Bool
WorkspaceScope Bool
SystemScope
show/hide Instances
data ServerCommand Source
Constructors
SystemCommand
scRebuild :: Bool
scSources :: Bool
scExtract :: Bool
WorkspaceCommand
wcRebuild :: Bool
wcPackage :: PackageIdentifier
wcPath :: FilePath
wcModList :: [(String, FilePath)]
ParseHeaderCommand
hcFilePath :: FilePath
show/hide Instances
data ServerAnswer Source
Constructors
ServerOK
ServerFailed String
ServerHeader (Either [ImportDecl] Int)
show/hide Instances
leksahVersion :: StringSource
configDirName :: StringSource
metadataVersion :: IntegerSource
data ImportDecl Source
An import declaration.
Constructors
ImportDecl
importLoc :: Location
importModule :: Stringname of the module imported.
importQualified :: Boolimported qualified?
importSrc :: Boolimported with {-# SOURCE #-}?
importPkg :: Maybe Stringimported with explicit package name
importAs :: Maybe Stringoptional alias name in an as clause.
importSpecs :: Maybe ImportSpecListoptional list of import specifications.
show/hide Instances
data ImportSpecList Source
An explicit import specification list.
Constructors
ImportSpecList Bool [ImportSpec]
show/hide Instances
data ImportSpec Source
An import specification, representing a single explicit item imported (or hidden) from a module.
Constructors
IVar Stringvariable
IAbs StringT: the name of a class, datatype or type synonym.
IThingAll StringT(..): a class imported with all of its methods, or a datatype imported with all of its constructors.
IThingWith String [String]T(C_1,...,C_n): a class imported with some of its methods, or a datatype imported with some of its constructors.
show/hide Instances
getThisPackage :: PackageConfig -> PackageIdentifierSource
data RetrieveStrategy Source
Constructors
RetrieveThenBuild
BuildThenRetrieve
NeverRetrieve
show/hide Instances
Produced by Haddock version 2.6.1