purescript-0.15.6: PureScript Programming Language Compiler
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.PureScript.Externs

Description

This module generates code for "externs" files, i.e. files containing only foreign import declarations.

Synopsis

Documentation

data ExternsFile Source #

The data which will be serialized to an externs file

Constructors

ExternsFile 

Fields

Instances

Instances details
Generic ExternsFile Source # 
Instance details

Defined in Language.PureScript.Externs

Associated Types

type Rep ExternsFile :: Type -> Type #

Show ExternsFile Source # 
Instance details

Defined in Language.PureScript.Externs

Serialise ExternsFile Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsFile Source # 
Instance details

Defined in Language.PureScript.Externs

data ExternsImport Source #

A module import in an externs file

Constructors

ExternsImport 

Fields

Instances

Instances details
Generic ExternsImport Source # 
Instance details

Defined in Language.PureScript.Externs

Associated Types

type Rep ExternsImport :: Type -> Type #

Show ExternsImport Source # 
Instance details

Defined in Language.PureScript.Externs

Serialise ExternsImport Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsImport Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsImport = D1 ('MetaData "ExternsImport" "Language.PureScript.Externs" "purescript-0.15.6-1py82rzyCAT3bEGm9U9Gns" 'False) (C1 ('MetaCons "ExternsImport" 'PrefixI 'True) (S1 ('MetaSel ('Just "eiModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName) :*: (S1 ('MetaSel ('Just "eiImportType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImportDeclarationType) :*: S1 ('MetaSel ('Just "eiImportedAs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModuleName)))))

data ExternsFixity Source #

A fixity declaration in an externs file

Constructors

ExternsFixity 

Fields

Instances

Instances details
Generic ExternsFixity Source # 
Instance details

Defined in Language.PureScript.Externs

Associated Types

type Rep ExternsFixity :: Type -> Type #

Show ExternsFixity Source # 
Instance details

Defined in Language.PureScript.Externs

Serialise ExternsFixity Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsFixity Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsFixity = D1 ('MetaData "ExternsFixity" "Language.PureScript.Externs" "purescript-0.15.6-1py82rzyCAT3bEGm9U9Gns" 'False) (C1 ('MetaCons "ExternsFixity" 'PrefixI 'True) ((S1 ('MetaSel ('Just "efAssociativity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Associativity) :*: S1 ('MetaSel ('Just "efPrecedence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Precedence)) :*: (S1 ('MetaSel ('Just "efOperator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OpName 'ValueOpName)) :*: S1 ('MetaSel ('Just "efAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Qualified (Either Ident (ProperName 'ConstructorName)))))))

data ExternsTypeFixity Source #

A type fixity declaration in an externs file

Constructors

ExternsTypeFixity 

Fields

Instances

Instances details
Generic ExternsTypeFixity Source # 
Instance details

Defined in Language.PureScript.Externs

Associated Types

type Rep ExternsTypeFixity :: Type -> Type #

Show ExternsTypeFixity Source # 
Instance details

Defined in Language.PureScript.Externs

Serialise ExternsTypeFixity Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsTypeFixity Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsTypeFixity = D1 ('MetaData "ExternsTypeFixity" "Language.PureScript.Externs" "purescript-0.15.6-1py82rzyCAT3bEGm9U9Gns" 'False) (C1 ('MetaCons "ExternsTypeFixity" 'PrefixI 'True) ((S1 ('MetaSel ('Just "efTypeAssociativity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Associativity) :*: S1 ('MetaSel ('Just "efTypePrecedence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Precedence)) :*: (S1 ('MetaSel ('Just "efTypeOperator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OpName 'TypeOpName)) :*: S1 ('MetaSel ('Just "efTypeAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Qualified (ProperName 'TypeName))))))

data ExternsDeclaration Source #

A type or value declaration appearing in an externs file

Instances

Instances details
Generic ExternsDeclaration Source # 
Instance details

Defined in Language.PureScript.Externs

Associated Types

type Rep ExternsDeclaration :: Type -> Type #

Show ExternsDeclaration Source # 
Instance details

Defined in Language.PureScript.Externs

Serialise ExternsDeclaration Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsDeclaration Source # 
Instance details

Defined in Language.PureScript.Externs

type Rep ExternsDeclaration = D1 ('MetaData "ExternsDeclaration" "Language.PureScript.Externs" "purescript-0.15.6-1py82rzyCAT3bEGm9U9Gns" 'False) ((C1 ('MetaCons "EDType" 'PrefixI 'True) (S1 ('MetaSel ('Just "edTypeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProperName 'TypeName)) :*: (S1 ('MetaSel ('Just "edTypeKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceType) :*: S1 ('MetaSel ('Just "edTypeDeclarationKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeKind))) :+: (C1 ('MetaCons "EDTypeSynonym" 'PrefixI 'True) (S1 ('MetaSel ('Just "edTypeSynonymName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProperName 'TypeName)) :*: (S1 ('MetaSel ('Just "edTypeSynonymArguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Maybe SourceType)]) :*: S1 ('MetaSel ('Just "edTypeSynonymType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceType))) :+: C1 ('MetaCons "EDDataConstructor" 'PrefixI 'True) ((S1 ('MetaSel ('Just "edDataCtorName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProperName 'ConstructorName)) :*: S1 ('MetaSel ('Just "edDataCtorOrigin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataDeclType)) :*: (S1 ('MetaSel ('Just "edDataCtorTypeCtor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProperName 'TypeName)) :*: (S1 ('MetaSel ('Just "edDataCtorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceType) :*: S1 ('MetaSel ('Just "edDataCtorFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ident])))))) :+: (C1 ('MetaCons "EDValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "edValueName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Just "edValueType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceType)) :+: (C1 ('MetaCons "EDClass" 'PrefixI 'True) ((S1 ('MetaSel ('Just "edClassName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProperName 'ClassName)) :*: (S1 ('MetaSel ('Just "edClassTypeArguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Maybe SourceType)]) :*: S1 ('MetaSel ('Just "edClassMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Ident, SourceType)]))) :*: (S1 ('MetaSel ('Just "edClassConstraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceConstraint]) :*: (S1 ('MetaSel ('Just "edFunctionalDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunctionalDependency]) :*: S1 ('MetaSel ('Just "edIsEmpty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: C1 ('MetaCons "EDInstance" 'PrefixI 'True) (((S1 ('MetaSel ('Just "edInstanceClassName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Qualified (ProperName 'ClassName))) :*: S1 ('MetaSel ('Just "edInstanceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :*: (S1 ('MetaSel ('Just "edInstanceForAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, SourceType)]) :*: (S1 ('MetaSel ('Just "edInstanceKinds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceType]) :*: S1 ('MetaSel ('Just "edInstanceTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceType])))) :*: ((S1 ('MetaSel ('Just "edInstanceConstraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [SourceConstraint])) :*: S1 ('MetaSel ('Just "edInstanceChain") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChainId))) :*: (S1 ('MetaSel ('Just "edInstanceChainIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: (S1 ('MetaSel ('Just "edInstanceNameSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NameSource) :*: S1 ('MetaSel ('Just "edInstanceSourceSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceSpan))))))))

externsIsCurrentVersion :: ExternsFile -> Bool Source #

Check whether the version in an externs file matches the currently running version.

moduleToExternsFile :: Module -> Environment -> Map Ident Ident -> ExternsFile Source #

Generate an externs file for all declarations in a module.

The `Map Ident Ident` argument should contain any top-level GenIdents that were rewritten to Idents when the module was compiled; this rewrite only happens in the CoreFn, not the original module AST, so it needs to be applied to the exported names here also. (The appropriate map is returned by renameInModule.)

applyExternsFileToEnvironment :: ExternsFile -> Environment -> Environment Source #

Convert an externs file back into a module