Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.PureScript.Environment
Synopsis
- data Environment = Environment {
- names :: Map (Qualified Ident) (SourceType, NameKind, NameVisibility)
- types :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- dataConstructors :: Map (Qualified (ProperName 'ConstructorName)) (DataDeclType, ProperName 'TypeName, SourceType, [Ident])
- typeSynonyms :: Map (Qualified (ProperName 'TypeName)) ([(Text, Maybe SourceType)], SourceType)
- typeClassDictionaries :: Map QualifiedBy (Map (Qualified (ProperName 'ClassName)) (Map (Qualified Ident) (NonEmpty NamedDict)))
- typeClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- data TypeClassData = TypeClassData {
- typeClassArguments :: [(Text, Maybe SourceType)]
- typeClassMembers :: [(Ident, SourceType, Maybe (Set (NonEmpty Int)))]
- typeClassSuperclasses :: [SourceConstraint]
- typeClassDependencies :: [FunctionalDependency]
- typeClassDeterminedArguments :: Set Int
- typeClassCoveringSets :: Set (Set Int)
- typeClassIsEmpty :: Bool
- data FunctionalDependency = FunctionalDependency {
- fdDeterminers :: [Int]
- fdDetermined :: [Int]
- initEnvironment :: Environment
- makeTypeClassData :: [(Text, Maybe SourceType)] -> [(Ident, SourceType)] -> [SourceConstraint] -> [FunctionalDependency] -> Bool -> TypeClassData
- type Frontier = Map IntSet (First (IntMap (NonEmpty IntSet)))
- computeCoveringSets :: Int -> [FunctionalDependency] -> (Set Int, Set (Set Int))
- data NameVisibility
- data NameKind
- data TypeKind
- = DataType DataDeclType [(Text, Maybe SourceType, Role)] [(ProperName 'ConstructorName, [SourceType])]
- | TypeSynonym
- | ExternData [Role]
- | LocalTypeVariable
- | ScopedTypeVar
- data DataDeclType
- showDataDeclType :: DataDeclType -> Text
- kindType :: SourceType
- kindConstraint :: SourceType
- kindSymbol :: SourceType
- kindDoc :: SourceType
- kindOrdering :: SourceType
- kindRowList :: SourceType -> SourceType
- kindRow :: SourceType -> SourceType
- kindOfREmpty :: SourceType
- tyFunction :: SourceType
- tyString :: SourceType
- tyChar :: SourceType
- tyNumber :: SourceType
- tyInt :: SourceType
- tyBoolean :: SourceType
- tyArray :: SourceType
- tyRecord :: SourceType
- tyVar :: Text -> SourceType
- tyForall :: Text -> SourceType -> SourceType -> SourceType
- function :: SourceType -> SourceType -> SourceType
- (-:>) :: SourceType -> SourceType -> SourceType
- primClass :: Qualified (ProperName 'ClassName) -> (SourceType -> SourceType) -> [(Qualified (ProperName 'TypeName), (SourceType, TypeKind))]
- primTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- allPrimTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primBooleanTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primCoerceTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primOrderingTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primRowTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primRowListTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primSymbolTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primIntTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primTypeErrorTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind)
- primClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- allPrimClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- primCoerceClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- primRowClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- primRowListClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- primSymbolClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- primIntClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- primTypeErrorClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData
- lookupConstructor :: Environment -> Qualified (ProperName 'ConstructorName) -> (DataDeclType, ProperName 'TypeName, SourceType, [Ident])
- lookupValue :: Environment -> Qualified Ident -> Maybe (SourceType, NameKind, NameVisibility)
- dictTypeName' :: Text -> Text
- dictTypeName :: forall (a :: ProperNameType). ProperName a -> ProperName a
- isDictTypeName :: forall (a :: ProperNameType). ProperName a -> Bool
- nominalRolesForKind :: Type a -> [Role]
- kindArity :: Type a -> Int
- unapplyKinds :: Type a -> ([Type a], Type a)
Documentation
data Environment #
The Environment
defines all values and types which are currently in scope:
Constructors
Environment | |
Fields
|
Instances
data TypeClassData #
Information about a type class
Constructors
TypeClassData | |
Fields
|
Instances
NFData TypeClassData # | |||||
Defined in Language.PureScript.Environment Methods rnf :: TypeClassData -> () # | |||||
Generic TypeClassData # | |||||
Defined in Language.PureScript.Environment Associated Types
| |||||
Show TypeClassData # | |||||
Defined in Language.PureScript.Environment Methods showsPrec :: Int -> TypeClassData -> ShowS # show :: TypeClassData -> String # showList :: [TypeClassData] -> ShowS # | |||||
type Rep TypeClassData # | |||||
Defined in Language.PureScript.Environment type Rep TypeClassData = D1 ('MetaData "TypeClassData" "Language.PureScript.Environment" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" 'False) (C1 ('MetaCons "TypeClassData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "typeClassArguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Maybe SourceType)]) :*: (S1 ('MetaSel ('Just "typeClassMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Ident, SourceType, Maybe (Set (NonEmpty Int)))]) :*: 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))) :*: S1 ('MetaSel ('Just "typeClassIsEmpty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) |
data FunctionalDependency #
A functional dependency indicates a relationship between two sets of type arguments in a class declaration.
Constructors
FunctionalDependency | |
Fields
|
Instances
FromJSON FunctionalDependency # | |||||
Defined in Language.PureScript.Environment Methods parseJSON :: Value -> Parser FunctionalDependency # parseJSONList :: Value -> Parser [FunctionalDependency] # | |||||
ToJSON FunctionalDependency # | |||||
Defined in Language.PureScript.Environment Methods toJSON :: FunctionalDependency -> Value # toEncoding :: FunctionalDependency -> Encoding # toJSONList :: [FunctionalDependency] -> Value # toEncodingList :: [FunctionalDependency] -> Encoding # omitField :: FunctionalDependency -> Bool # | |||||
NFData FunctionalDependency # | |||||
Defined in Language.PureScript.Environment Methods rnf :: FunctionalDependency -> () # | |||||
Generic FunctionalDependency # | |||||
Defined in Language.PureScript.Environment Associated Types
Methods from :: FunctionalDependency -> Rep FunctionalDependency x # to :: Rep FunctionalDependency x -> FunctionalDependency # | |||||
Show FunctionalDependency # | |||||
Defined in Language.PureScript.Environment Methods showsPrec :: Int -> FunctionalDependency -> ShowS # show :: FunctionalDependency -> String # showList :: [FunctionalDependency] -> ShowS # | |||||
Serialise FunctionalDependency # | |||||
Defined in Language.PureScript.Environment Methods encode :: FunctionalDependency -> Encoding # decode :: Decoder s FunctionalDependency # encodeList :: [FunctionalDependency] -> Encoding # decodeList :: Decoder s [FunctionalDependency] # | |||||
type Rep FunctionalDependency # | |||||
Defined in Language.PureScript.Environment type Rep FunctionalDependency = D1 ('MetaData "FunctionalDependency" "Language.PureScript.Environment" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" '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 #
The initial environment with no values and only the default javascript types defined
makeTypeClassData :: [(Text, Maybe SourceType)] -> [(Ident, SourceType)] -> [SourceConstraint] -> [FunctionalDependency] -> Bool -> TypeClassData #
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.
computeCoveringSets :: Int -> [FunctionalDependency] -> (Set Int, Set (Set Int)) #
data NameVisibility #
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
NFData NameVisibility # | |||||
Defined in Language.PureScript.Environment Methods rnf :: NameVisibility -> () # | |||||
Generic NameVisibility # | |||||
Defined in Language.PureScript.Environment Associated Types
Methods from :: NameVisibility -> Rep NameVisibility x # to :: Rep NameVisibility x -> NameVisibility # | |||||
Show NameVisibility # | |||||
Defined in Language.PureScript.Environment Methods showsPrec :: Int -> NameVisibility -> ShowS # show :: NameVisibility -> String # showList :: [NameVisibility] -> ShowS # | |||||
Eq NameVisibility # | |||||
Defined in Language.PureScript.Environment Methods (==) :: NameVisibility -> NameVisibility -> Bool # (/=) :: NameVisibility -> NameVisibility -> Bool # | |||||
Serialise NameVisibility # | |||||
Defined in Language.PureScript.Environment Methods encode :: NameVisibility -> Encoding # decode :: Decoder s NameVisibility # encodeList :: [NameVisibility] -> Encoding # decodeList :: Decoder s [NameVisibility] # | |||||
type Rep NameVisibility # | |||||
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.
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 foreign import declaration |
External | A name for member introduced by foreign import |
Instances
NFData NameKind # | |||||
Defined in Language.PureScript.Environment | |||||
Generic NameKind # | |||||
Defined in Language.PureScript.Environment Associated Types
| |||||
Show NameKind # | |||||
Eq NameKind # | |||||
Serialise NameKind # | |||||
type Rep NameKind # | |||||
Defined in Language.PureScript.Environment type Rep NameKind = D1 ('MetaData "NameKind" "Language.PureScript.Environment" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" '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
Constructors
DataType DataDeclType [(Text, Maybe SourceType, Role)] [(ProperName 'ConstructorName, [SourceType])] | Data type |
TypeSynonym | Type synonym |
ExternData [Role] | Foreign data |
LocalTypeVariable | A local type variable |
ScopedTypeVar | A scoped type variable |
Instances
NFData TypeKind # | |||||
Defined in Language.PureScript.Environment | |||||
Generic TypeKind # | |||||
Defined in Language.PureScript.Environment Associated Types
| |||||
Show TypeKind # | |||||
Eq TypeKind # | |||||
Serialise TypeKind # | |||||
type Rep TypeKind # | |||||
Defined in Language.PureScript.Environment type Rep TypeKind = D1 ('MetaData "TypeKind" "Language.PureScript.Environment" "purescript-0.15.15-8K0LbmS63k4ILju2RsIrDp" 'False) ((C1 ('MetaCons "DataType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataDeclType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Maybe SourceType, Role)]) :*: 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) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role])) :+: (C1 ('MetaCons "LocalTypeVariable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScopedTypeVar" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data DataDeclType #
The type ('data' or 'newtype') of a data type declaration
Instances
FromJSON DataDeclType # | |||||
Defined in Language.PureScript.Environment | |||||
ToJSON DataDeclType # | |||||
Defined in Language.PureScript.Environment Methods toJSON :: DataDeclType -> Value # toEncoding :: DataDeclType -> Encoding # toJSONList :: [DataDeclType] -> Value # toEncodingList :: [DataDeclType] -> Encoding # omitField :: DataDeclType -> Bool # | |||||
NFData DataDeclType # | |||||
Defined in Language.PureScript.Environment Methods rnf :: DataDeclType -> () # | |||||
Generic DataDeclType # | |||||
Defined in Language.PureScript.Environment Associated Types
| |||||
Show DataDeclType # | |||||
Defined in Language.PureScript.Environment Methods showsPrec :: Int -> DataDeclType -> ShowS # show :: DataDeclType -> String # showList :: [DataDeclType] -> ShowS # | |||||
Eq DataDeclType # | |||||
Defined in Language.PureScript.Environment | |||||
Ord DataDeclType # | |||||
Defined in Language.PureScript.Environment Methods compare :: DataDeclType -> DataDeclType -> Ordering # (<) :: DataDeclType -> DataDeclType -> Bool # (<=) :: DataDeclType -> DataDeclType -> Bool # (>) :: DataDeclType -> DataDeclType -> Bool # (>=) :: DataDeclType -> DataDeclType -> Bool # max :: DataDeclType -> DataDeclType -> DataDeclType # min :: DataDeclType -> DataDeclType -> DataDeclType # | |||||
Serialise DataDeclType # | |||||
Defined in Language.PureScript.Environment Methods encode :: DataDeclType -> Encoding # decode :: Decoder s DataDeclType # encodeList :: [DataDeclType] -> Encoding # decodeList :: Decoder s [DataDeclType] # | |||||
type Rep DataDeclType # | |||||
Defined in Language.PureScript.Environment |
showDataDeclType :: DataDeclType -> Text #
kindType :: SourceType #
Kind of ground types
kindDoc :: SourceType #
kindRowList :: SourceType -> SourceType #
kindRow :: SourceType -> SourceType #
Type constructor for functions
tyString :: SourceType #
Type constructor for strings
tyChar :: SourceType #
Type constructor for strings
tyNumber :: SourceType #
Type constructor for numbers
tyInt :: SourceType #
Type constructor for integers
tyBoolean :: SourceType #
Type constructor for booleans
tyArray :: SourceType #
Type constructor for arrays
tyRecord :: SourceType #
Type constructor for records
tyVar :: Text -> SourceType #
tyForall :: Text -> SourceType -> SourceType -> SourceType #
function :: SourceType -> SourceType -> SourceType #
Smart constructor for function types
(-:>) :: SourceType -> SourceType -> SourceType infixr 4 #
primClass :: Qualified (ProperName 'ClassName) -> (SourceType -> SourceType) -> [(Qualified (ProperName 'TypeName), (SourceType, TypeKind))] #
primTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
The primitive types in the external 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)) (SourceType, TypeKind) #
This Map
contains all of the prim types from all Prim modules.
primBooleanTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primCoerceTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primOrderingTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primRowTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primRowListTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primSymbolTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primIntTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primTypeErrorTypes :: Map (Qualified (ProperName 'TypeName)) (SourceType, TypeKind) #
primClasses :: Map (Qualified (ProperName 'ClassName)) TypeClassData #
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 #
This contains all of the type classes from all Prim modules.
lookupConstructor :: Environment -> Qualified (ProperName 'ConstructorName) -> (DataDeclType, ProperName 'TypeName, SourceType, [Ident]) #
Finds information about data constructors from the current environment.
lookupValue :: Environment -> Qualified Ident -> Maybe (SourceType, NameKind, NameVisibility) #
Finds information about values from the current environment.
dictTypeName' :: Text -> Text #
dictTypeName :: forall (a :: ProperNameType). ProperName a -> ProperName a #
isDictTypeName :: forall (a :: ProperNameType). ProperName a -> Bool #
nominalRolesForKind :: Type a -> [Role] #
Given the kind of a type, generate a list Nominal
roles. This is used for
opaque foreign types as well as type classes.
unapplyKinds :: Type a -> ([Type a], Type a) #