purescript-0.13.2: PureScript Programming Language Compiler

Safe HaskellNone
LanguageHaskell2010

Language.PureScript.Environment

Synopsis

Documentation

data Environment Source #

The Environment defines all values and types which are currently in scope:

Constructors

Environment 

Fields

Instances
Show Environment Source # 
Instance details

Defined in Language.PureScript.Environment

Generic Environment Source # 
Instance details

Defined in Language.PureScript.Environment

Associated Types

type Rep Environment :: Type -> Type #

NFData Environment Source # 
Instance details

Defined in Language.PureScript.Environment

Methods

rnf :: Environment -> () #

type Rep Environment Source # 
Instance details

Defined in Language.PureScript.Environment

data TypeClassData Source #

Information about a type class

Constructors

TypeClassData 

Fields

Instances
Show TypeClassData Source # 
Instance details

Defined in Language.PureScript.Environment

Generic TypeClassData Source # 
Instance details

Defined in Language.PureScript.Environment

Associated Types

type Rep TypeClassData :: Type -> Type #

NFData TypeClassData Source # 
Instance details

Defined in Language.PureScript.Environment

Methods

rnf :: TypeClassData -> () #

type Rep TypeClassData Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep TypeClassData = D1 (MetaData "TypeClassData" "Language.PureScript.Environment" "purescript-0.13.2-3QkFEXX4DzwIft0Bgxs9Xq" False) (C1 (MetaCons "TypeClassData" PrefixI True) ((S1 (MetaSel (Just "typeClassArguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Text, Maybe SourceKind)]) :*: (S1 (MetaSel (Just "typeClassMembers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Ident, SourceType)]) :*: S1 (MetaSel (Just "typeClassSuperclasses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SourceConstraint]))) :*: (S1 (MetaSel (Just "typeClassDependencies") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FunctionalDependency]) :*: (S1 (MetaSel (Just "typeClassDeterminedArguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set Int)) :*: S1 (MetaSel (Just "typeClassCoveringSets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (Set Int)))))))

data FunctionalDependency Source #

A functional dependency indicates a relationship between two sets of type arguments in a class declaration.

Constructors

FunctionalDependency 

Fields

Instances
Show FunctionalDependency Source # 
Instance details

Defined in Language.PureScript.Environment

Generic FunctionalDependency Source # 
Instance details

Defined in Language.PureScript.Environment

Associated Types

type Rep FunctionalDependency :: Type -> Type #

NFData FunctionalDependency Source # 
Instance details

Defined in Language.PureScript.Environment

Methods

rnf :: FunctionalDependency -> () #

ToJSON FunctionalDependency Source # 
Instance details

Defined in Language.PureScript.Environment

FromJSON FunctionalDependency Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep FunctionalDependency Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep FunctionalDependency = D1 (MetaData "FunctionalDependency" "Language.PureScript.Environment" "purescript-0.13.2-3QkFEXX4DzwIft0Bgxs9Xq" False) (C1 (MetaCons "FunctionalDependency" PrefixI True) (S1 (MetaSel (Just "fdDeterminers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int]) :*: S1 (MetaSel (Just "fdDetermined") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])))

initEnvironment :: Environment Source #

The initial environment with no values and only the default javascript types defined

makeTypeClassData :: [(Text, Maybe SourceKind)] -> [(Ident, SourceType)] -> [SourceConstraint] -> [FunctionalDependency] -> TypeClassData Source #

A constructor for TypeClassData that computes which type class arguments are fully determined and argument covering sets. Fully determined means that this argument cannot be used when selecting a type class instance. A covering set is a minimal collection of arguments that can be used to find an instance and therefore determine all other type arguments.

An example of the difference between determined and fully determined would be with the class: ```class C a b c | a -> b, b -> a, b -> c``` In this case, a must differ when b differs, and vice versa - each is determined by the other. Both a and b can be used in selecting a type class instance. However, c cannot - it is fully determined by a and b.

Define a graph of type class arguments with edges being fundep determiners to determined. Each argument also has a self looping edge. An argument is fully determined if doesn't appear at the start of a path of strongly connected components. An argument is not fully determined otherwise.

The way we compute this is by saying: an argument X is fully determined if there are arguments that determine X that X does not determine. This is the same thing: everything X determines includes everything in its SCC, and everything determining X is either before it in an SCC path, or in the same SCC.

data NameVisibility Source #

The visibility of a name in scope

Constructors

Undefined

The name is defined in the current binding group, but is not visible

Defined

The name is defined in the another binding group, or has been made visible by a function binder

Instances
Eq NameVisibility Source # 
Instance details

Defined in Language.PureScript.Environment

Show NameVisibility Source # 
Instance details

Defined in Language.PureScript.Environment

Generic NameVisibility Source # 
Instance details

Defined in Language.PureScript.Environment

Associated Types

type Rep NameVisibility :: Type -> Type #

NFData NameVisibility Source # 
Instance details

Defined in Language.PureScript.Environment

Methods

rnf :: NameVisibility -> () #

type Rep NameVisibility Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep NameVisibility = D1 (MetaData "NameVisibility" "Language.PureScript.Environment" "purescript-0.13.2-3QkFEXX4DzwIft0Bgxs9Xq" False) (C1 (MetaCons "Undefined" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Defined" PrefixI False) (U1 :: Type -> Type))

data NameKind Source #

A flag for whether a name is for an private or public value - only public values will be included in a generated externs file.

Constructors

Private

A private value introduced as an artifact of code generation (class instances, class member accessors, etc.)

Public

A public value for a module member or foreing import declaration

External

A name for member introduced by foreign import

Instances
Eq NameKind Source # 
Instance details

Defined in Language.PureScript.Environment

Show NameKind Source # 
Instance details

Defined in Language.PureScript.Environment

Generic NameKind Source # 
Instance details

Defined in Language.PureScript.Environment

Associated Types

type Rep NameKind :: Type -> Type #

Methods

from :: NameKind -> Rep NameKind x #

to :: Rep NameKind x -> NameKind #

NFData NameKind Source # 
Instance details

Defined in Language.PureScript.Environment

Methods

rnf :: NameKind -> () #

type Rep NameKind Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep NameKind = D1 (MetaData "NameKind" "Language.PureScript.Environment" "purescript-0.13.2-3QkFEXX4DzwIft0Bgxs9Xq" False) (C1 (MetaCons "Private" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Public" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "External" PrefixI False) (U1 :: Type -> Type)))

data TypeKind Source #

The kinds of a type

Constructors

DataType [(Text, Maybe SourceKind)] [(ProperName ConstructorName, [SourceType])]

Data type

TypeSynonym

Type synonym

ExternData

Foreign data

LocalTypeVariable

A local type variable

ScopedTypeVar

A scoped type variable

Instances
Eq TypeKind Source # 
Instance details

Defined in Language.PureScript.Environment

Show TypeKind Source # 
Instance details

Defined in Language.PureScript.Environment

Generic TypeKind Source # 
Instance details

Defined in Language.PureScript.Environment

Associated Types

type Rep TypeKind :: Type -> Type #

Methods

from :: TypeKind -> Rep TypeKind x #

to :: Rep TypeKind x -> TypeKind #

NFData TypeKind Source # 
Instance details

Defined in Language.PureScript.Environment

Methods

rnf :: TypeKind -> () #

ToJSON TypeKind Source # 
Instance details

Defined in Language.PureScript.Environment

FromJSON TypeKind Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep TypeKind Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep TypeKind = D1 (MetaData "TypeKind" "Language.PureScript.Environment" "purescript-0.13.2-3QkFEXX4DzwIft0Bgxs9Xq" False) ((C1 (MetaCons "DataType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Text, Maybe SourceKind)]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ProperName ConstructorName, [SourceType])])) :+: C1 (MetaCons "TypeSynonym" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ExternData" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LocalTypeVariable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ScopedTypeVar" PrefixI False) (U1 :: Type -> Type))))

data DataDeclType Source #

The type ('data' or 'newtype') of a data type declaration

Constructors

Data

A standard data constructor

Newtype

A newtype constructor

Instances
Eq DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

Ord DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

Show DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

Generic DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

Associated Types

type Rep DataDeclType :: Type -> Type #

NFData DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

Methods

rnf :: DataDeclType -> () #

ToJSON DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

FromJSON DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep DataDeclType Source # 
Instance details

Defined in Language.PureScript.Environment

type Rep DataDeclType = D1 (MetaData "DataDeclType" "Language.PureScript.Environment" "purescript-0.13.2-3QkFEXX4DzwIft0Bgxs9Xq" False) (C1 (MetaCons "Data" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Newtype" PrefixI False) (U1 :: Type -> Type))

primName :: Text -> Qualified (ProperName a) Source #

Construct a ProperName in the Prim module

primSubName :: Text -> Text -> Qualified (ProperName a) Source #

Construct a ProperName in the Prim.NAME module.

kindType :: SourceKind Source #

Kind of ground types

primTy :: Text -> SourceType Source #

Construct a type in the Prim module

tyFunction :: SourceType Source #

Type constructor for functions

tyString :: SourceType Source #

Type constructor for strings

tyChar :: SourceType Source #

Type constructor for strings

tyNumber :: SourceType Source #

Type constructor for numbers

tyInt :: SourceType Source #

Type constructor for integers

tyBoolean :: SourceType Source #

Type constructor for booleans

tyArray :: SourceType Source #

Type constructor for arrays

tyRecord :: SourceType Source #

Type constructor for records

isObject :: Type a -> Bool Source #

Check whether a type is a record

isFunction :: Type a -> Bool Source #

Check whether a type is a function

function :: SourceType -> SourceType -> SourceType Source #

Smart constructor for function types

primTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind) Source #

The primitive types in the external javascript environment with their associated kinds. There are also pseudo Fail, Warn, and Partial types that correspond to the classes with the same names.

allPrimTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind) Source #

This Map contains all of the prim types from all Prim modules.

primClasses :: Map (Qualified (ProperName ClassName)) TypeClassData Source #

The primitive class map. This just contains the Partial class. Partial is used as a kind of magic constraint for partial functions.

allPrimClasses :: Map (Qualified (ProperName ClassName)) TypeClassData Source #

This contains all of the type classes from all Prim modules.

lookupConstructor :: Environment -> Qualified (ProperName ConstructorName) -> (DataDeclType, ProperName TypeName, SourceType, [Ident]) Source #

Finds information about data constructors from the current environment.

isNewtypeConstructor :: Environment -> Qualified (ProperName ConstructorName) -> Bool Source #

Checks whether a data constructor is for a newtype.

lookupValue :: Environment -> Qualified Ident -> Maybe (SourceType, NameKind, NameVisibility) Source #

Finds information about values from the current environment.