Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.PureScript.Ide.Types
Description
Type definitions for psc-ide
- type ModuleIdent = Text
- type ModuleMap a = Map ModuleName a
- data IdeDeclaration
- data IdeValue = IdeValue {}
- data IdeType = IdeType {}
- data IdeTypeSynonym = IdeTypeSynonym {}
- data IdeDataConstructor = IdeDataConstructor {}
- data IdeTypeClass = IdeTypeClass {}
- data IdeInstance = IdeInstance {}
- data IdeValueOperator = IdeValueOperator {}
- data IdeTypeOperator = IdeTypeOperator {}
- _IdeDeclKind :: Prism' IdeDeclaration (ProperName KindName)
- _IdeDeclTypeOperator :: Prism' IdeDeclaration IdeTypeOperator
- _IdeDeclValueOperator :: Prism' IdeDeclaration IdeValueOperator
- _IdeDeclTypeClass :: Prism' IdeDeclaration IdeTypeClass
- _IdeDeclDataConstructor :: Prism' IdeDeclaration IdeDataConstructor
- _IdeDeclTypeSynonym :: Prism' IdeDeclaration IdeTypeSynonym
- _IdeDeclType :: Prism' IdeDeclaration IdeType
- _IdeDeclValue :: Prism' IdeDeclaration IdeValue
- ideValueType :: Lens' IdeValue Type
- ideValueIdent :: Lens' IdeValue Ident
- ideTypeName :: Lens' IdeType (ProperName TypeName)
- ideTypeKind :: Lens' IdeType Kind
- ideTypeDtors :: Lens' IdeType [(ProperName ConstructorName, Type)]
- ideSynonymType :: Lens' IdeTypeSynonym Type
- ideSynonymName :: Lens' IdeTypeSynonym (ProperName TypeName)
- ideSynonymKind :: Lens' IdeTypeSynonym Kind
- ideDtorTypeName :: Lens' IdeDataConstructor (ProperName TypeName)
- ideDtorType :: Lens' IdeDataConstructor Type
- ideDtorName :: Lens' IdeDataConstructor (ProperName ConstructorName)
- ideTCName :: Lens' IdeTypeClass (ProperName ClassName)
- ideTCKind :: Lens' IdeTypeClass Kind
- ideTCInstances :: Lens' IdeTypeClass [IdeInstance]
- ideInstanceTypes :: Lens' IdeInstance [Type]
- ideInstanceName :: Lens' IdeInstance Ident
- ideInstanceModule :: Lens' IdeInstance ModuleName
- ideInstanceConstraints :: Lens' IdeInstance (Maybe [Constraint])
- ideValueOpType :: Lens' IdeValueOperator (Maybe Type)
- ideValueOpPrecedence :: Lens' IdeValueOperator Precedence
- ideValueOpName :: Lens' IdeValueOperator (OpName ValueOpName)
- ideValueOpAssociativity :: Lens' IdeValueOperator Associativity
- ideValueOpAlias :: Lens' IdeValueOperator (Qualified (Either Ident (ProperName ConstructorName)))
- ideTypeOpPrecedence :: Lens' IdeTypeOperator Precedence
- ideTypeOpName :: Lens' IdeTypeOperator (OpName TypeOpName)
- ideTypeOpKind :: Lens' IdeTypeOperator (Maybe Kind)
- ideTypeOpAssociativity :: Lens' IdeTypeOperator Associativity
- ideTypeOpAlias :: Lens' IdeTypeOperator (Qualified (ProperName TypeName))
- data IdeDeclarationAnn = IdeDeclarationAnn {}
- data Annotation = Annotation {}
- annTypeAnnotation :: Lens' Annotation (Maybe Type)
- annLocation :: Lens' Annotation (Maybe SourceSpan)
- annExportedFrom :: Lens' Annotation (Maybe ModuleName)
- annDocumentation :: Lens' Annotation (Maybe Text)
- idaDeclaration :: Lens' IdeDeclarationAnn IdeDeclaration
- idaAnnotation :: Lens' IdeDeclarationAnn Annotation
- emptyAnn :: Annotation
- type DefinitionSites a = Map IdeNamespaced a
- type TypeAnnotations = Map Ident Type
- newtype AstData a = AstData (ModuleMap (DefinitionSites a, TypeAnnotations))
- data IdeLogLevel
- = LogDebug
- | LogPerf
- | LogAll
- | LogDefault
- | LogNone
- data IdeConfiguration = IdeConfiguration {}
- data IdeEnvironment = IdeEnvironment {}
- type Ide m = (MonadIO m, MonadReader IdeEnvironment m)
- data IdeState = IdeState {}
- emptyIdeState :: IdeState
- emptyFileState :: IdeFileState
- emptyVolatileState :: IdeVolatileState
- data IdeFileState = IdeFileState {}
- data IdeVolatileState = IdeVolatileState {}
- newtype Match a = Match (ModuleName, a)
- data Completion = Completion {}
- identifierFromDeclarationRef :: DeclarationRef -> Text
- data Success
- encodeSuccess :: ToJSON a => a -> Value
- encodeImport :: (ModuleName, ImportDeclarationType, Maybe ModuleName) -> Value
- newtype PursuitQuery = PursuitQuery Text
- data PursuitSearchType
- data PursuitResponse
- data IdeNamespace
- data IdeNamespaced = IdeNamespaced IdeNamespace Text
Documentation
type ModuleIdent = Text Source #
type ModuleMap a = Map ModuleName a Source #
data IdeDeclaration Source #
Constructors
Instances
Constructors
IdeValue | |
Fields
|
Constructors
IdeType | |
Fields
|
data IdeDataConstructor Source #
Constructors
IdeDataConstructor | |
Fields |
data IdeValueOperator Source #
Constructors
IdeValueOperator | |
data IdeTypeOperator Source #
Constructors
IdeTypeOperator | |
ideTypeDtors :: Lens' IdeType [(ProperName ConstructorName, Type)] Source #
ideValueOpAlias :: Lens' IdeValueOperator (Qualified (Either Ident (ProperName ConstructorName))) Source #
data IdeDeclarationAnn Source #
Constructors
IdeDeclarationAnn | |
Fields |
type DefinitionSites a = Map IdeNamespaced a Source #
Constructors
AstData (ModuleMap (DefinitionSites a, TypeAnnotations)) | SourceSpans for the definition sites of values and types as well as type annotations found in a module |
data IdeConfiguration Source #
Constructors
IdeConfiguration | |
Fields
|
data IdeEnvironment Source #
Constructors
IdeEnvironment | |
Fields |
type Ide m = (MonadIO m, MonadReader IdeEnvironment m) Source #
Constructors
IdeState | |
Fields |
data IdeFileState Source #
IdeFileState
holds data that corresponds 1-to-1 to an entity on the
filesystem. Externs correspond to the ExternsFiles the compiler emits into
the output folder, and modules are parsed ASTs from source files. This means,
that we can update single modules or ExternsFiles inside this state whenever
the corresponding entity changes on the file system.
Constructors
IdeFileState | |
Instances
data IdeVolatileState Source #
IdeVolatileState
is derived from the IdeFileState
and needs to be
invalidated and refreshed carefully. It holds AstData
, which is the data we
extract from the parsed ASTs, as well as the IdeDeclarations, which contain
lots of denormalized data, so they need to fully rebuilt whenever
IdeFileState
changes. The vsCachedRebuild field can hold a rebuild result
with open imports which is used to provide completions for module private
declarations
Constructors
IdeVolatileState | |
Fields |
Instances
Constructors
Match (ModuleName, a) |
data Completion Source #
A completion as it gets sent to the editors
Constructors
Completion | |
Fields
|
Instances
encodeSuccess :: ToJSON a => a -> Value Source #
data PursuitSearchType Source #
Constructors
Package | |
Identifier |
data PursuitResponse Source #
Constructors
ModuleResponse ModuleIdent Text | A Pursuit Response for a module. Consists of the modules name and the package it belongs to |
DeclarationResponse Text ModuleIdent Text (Maybe Text) Text | A Pursuit Response for a declaration. Consist of the declaration's module, name, package, type summary text |
data IdeNamespace Source #
Denotes the different namespaces a name in PureScript can reside in.
Constructors
IdeNSValue | |
IdeNSType | |
IdeNSKind |
Instances
data IdeNamespaced Source #
A name tagged with a namespace
Constructors
IdeNamespaced IdeNamespace Text |
Instances