Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Environment = Environment {
- names :: Map (Qualified Ident) (SourceType, NameKind, NameVisibility)
- types :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- dataConstructors :: Map (Qualified (ProperName ConstructorName)) (DataDeclType, ProperName TypeName, SourceType, [Ident])
- typeSynonyms :: Map (Qualified (ProperName TypeName)) ([(Text, Maybe SourceKind)], SourceType)
- typeClassDictionaries :: Map (Maybe ModuleName) (Map (Qualified (ProperName ClassName)) (Map (Qualified Ident) (NonEmpty NamedDict)))
- typeClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- kinds :: Set (Qualified (ProperName KindName))
- data TypeClassData = TypeClassData {}
- data FunctionalDependency = FunctionalDependency {
- fdDeterminers :: [Int]
- fdDetermined :: [Int]
- initEnvironment :: Environment
- makeTypeClassData :: [(Text, Maybe SourceKind)] -> [(Ident, SourceType)] -> [SourceConstraint] -> [FunctionalDependency] -> TypeClassData
- data NameVisibility
- data NameKind
- data TypeKind
- data DataDeclType
- showDataDeclType :: DataDeclType -> Text
- primName :: Text -> Qualified (ProperName a)
- primSubName :: Text -> Text -> Qualified (ProperName a)
- primKind :: Text -> SourceKind
- primSubKind :: Text -> Text -> SourceKind
- kindType :: SourceKind
- kindConstraint :: SourceKind
- isKindType :: Kind a -> Bool
- (-:>) :: SourceKind -> SourceKind -> SourceKind
- kindSymbol :: SourceKind
- kindDoc :: SourceKind
- kindBoolean :: SourceKind
- kindOrdering :: SourceKind
- kindRowList :: SourceKind
- kindRow :: SourceKind -> SourceKind
- primTy :: Text -> SourceType
- tyFunction :: SourceType
- tyString :: SourceType
- tyChar :: SourceType
- tyNumber :: SourceType
- tyInt :: SourceType
- tyBoolean :: SourceType
- tyArray :: SourceType
- tyRecord :: SourceType
- isObject :: Type a -> Bool
- isFunction :: Type a -> Bool
- isTypeOrApplied :: Type a -> Type b -> Bool
- function :: SourceType -> SourceType -> SourceType
- primKinds :: Set (Qualified (ProperName KindName))
- primBooleanKinds :: Set (Qualified (ProperName KindName))
- primOrderingKinds :: Set (Qualified (ProperName KindName))
- primRowListKinds :: Set (Qualified (ProperName KindName))
- primTypeErrorKinds :: Set (Qualified (ProperName KindName))
- allPrimKinds :: Set (Qualified (ProperName KindName))
- primTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- allPrimTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- primBooleanTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- primOrderingTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- primRowTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- primRowListTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- primSymbolTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- primTypeErrorTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind)
- primClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- allPrimClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- primRowClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- primRowListClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- primSymbolClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- primTypeErrorClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- lookupConstructor :: Environment -> Qualified (ProperName ConstructorName) -> (DataDeclType, ProperName TypeName, SourceType, [Ident])
- isNewtypeConstructor :: Environment -> Qualified (ProperName ConstructorName) -> Bool
- lookupValue :: Environment -> Qualified Ident -> Maybe (SourceType, NameKind, NameVisibility)
Documentation
data Environment Source #
The Environment
defines all values and types which are currently in scope:
Environment | |
|
Instances
data TypeClassData Source #
Information about a type class
TypeClassData | |
|
Instances
data FunctionalDependency Source #
A functional dependency indicates a relationship between two sets of type arguments in a class declaration.
FunctionalDependency | |
|
Instances
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
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 # | |
Defined in Language.PureScript.Environment (==) :: NameVisibility -> NameVisibility -> Bool # (/=) :: NameVisibility -> NameVisibility -> Bool # | |
Show NameVisibility Source # | |
Defined in Language.PureScript.Environment showsPrec :: Int -> NameVisibility -> ShowS # show :: NameVisibility -> String # showList :: [NameVisibility] -> ShowS # | |
Generic NameVisibility Source # | |
Defined in Language.PureScript.Environment type Rep NameVisibility :: Type -> Type # from :: NameVisibility -> Rep NameVisibility x # to :: Rep NameVisibility x -> NameVisibility # | |
NFData NameVisibility Source # | |
Defined in Language.PureScript.Environment rnf :: NameVisibility -> () # | |
type Rep NameVisibility Source # | |
Defined in Language.PureScript.Environment |
A flag for whether a name is for an private or public value - only public values will be included in a generated externs file.
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 # | |
Show NameKind Source # | |
Generic NameKind Source # | |
NFData NameKind Source # | |
Defined in Language.PureScript.Environment | |
type Rep NameKind Source # | |
Defined in Language.PureScript.Environment type Rep NameKind = D1 (MetaData "NameKind" "Language.PureScript.Environment" "purescript-0.13.0-1whdl2565Nb1wvlLK7uK18" 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))) |
The kinds of a type
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
data DataDeclType Source #
The type ('data' or 'newtype') of a data type declaration
Instances
showDataDeclType :: DataDeclType -> Text Source #
primSubName :: Text -> Text -> Qualified (ProperName a) Source #
Construct a ProperName
in the Prim.NAME
module.
primKind :: Text -> SourceKind Source #
primSubKind :: Text -> Text -> SourceKind Source #
kindType :: SourceKind Source #
Kind of ground types
isKindType :: Kind a -> Bool Source #
(-:>) :: SourceKind -> SourceKind -> SourceKind infixr 4 Source #
kindDoc :: SourceKind Source #
kindRow :: SourceKind -> SourceKind Source #
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
isFunction :: Type a -> Bool Source #
Check whether a type is a function
function :: SourceType -> SourceType -> SourceType Source #
Smart constructor for function types
primBooleanKinds :: Set (Qualified (ProperName KindName)) Source #
Kinds in Prim.Boolean
primOrderingKinds :: Set (Qualified (ProperName KindName)) Source #
Kinds in Prim.Ordering
primRowListKinds :: Set (Qualified (ProperName KindName)) Source #
Kinds in Prim.RowList
primTypeErrorKinds :: Set (Qualified (ProperName KindName)) Source #
Kinds in Prim.TypeError
allPrimKinds :: Set (Qualified (ProperName KindName)) Source #
All primitive kinds
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.
primBooleanTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind) Source #
primOrderingTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind) Source #
primRowTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind) Source #
primRowListTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind) Source #
primSymbolTypes :: Map (Qualified (ProperName TypeName)) (SourceKind, TypeKind) Source #
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.