Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Environment = Environment {
- names :: Map (Qualified Ident) (Type, NameKind, NameVisibility)
- types :: Map (Qualified (ProperName TypeName)) (Kind, TypeKind)
- dataConstructors :: Map (Qualified (ProperName ConstructorName)) (DataDeclType, ProperName TypeName, Type, [Ident])
- typeSynonyms :: Map (Qualified (ProperName TypeName)) ([(Text, Maybe Kind)], Type)
- typeClassDictionaries :: Map (Maybe ModuleName) (Map (Qualified (ProperName ClassName)) (Map (Qualified Ident) 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 Kind)] -> [(Ident, Type)] -> [Constraint] -> [FunctionalDependency] -> TypeClassData
- data NameVisibility
- data NameKind
- data TypeKind
- = DataType [(Text, Maybe Kind)] [(ProperName ConstructorName, [Type])]
- | TypeSynonym
- | ExternData
- | LocalTypeVariable
- | ScopedTypeVar
- data DataDeclType
- showDataDeclType :: DataDeclType -> Text
- primName :: Text -> Qualified (ProperName a)
- primKind :: Text -> Kind
- kindType :: Kind
- kindEffect :: Kind
- kindSymbol :: Kind
- primTy :: Text -> Type
- tyFunction :: Type
- tyString :: Type
- tyChar :: Type
- tyNumber :: Type
- tyInt :: Type
- tyBoolean :: Type
- tyArray :: Type
- tyRecord :: Type
- isObject :: Type -> Bool
- isFunction :: Type -> Bool
- isTypeOrApplied :: Type -> Type -> Bool
- function :: Type -> Type -> Type
- primKinds :: Set (Qualified (ProperName KindName))
- primTypes :: Map (Qualified (ProperName TypeName)) (Kind, TypeKind)
- primClasses :: Map (Qualified (ProperName ClassName)) TypeClassData
- lookupConstructor :: Environment -> Qualified (ProperName ConstructorName) -> (DataDeclType, ProperName TypeName, Type, [Ident])
- isNewtypeConstructor :: Environment -> Qualified (ProperName ConstructorName) -> Bool
- lookupValue :: Environment -> Qualified Ident -> Maybe (Type, NameKind, NameVisibility)
Documentation
data Environment Source #
The Environment
defines all values and types which are currently in scope:
Environment | |
|
data TypeClassData Source #
Information about a type class
TypeClassData | |
|
data FunctionalDependency Source #
A functional dependency indicates a relationship between two sets of type arguments in a class declaration.
FunctionalDependency | |
|
initEnvironment :: Environment Source #
The initial environment with no values and only the default javascript types defined
makeTypeClassData :: [(Text, Maybe Kind)] -> [(Ident, Type)] -> [Constraint] -> [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
A flag for whether a name is for an private or public value - only public values will be included in a generated externs file.
The kinds of a type
DataType [(Text, Maybe Kind)] [(ProperName ConstructorName, [Type])] | Data type |
TypeSynonym | Type synonym |
ExternData | Foreign data |
LocalTypeVariable | A local type variable |
ScopedTypeVar | A scoped type variable |
data DataDeclType Source #
The type ('data' or 'newtype') of a data type declaration
showDataDeclType :: DataDeclType -> Text Source #
kindEffect :: Kind Source #
kindSymbol :: Kind Source #
tyFunction :: Type Source #
Type constructor for functions
isFunction :: Type -> Bool Source #
Check whether a type is a function
primTypes :: Map (Qualified (ProperName TypeName)) (Kind, TypeKind) Source #
The primitive types in the external javascript environment with their
associated kinds. There are also pseudo Fail
and Partial
types
that correspond to the classes with the same names.
primClasses :: Map (Qualified (ProperName ClassName)) TypeClassData Source #
The primitive class map. This just contains the Fail
and Partial
classes. Partial
is used as a kind of magic constraint for partial
functions. Fail
is used for user-defined type errors.
lookupConstructor :: Environment -> Qualified (ProperName ConstructorName) -> (DataDeclType, ProperName TypeName, Type, [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 (Type, NameKind, NameVisibility) Source #
Finds information about values from the current environment.