language-oberon-0.3: Parser, pretty-printer, and more for the Oberon programming language
Safe HaskellNone
LanguageHaskell2010

Language.Oberon.Resolver

Description

This module exports functions for resolving the syntactic ambiguities in a parsed module. For example, an Oberon expression foo(bar) may be a call to function foo with a parameter bar, or it may be type guard on variable foo casting it to type bar.

Synopsis

Documentation

resolveModules :: forall l. (BindableDeclaration l, CoFormalParameters l, Wirthy l, Traversable (Resolution l) (Declaration l l), Traversable (Resolution l) (Type l l), Traversable (Resolution l) (ProcedureHeading l l), Traversable (Resolution l) (FormalParameters l l), Traversable (Resolution l) (Expression l l), Traversable (Resolution l) (Block l l), Traversable (Resolution l) (StatementSequence l l), Traversable (Resolution l) (Declaration l l), Traversable (Resolution l) (Type l l), Traversable (Resolution l) (ProcedureHeading l l), Traversable (Resolution l) (FormalParameters l l), Traversable (Resolution l) (Expression l l), Traversable (Resolution l) (Block l l), Traversable (Resolution l) (StatementSequence l l), Resolution l `At` Block l l NodeWrap NodeWrap) => Predefined l -> Map Ident (NodeWrap (Module l l NodeWrap NodeWrap)) -> Validation (NonEmpty (Ident, NonEmpty (Error l))) (Map Ident (Placed (Module l l Placed Placed))) Source #

Resolve ambiguities in the given collection of modules, a Map keyed by module name. The value for the first argument is typically predefined or predefined2. Note that all class constraints in the function's type signature are satisfied by the Oberon Language.

resolveModule :: forall l. (BindableDeclaration l, CoFormalParameters l, Traversable (Resolution l) (Block l l), Traversable (Resolution l) (Declaration l l), Traversable (Resolution l) (Type l l), Traversable (Resolution l) (FormalParameters l l), Traversable (Resolution l) (ConstExpression l l), Traversable (Resolution l) (StatementSequence l l), Traversable (Resolution l) (Declaration l l), Traversable (Resolution l) (Declaration l l), Traversable (Resolution l) (StatementSequence l l), Traversable (Resolution l) (Type l l), Traversable (Resolution l) (FormalParameters l l), Traversable (Resolution l) (ConstExpression l l), Resolution l `At` Block l l NodeWrap NodeWrap) => Scope l -> Map Ident (Validation (NonEmpty (Error l)) (Placed (Module l l Placed Placed))) -> NodeWrap (Module l l NodeWrap NodeWrap) -> Validation (NonEmpty (Error l)) (Placed (Module l l Placed Placed)) Source #

Resolve ambiguities in a single module. The value for the first argument is typically predefined or predefined2. The imports are resolved using the given map of already resolved modules. Note that all class constraints in the function's type signature are satisfied by the Oberon Language.

resolvePositions :: (p ~ NodeWrap, q ~ NodeWrap, Functor (Map p q) g) => Text -> p (g p p) -> q (g q q) Source #

Replace the stored positions in the entire ambiguous parsed tree, as obtained from Language.Oberon.Grammar, | with offsets from the start of the given source text

resolvePosition :: Text -> NodeWrap a -> NodeWrap a Source #

Replace the stored positions of the given node, as obtained from Language.Oberon.Grammar, with offset from the | start of the given source text

data Error l Source #

All possible resolution errors

Instances

Instances details
Monad (Validation (NonEmpty (Error l))) Source # 
Instance details

Defined in Language.Oberon.Resolver

Methods

(>>=) :: Validation (NonEmpty (Error l)) a -> (a -> Validation (NonEmpty (Error l)) b) -> Validation (NonEmpty (Error l)) b #

(>>) :: Validation (NonEmpty (Error l)) a -> Validation (NonEmpty (Error l)) b -> Validation (NonEmpty (Error l)) b #

return :: a -> Validation (NonEmpty (Error l)) a #

(Show (QualIdent l), Show (Declaration l l NodeWrap NodeWrap), Show (Statement l l NodeWrap NodeWrap), Show (Expression l l NodeWrap NodeWrap), Show (Expression l l NodeWrap NodeWrap), Show (Designator l l NodeWrap NodeWrap)) => Show (Error l) Source # 
Instance details

Defined in Language.Oberon.Resolver

Methods

showsPrec :: Int -> Error l -> ShowS #

show :: Error l -> String #

showList :: [Error l] -> ShowS #

type Predefined l = Scope l Source #

A set of predefined declarations.

type Placed = (,) (Int, ParsedLexemes, Int) Source #

The node wrapper in a fully resolved AST

type NodeWrap = Compose ((,) (Int, Int)) (Compose Ambiguous ((,) ParsedLexemes)) Source #

The node wrapper in an ambiguous, freshly parsed AST, only with Position replaced with an offset from the beginning of the source.

predefined :: Oberon l => Predefined l Source #

The set of Predefined types and procedures defined in the Oberon Language Report.

predefined2 :: Oberon l => Predefined l Source #

The set of Predefined types and procedures defined in the Oberon-2 Language Report.