purescript-0.11.7: PureScript Programming Language Compiler

Safe HaskellNone
LanguageHaskell2010

Language.PureScript.Ide.Types

Description

Type definitions for psc-ide

Synopsis

Documentation

data IdeDeclaration Source #

Instances

Eq IdeDeclaration Source # 
Ord IdeDeclaration Source # 
Show IdeDeclaration Source # 
Generic IdeDeclaration Source # 

Associated Types

type Rep IdeDeclaration :: * -> * #

NFData IdeDeclaration Source # 

Methods

rnf :: IdeDeclaration -> () #

type Rep IdeDeclaration Source # 

data IdeValue Source #

Constructors

IdeValue 

Instances

Eq IdeValue Source # 
Ord IdeValue Source # 
Show IdeValue Source # 
Generic IdeValue Source # 

Associated Types

type Rep IdeValue :: * -> * #

Methods

from :: IdeValue -> Rep IdeValue x #

to :: Rep IdeValue x -> IdeValue #

NFData IdeValue Source # 

Methods

rnf :: IdeValue -> () #

type Rep IdeValue Source # 
type Rep IdeValue = D1 (MetaData "IdeValue" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" False) (C1 (MetaCons "IdeValue" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ideValueIdent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident)) (S1 (MetaSel (Just Symbol "_ideValueType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))

data IdeTypeSynonym Source #

Instances

Eq IdeTypeSynonym Source # 
Ord IdeTypeSynonym Source # 
Show IdeTypeSynonym Source # 
Generic IdeTypeSynonym Source # 

Associated Types

type Rep IdeTypeSynonym :: * -> * #

NFData IdeTypeSynonym Source # 

Methods

rnf :: IdeTypeSynonym -> () #

type Rep IdeTypeSynonym Source # 
type Rep IdeTypeSynonym = D1 (MetaData "IdeTypeSynonym" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" False) (C1 (MetaCons "IdeTypeSynonym" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ideSynonymName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName TypeName))) ((:*:) (S1 (MetaSel (Just Symbol "_ideSynonymType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Just Symbol "_ideSynonymKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Kind)))))

data IdeDataConstructor Source #

Instances

Eq IdeDataConstructor Source # 
Ord IdeDataConstructor Source # 
Show IdeDataConstructor Source # 
Generic IdeDataConstructor Source # 
NFData IdeDataConstructor Source # 

Methods

rnf :: IdeDataConstructor -> () #

type Rep IdeDataConstructor Source # 
type Rep IdeDataConstructor = D1 (MetaData "IdeDataConstructor" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" False) (C1 (MetaCons "IdeDataConstructor" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ideDtorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName ConstructorName))) ((:*:) (S1 (MetaSel (Just Symbol "_ideDtorTypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName TypeName))) (S1 (MetaSel (Just Symbol "_ideDtorType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))

data IdeTypeClass Source #

data IdeInstance Source #

Instances

Eq IdeInstance Source # 
Ord IdeInstance Source # 
Show IdeInstance Source # 
Generic IdeInstance Source # 

Associated Types

type Rep IdeInstance :: * -> * #

NFData IdeInstance Source # 

Methods

rnf :: IdeInstance -> () #

type Rep IdeInstance Source # 
type Rep IdeInstance = D1 (MetaData "IdeInstance" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" False) (C1 (MetaCons "IdeInstance" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ideInstanceModule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModuleName)) (S1 (MetaSel (Just Symbol "_ideInstanceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident))) ((:*:) (S1 (MetaSel (Just Symbol "_ideInstanceTypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type])) (S1 (MetaSel (Just Symbol "_ideInstanceConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Constraint]))))))

data IdeValueOperator Source #

Instances

Eq IdeValueOperator Source # 
Ord IdeValueOperator Source # 
Show IdeValueOperator Source # 
Generic IdeValueOperator Source # 
NFData IdeValueOperator Source # 

Methods

rnf :: IdeValueOperator -> () #

type Rep IdeValueOperator Source # 

data IdeTypeOperator Source #

Instances

Eq IdeTypeOperator Source # 
Ord IdeTypeOperator Source # 
Show IdeTypeOperator Source # 
Generic IdeTypeOperator Source # 
NFData IdeTypeOperator Source # 

Methods

rnf :: IdeTypeOperator -> () #

type Rep IdeTypeOperator Source # 
type Rep IdeTypeOperator = D1 (MetaData "IdeTypeOperator" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" False) (C1 (MetaCons "IdeTypeOperator" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ideTypeOpName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (OpName TypeOpName))) (S1 (MetaSel (Just Symbol "_ideTypeOpAlias") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Qualified (ProperName TypeName))))) ((:*:) (S1 (MetaSel (Just Symbol "_ideTypeOpPrecedence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Precedence)) ((:*:) (S1 (MetaSel (Just Symbol "_ideTypeOpAssociativity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Associativity)) (S1 (MetaSel (Just Symbol "_ideTypeOpKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kind)))))))

data IdeDeclarationAnn Source #

Instances

Eq IdeDeclarationAnn Source # 
Ord IdeDeclarationAnn Source # 
Show IdeDeclarationAnn Source # 
Generic IdeDeclarationAnn Source # 
NFData IdeDeclarationAnn Source # 

Methods

rnf :: IdeDeclarationAnn -> () #

FromJSON (Matcher IdeDeclarationAnn) # 
type Rep IdeDeclarationAnn Source # 
type Rep IdeDeclarationAnn = D1 (MetaData "IdeDeclarationAnn" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" False) (C1 (MetaCons "IdeDeclarationAnn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_idaAnnotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Annotation)) (S1 (MetaSel (Just Symbol "_idaDeclaration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeDeclaration))))

data Annotation Source #

Instances

Eq Annotation Source # 
Ord Annotation Source # 
Show Annotation Source # 
Generic Annotation Source # 

Associated Types

type Rep Annotation :: * -> * #

NFData Annotation Source # 

Methods

rnf :: Annotation -> () #

type Rep Annotation Source # 
type Rep Annotation = D1 (MetaData "Annotation" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" False) (C1 (MetaCons "Annotation" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_annLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SourceSpan))) (S1 (MetaSel (Just Symbol "_annExportedFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ModuleName)))) ((:*:) (S1 (MetaSel (Just Symbol "_annTypeAnnotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Type))) (S1 (MetaSel (Just Symbol "_annDocumentation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))))

newtype AstData 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

Instances

Functor AstData Source # 

Methods

fmap :: (a -> b) -> AstData a -> AstData b #

(<$) :: a -> AstData b -> AstData a #

Foldable AstData Source # 

Methods

fold :: Monoid m => AstData m -> m #

foldMap :: Monoid m => (a -> m) -> AstData a -> m #

foldr :: (a -> b -> b) -> b -> AstData a -> b #

foldr' :: (a -> b -> b) -> b -> AstData a -> b #

foldl :: (b -> a -> b) -> b -> AstData a -> b #

foldl' :: (b -> a -> b) -> b -> AstData a -> b #

foldr1 :: (a -> a -> a) -> AstData a -> a #

foldl1 :: (a -> a -> a) -> AstData a -> a #

toList :: AstData a -> [a] #

null :: AstData a -> Bool #

length :: AstData a -> Int #

elem :: Eq a => a -> AstData a -> Bool #

maximum :: Ord a => AstData a -> a #

minimum :: Ord a => AstData a -> a #

sum :: Num a => AstData a -> a #

product :: Num a => AstData a -> a #

Eq a => Eq (AstData a) Source # 

Methods

(==) :: AstData a -> AstData a -> Bool #

(/=) :: AstData a -> AstData a -> Bool #

Ord a => Ord (AstData a) Source # 

Methods

compare :: AstData a -> AstData a -> Ordering #

(<) :: AstData a -> AstData a -> Bool #

(<=) :: AstData a -> AstData a -> Bool #

(>) :: AstData a -> AstData a -> Bool #

(>=) :: AstData a -> AstData a -> Bool #

max :: AstData a -> AstData a -> AstData a #

min :: AstData a -> AstData a -> AstData a #

Show a => Show (AstData a) Source # 

Methods

showsPrec :: Int -> AstData a -> ShowS #

show :: AstData a -> String #

showList :: [AstData a] -> ShowS #

Generic (AstData a) Source # 

Associated Types

type Rep (AstData a) :: * -> * #

Methods

from :: AstData a -> Rep (AstData a) x #

to :: Rep (AstData a) x -> AstData a #

NFData a => NFData (AstData a) Source # 

Methods

rnf :: AstData a -> () #

type Rep (AstData a) Source # 
type Rep (AstData a) = D1 (MetaData "AstData" "Language.PureScript.Ide.Types" "purescript-0.11.7-LYkkdaNPe76o3Ss2KvZX" True) (C1 (MetaCons "AstData" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ModuleMap (DefinitionSites a, TypeAnnotations)))))

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.

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

newtype Match a Source #

Constructors

Match (ModuleName, a) 

Instances

Functor Match Source # 

Methods

fmap :: (a -> b) -> Match a -> Match b #

(<$) :: a -> Match b -> Match a #

Eq a => Eq (Match a) Source # 

Methods

(==) :: Match a -> Match a -> Bool #

(/=) :: Match a -> Match a -> Bool #

Show a => Show (Match a) Source # 

Methods

showsPrec :: Int -> Match a -> ShowS #

show :: Match a -> String #

showList :: [Match a] -> ShowS #

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.