Copyright | (c) 2002 - 2004 Wolfgang Lux Martin Engelke 2015 Jan Tikovsky 2016 Finn Teegen |
---|---|
License | BSD-3-clause |
Maintainer | bjp@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module modules provides the definitions for the internal representation of types in the compiler along with some helper functions.
Synopsis
- data Type
- applyType :: Type -> [Type] -> Type
- unapplyType :: Bool -> Type -> (Type, [Type])
- rootOfType :: Type -> QualIdent
- isArrowType :: Type -> Bool
- arrowArity :: Type -> Int
- arrowArgs :: Type -> [Type]
- arrowBase :: Type -> Type
- arrowUnapply :: Type -> ([Type], Type)
- class IsType t where
- typeConstrs :: Type -> [QualIdent]
- qualifyType :: ModuleIdent -> Type -> Type
- unqualifyType :: ModuleIdent -> Type -> Type
- qualifyTC :: ModuleIdent -> QualIdent -> QualIdent
- data Pred = Pred QualIdent Type
- qualifyPred :: ModuleIdent -> Pred -> Pred
- unqualifyPred :: ModuleIdent -> Pred -> Pred
- type PredSet = Set Pred
- emptyPredSet :: PredSet
- partitionPredSet :: PredSet -> (PredSet, PredSet)
- minPredSet :: ClassEnv -> PredSet -> PredSet
- maxPredSet :: ClassEnv -> PredSet -> PredSet
- qualifyPredSet :: ModuleIdent -> PredSet -> PredSet
- unqualifyPredSet :: ModuleIdent -> PredSet -> PredSet
- data PredType = PredType PredSet Type
- predType :: Type -> PredType
- unpredType :: PredType -> Type
- qualifyPredType :: ModuleIdent -> PredType -> PredType
- unqualifyPredType :: ModuleIdent -> PredType -> PredType
- data DataConstr
- = DataConstr Ident [Type]
- | RecordConstr Ident [Ident] [Type]
- constrIdent :: DataConstr -> Ident
- constrTypes :: DataConstr -> [Type]
- recLabels :: DataConstr -> [Ident]
- recLabelTypes :: DataConstr -> [Type]
- tupleData :: [DataConstr]
- data ClassMethod = ClassMethod Ident (Maybe Int) PredType
- methodName :: ClassMethod -> Ident
- methodArity :: ClassMethod -> Maybe Int
- methodType :: ClassMethod -> PredType
- data TypeScheme = ForAll Int PredType
- monoType :: Type -> TypeScheme
- polyType :: Type -> TypeScheme
- typeScheme :: PredType -> TypeScheme
- rawType :: TypeScheme -> Type
- arrowType :: Type -> Type -> Type
- unitType :: Type
- predUnitType :: PredType
- boolType :: Type
- predBoolType :: PredType
- charType :: Type
- intType :: Type
- predIntType :: PredType
- floatType :: Type
- predFloatType :: PredType
- stringType :: Type
- predStringType :: PredType
- listType :: Type -> Type
- consType :: Type -> Type
- ioType :: Type -> Type
- tupleType :: [Type] -> Type
- numTypes :: [Type]
- fractionalTypes :: [Type]
- predefTypes :: [(Type, [DataConstr])]
Representation of types
TypeConstructor QualIdent | |
TypeVariable Int | |
TypeConstrained [Type] Int | |
TypeApply Type Type | |
TypeArrow Type Type | |
TypeForall [Int] Type |
rootOfType :: Type -> QualIdent Source #
isArrowType :: Type -> Bool Source #
arrowArity :: Type -> Int Source #
typeConstrs :: Type -> [QualIdent] Source #
qualifyType :: ModuleIdent -> Type -> Type Source #
unqualifyType :: ModuleIdent -> Type -> Type Source #
Representation of predicate, predicate sets and predicated types
qualifyPred :: ModuleIdent -> Pred -> Pred Source #
unqualifyPred :: ModuleIdent -> Pred -> Pred Source #
qualifyPredSet :: ModuleIdent -> PredSet -> PredSet Source #
unqualifyPredSet :: ModuleIdent -> PredSet -> PredSet Source #
unpredType :: PredType -> Type Source #
qualifyPredType :: ModuleIdent -> PredType -> PredType Source #
unqualifyPredType :: ModuleIdent -> PredType -> PredType Source #
Representation of data constructors
data DataConstr Source #
DataConstr Ident [Type] | |
RecordConstr Ident [Ident] [Type] |
Instances
Eq DataConstr Source # | |
Defined in Base.Types (==) :: DataConstr -> DataConstr -> Bool # (/=) :: DataConstr -> DataConstr -> Bool # | |
Show DataConstr Source # | |
Defined in Base.Types showsPrec :: Int -> DataConstr -> ShowS # show :: DataConstr -> String # showList :: [DataConstr] -> ShowS # | |
Pretty DataConstr Source # | |
Defined in Base.PrettyTypes pPrint :: DataConstr -> Doc # pPrintPrec :: Int -> DataConstr -> Doc # pPrintList :: [DataConstr] -> Doc # |
constrIdent :: DataConstr -> Ident Source #
constrTypes :: DataConstr -> [Type] Source #
recLabels :: DataConstr -> [Ident] Source #
recLabelTypes :: DataConstr -> [Type] Source #
tupleData :: [DataConstr] Source #
Representation of class methods
data ClassMethod Source #
Instances
Eq ClassMethod Source # | |
Defined in Base.Types (==) :: ClassMethod -> ClassMethod -> Bool # (/=) :: ClassMethod -> ClassMethod -> Bool # | |
Show ClassMethod Source # | |
Defined in Base.Types showsPrec :: Int -> ClassMethod -> ShowS # show :: ClassMethod -> String # showList :: [ClassMethod] -> ShowS # | |
Pretty ClassMethod Source # | |
Defined in Base.PrettyTypes pPrint :: ClassMethod -> Doc # pPrintPrec :: Int -> ClassMethod -> Doc # pPrintList :: [ClassMethod] -> Doc # |
methodName :: ClassMethod -> Ident Source #
methodArity :: ClassMethod -> Maybe Int Source #
methodType :: ClassMethod -> PredType Source #
Representation of quantification
data TypeScheme Source #
Instances
Eq TypeScheme Source # | |
Defined in Base.Types (==) :: TypeScheme -> TypeScheme -> Bool # (/=) :: TypeScheme -> TypeScheme -> Bool # | |
Show TypeScheme Source # | |
Defined in Base.Types showsPrec :: Int -> TypeScheme -> ShowS # show :: TypeScheme -> String # showList :: [TypeScheme] -> ShowS # | |
Pretty TypeScheme Source # | |
Defined in Base.PrettyTypes pPrint :: TypeScheme -> Doc # pPrintPrec :: Int -> TypeScheme -> Doc # pPrintList :: [TypeScheme] -> Doc # | |
IsType TypeScheme Source # | |
Defined in Base.Types typeVars :: TypeScheme -> [Int] Source # | |
SubstType TypeScheme Source # | |
Defined in Base.TypeSubst subst :: TypeSubst -> TypeScheme -> TypeScheme Source # |
monoType :: Type -> TypeScheme Source #
polyType :: Type -> TypeScheme Source #
typeScheme :: PredType -> TypeScheme Source #
rawType :: TypeScheme -> Type Source #
Predefined types
stringType :: Type Source #
fractionalTypes :: [Type] Source #
predefTypes :: [(Type, [DataConstr])] Source #