purescript-0.12.4: 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 # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeDeclaration Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeDeclaration Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeDeclaration Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeDeclaration :: Type -> Type #

NFData IdeDeclaration Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeDeclaration -> () #

type Rep IdeDeclaration Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeDeclaration = D1 (MetaData "IdeDeclaration" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (((C1 (MetaCons "IdeDeclValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeValue)) :+: C1 (MetaCons "IdeDeclType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeType))) :+: (C1 (MetaCons "IdeDeclTypeSynonym" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeTypeSynonym)) :+: C1 (MetaCons "IdeDeclDataConstructor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeDataConstructor)))) :+: ((C1 (MetaCons "IdeDeclTypeClass" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeTypeClass)) :+: C1 (MetaCons "IdeDeclValueOperator" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeValueOperator))) :+: (C1 (MetaCons "IdeDeclTypeOperator" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeTypeOperator)) :+: (C1 (MetaCons "IdeDeclModule" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModuleName)) :+: C1 (MetaCons "IdeDeclKind" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName KindName)))))))

data IdeValue Source #

Instances
Eq IdeValue Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeValue Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeValue Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeValue Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeValue :: Type -> Type #

Methods

from :: IdeValue -> Rep IdeValue x #

to :: Rep IdeValue x -> IdeValue #

NFData IdeValue Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeValue -> () #

type Rep IdeValue Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeValue = D1 (MetaData "IdeValue" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeValue" PrefixI True) (S1 (MetaSel (Just "_ideValueIdent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident) :*: S1 (MetaSel (Just "_ideValueType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceType)))

data IdeType Source #

Instances
Eq IdeType Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

(==) :: IdeType -> IdeType -> Bool #

(/=) :: IdeType -> IdeType -> Bool #

Ord IdeType Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeType Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeType Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeType :: Type -> Type #

Methods

from :: IdeType -> Rep IdeType x #

to :: Rep IdeType x -> IdeType #

NFData IdeType Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeType -> () #

type Rep IdeType Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeType = D1 (MetaData "IdeType" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeType" PrefixI True) (S1 (MetaSel (Just "_ideTypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName TypeName)) :*: (S1 (MetaSel (Just "_ideTypeKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceKind) :*: S1 (MetaSel (Just "_ideTypeDtors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ProperName ConstructorName, SourceType)]))))

data IdeTypeSynonym Source #

Instances
Eq IdeTypeSynonym Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeTypeSynonym Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeTypeSynonym Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeTypeSynonym Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeTypeSynonym :: Type -> Type #

NFData IdeTypeSynonym Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeTypeSynonym -> () #

type Rep IdeTypeSynonym Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeTypeSynonym = D1 (MetaData "IdeTypeSynonym" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeTypeSynonym" PrefixI True) (S1 (MetaSel (Just "_ideSynonymName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName TypeName)) :*: (S1 (MetaSel (Just "_ideSynonymType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceType) :*: S1 (MetaSel (Just "_ideSynonymKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceKind))))

data IdeDataConstructor Source #

Instances
Eq IdeDataConstructor Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeDataConstructor Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeDataConstructor Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeDataConstructor Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeDataConstructor :: Type -> Type #

NFData IdeDataConstructor Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeDataConstructor -> () #

type Rep IdeDataConstructor Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeDataConstructor = D1 (MetaData "IdeDataConstructor" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeDataConstructor" PrefixI True) (S1 (MetaSel (Just "_ideDtorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName ConstructorName)) :*: (S1 (MetaSel (Just "_ideDtorTypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName TypeName)) :*: S1 (MetaSel (Just "_ideDtorType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceType))))

data IdeTypeClass Source #

Instances
Eq IdeTypeClass Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeTypeClass Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeTypeClass Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeTypeClass Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeTypeClass :: Type -> Type #

NFData IdeTypeClass Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeTypeClass -> () #

type Rep IdeTypeClass Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeTypeClass = D1 (MetaData "IdeTypeClass" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeTypeClass" PrefixI True) (S1 (MetaSel (Just "_ideTCName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ProperName ClassName)) :*: (S1 (MetaSel (Just "_ideTCKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SourceKind) :*: S1 (MetaSel (Just "_ideTCInstances") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [IdeInstance]))))

data IdeInstance Source #

Instances
Eq IdeInstance Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeInstance Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeInstance Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeInstance Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeInstance :: Type -> Type #

NFData IdeInstance Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeInstance -> () #

type Rep IdeInstance Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeInstance = D1 (MetaData "IdeInstance" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeInstance" PrefixI True) ((S1 (MetaSel (Just "_ideInstanceModule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModuleName) :*: S1 (MetaSel (Just "_ideInstanceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident)) :*: (S1 (MetaSel (Just "_ideInstanceTypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SourceType]) :*: S1 (MetaSel (Just "_ideInstanceConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [SourceConstraint])))))

data IdeValueOperator Source #

Instances
Eq IdeValueOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeValueOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeValueOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeValueOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeValueOperator :: Type -> Type #

NFData IdeValueOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeValueOperator -> () #

type Rep IdeValueOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeValueOperator = D1 (MetaData "IdeValueOperator" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeValueOperator" PrefixI True) ((S1 (MetaSel (Just "_ideValueOpName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (OpName ValueOpName)) :*: S1 (MetaSel (Just "_ideValueOpAlias") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Qualified (Either Ident (ProperName ConstructorName))))) :*: (S1 (MetaSel (Just "_ideValueOpPrecedence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Precedence) :*: (S1 (MetaSel (Just "_ideValueOpAssociativity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Associativity) :*: S1 (MetaSel (Just "_ideValueOpType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SourceType))))))

data IdeTypeOperator Source #

Instances
Eq IdeTypeOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeTypeOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeTypeOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeTypeOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeTypeOperator :: Type -> Type #

NFData IdeTypeOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeTypeOperator -> () #

type Rep IdeTypeOperator Source # 
Instance details

Defined in Language.PureScript.Ide.Types

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

anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool Source #

data IdeDeclarationAnn Source #

Instances
Eq IdeDeclarationAnn Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeDeclarationAnn Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeDeclarationAnn Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeDeclarationAnn Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeDeclarationAnn :: Type -> Type #

NFData IdeDeclarationAnn Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeDeclarationAnn -> () #

FromJSON (Matcher IdeDeclarationAnn) Source # 
Instance details

Defined in Language.PureScript.Ide.Matcher

type Rep IdeDeclarationAnn Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeDeclarationAnn = D1 (MetaData "IdeDeclarationAnn" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeDeclarationAnn" PrefixI True) (S1 (MetaSel (Just "_idaAnnotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Annotation) :*: S1 (MetaSel (Just "_idaDeclaration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeDeclaration)))

data Annotation Source #

Instances
Eq Annotation Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord Annotation Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show Annotation Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic Annotation Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep Annotation :: Type -> Type #

NFData Annotation Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: Annotation -> () #

type Rep Annotation Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep Annotation = D1 (MetaData "Annotation" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "Annotation" PrefixI True) ((S1 (MetaSel (Just "_annLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SourceSpan)) :*: S1 (MetaSel (Just "_annExportedFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ModuleName))) :*: (S1 (MetaSel (Just "_annTypeAnnotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SourceType)) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

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

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

Foldable AstData Source # 
Instance details

Defined in Language.PureScript.Ide.Types

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 # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

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

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

Ord a => Ord (AstData a) Source # 
Instance details

Defined in Language.PureScript.Ide.Types

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 # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

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

show :: AstData a -> String #

showList :: [AstData a] -> ShowS #

Generic (AstData a) Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

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

Methods

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

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

NFData a => NFData (AstData a) Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: AstData a -> () #

type Rep (AstData a) Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep (AstData a) = D1 (MetaData "AstData" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" True) (C1 (MetaCons "AstData" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

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

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

Eq a => Eq (Match a) Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

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

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

Show a => Show (Match a) Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

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

show :: Match a -> String #

showList :: [Match a] -> ShowS #

data IdeNamespace Source #

Denotes the different namespaces a name in PureScript can reside in.

Instances
Eq IdeNamespace Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeNamespace Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeNamespace Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeNamespace Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeNamespace :: Type -> Type #

NFData IdeNamespace Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeNamespace -> () #

FromJSON IdeNamespace Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeNamespace Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeNamespace = D1 (MetaData "IdeNamespace" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) ((C1 (MetaCons "IdeNSValue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IdeNSType" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "IdeNSKind" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IdeNSModule" PrefixI False) (U1 :: Type -> Type)))

data IdeNamespaced Source #

A name tagged with a namespace

Instances
Eq IdeNamespaced Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Ord IdeNamespaced Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Show IdeNamespaced Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Generic IdeNamespaced Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Associated Types

type Rep IdeNamespaced :: Type -> Type #

NFData IdeNamespaced Source # 
Instance details

Defined in Language.PureScript.Ide.Types

Methods

rnf :: IdeNamespaced -> () #

type Rep IdeNamespaced Source # 
Instance details

Defined in Language.PureScript.Ide.Types

type Rep IdeNamespaced = D1 (MetaData "IdeNamespaced" "Language.PureScript.Ide.Types" "purescript-0.12.4-4431FMqBZsLBJwEgpbTTth" False) (C1 (MetaCons "IdeNamespaced" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IdeNamespace) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))