- newtype TypeVar = TypeVar Int
- data TypeScheme = ForAll [(TypeVar, [Constraint])] Type
- data Constraint
- data Type
- data TypeVarRef = TypeVarRef TypeVar [Constraint] PType
- newtype IORefMaybe a = IORefMaybe (Maybe a)
- type SymbolTable = PartialFunction Name TypeScheme
- type PType = IORef (Maybe Type)
- type PSymbolTable = IORef SymbolTable
- readPType :: MonadIO m => PType -> m (Maybe Type)
- setPType :: MonadIO m => PType -> Type -> m ()
- freshPType :: MonadIO m => m PType
- readPSymbolTable :: MonadIO m => PSymbolTable -> m SymbolTable
- setPSymbolTable :: MonadIO m => PSymbolTable -> SymbolTable -> m ()
- freshPSymbolTable :: MonadIO m => m PSymbolTable
- prettyPrintTypes :: [Type] -> [Doc]
- prettyPrintType :: PartialFunction Int Char -> Type -> Doc
- collectConstraints :: Type -> [(TypeVar, [Constraint])]
Documentation
data TypeScheme Source
ForAll [(TypeVar, [Constraint])] Type |
data Constraint Source
TVar TypeVarRef | |
TProc | |
TInt | |
TBool | |
TEvent | |
TEventable | |
TSet Type | |
TSeq Type | |
TDot Type Type | |
TTuple [Type] | |
TFunction [Type] Type | |
TDotable Type Type | |
TDatatype Name |
newtype IORefMaybe a Source
IORefMaybe (Maybe a) |
type PSymbolTable = IORef SymbolTableSource
freshPType :: MonadIO m => m PTypeSource
readPSymbolTable :: MonadIO m => PSymbolTable -> m SymbolTableSource
setPSymbolTable :: MonadIO m => PSymbolTable -> SymbolTable -> m ()Source
freshPSymbolTable :: MonadIO m => m PSymbolTableSource
prettyPrintTypes :: [Type] -> [Doc]Source
Pretty prints several types using the same variable substitutions
prettyPrintType :: PartialFunction Int Char -> Type -> DocSource
collectConstraints :: Type -> [(TypeVar, [Constraint])]Source