Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Type checker for Oberon AST. The AST must have its ambiguities previously resolved by Language.Oberon.Resolver.
Synopsis
- checkModules :: forall l. (Oberon l, Nameable l, Ord (QualIdent l), Show (QualIdent l), Atts (Inherited (Auto TypeCheck)) (Block l l Sem Sem) ~ InhTC l, Atts (Synthesized (Auto TypeCheck)) (Block l l Sem Sem) ~ SynTCMod l, Functor (Auto TypeCheck) (Block l l)) => Environment l -> Map Ident (Placed (Module l l Placed Placed)) -> [Error Ident l]
- errorMessage :: (Nameable l, Oberon l, Show (QualIdent l)) => ErrorType l -> String
- data Error m l = Error {
- errorModule :: m
- errorPosition :: LexicalPosition
- errorType :: ErrorType l
- data ErrorType l
- = ArgumentCountMismatch Int Int
- | ExtraDimensionalIndex Int Int
- | IncomparableTypes (Type l) (Type l)
- | IncompatibleTypes (Type l) (Type l)
- | TooSmallArrayType Int Int
- | OpenArrayVariable
- | NonArrayType (Type l)
- | NonBooleanType (Type l)
- | NonFunctionType (Type l)
- | NonIntegerType (Type l)
- | NonNumericType (Type l)
- | NonPointerType (Type l)
- | NonProcedureType (Type l)
- | NonRecordType (Type l)
- | TypeMismatch (Type l) (Type l)
- | UnequalTypes (Type l) (Type l)
- | UnrealType (Type l)
- | UnknownName (QualIdent l)
- | UnknownField Ident (Type l)
- predefined :: (Wirthy l, Ord (QualIdent l)) => Environment l
- predefined2 :: (Wirthy l, Ord (QualIdent l)) => Environment l
Documentation
checkModules :: forall l. (Oberon l, Nameable l, Ord (QualIdent l), Show (QualIdent l), Atts (Inherited (Auto TypeCheck)) (Block l l Sem Sem) ~ InhTC l, Atts (Synthesized (Auto TypeCheck)) (Block l l Sem Sem) ~ SynTCMod l, Functor (Auto TypeCheck) (Block l l)) => Environment l -> Map Ident (Placed (Module l l Placed Placed)) -> [Error Ident l] Source #
Check if the given collection of modules is well typed and return all type errors found. The collection is a
Map
keyed by module name. The first argument's value is typically predefined
or predefined2
.
Error | |
|
ArgumentCountMismatch Int Int | |
ExtraDimensionalIndex Int Int | |
IncomparableTypes (Type l) (Type l) | |
IncompatibleTypes (Type l) (Type l) | |
TooSmallArrayType Int Int | |
OpenArrayVariable | |
NonArrayType (Type l) | |
NonBooleanType (Type l) | |
NonFunctionType (Type l) | |
NonIntegerType (Type l) | |
NonNumericType (Type l) | |
NonPointerType (Type l) | |
NonProcedureType (Type l) | |
NonRecordType (Type l) | |
TypeMismatch (Type l) (Type l) | |
UnequalTypes (Type l) (Type l) | |
UnrealType (Type l) | |
UnknownName (QualIdent l) | |
UnknownField Ident (Type l) |
predefined :: (Wirthy l, Ord (QualIdent l)) => Environment l Source #
The set of Predefined
types and procedures defined in the Oberon Language Report.
predefined2 :: (Wirthy l, Ord (QualIdent l)) => Environment l Source #
The set of Predefined
types and procedures defined in the Oberon-2 Language Report.
Orphan instances
Apply (Module l l f' :: (Type -> Type) -> Type) Source # | |
(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Module l l f' (p ~> q) -> Module l l f' p -> Module l l f' q # liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Module l l f' p -> Module l l f' q -> Module l l f' r # liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Module l l f' p -> Module l l f' q -> Module l l f' r -> Module l l f' s # |