language-Modula2-0.1: Parser, pretty-printer, and more for the Modula-2 programming language
Safe HaskellNone
LanguageHaskell2010

Language.Modula2.Grammar

Description

Modula-2 grammar adapted from ''Report on the Programming Language Modula-2''

Synopsis

Documentation

data Modula2Grammar l f p Source #

The names and types of all the Modula-2 grammar productions

Constructors

Modula2Grammar 

Fields

Instances

Instances details
Functor (Modula2Grammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.Grammar

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Modula2Grammar l f p -> Modula2Grammar l f q #

Foldable (Modula2Grammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.Grammar

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Modula2Grammar l f p -> m #

Traversable (Modula2Grammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.Grammar

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Modula2Grammar l f p -> m (Modula2Grammar l f q) #

sequence :: forall m (p :: k -> Type). Applicative m => Modula2Grammar l f (Compose m p) -> m (Modula2Grammar l f p) #

Apply (Modula2Grammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.Grammar

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Modula2Grammar l f (p ~> q) -> Modula2Grammar l f p -> Modula2Grammar l f q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Modula2Grammar l f p -> Modula2Grammar l f q -> Modula2Grammar l f r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Modula2Grammar l f p -> Modula2Grammar l f q -> Modula2Grammar l f r -> Modula2Grammar l f s #

Applicative (Modula2Grammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.Grammar

Methods

pure :: (forall (a :: k). f0 a) -> Modula2Grammar l f f0 #

Distributive (Modula2Grammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.Grammar

Methods

collect :: forall f1 a (f2 :: k -> Type). Functor f1 => (a -> Modula2Grammar l f f2) -> f1 a -> Modula2Grammar l f (Compose f1 f2) #

distribute :: forall f1 (f2 :: k -> Type). Functor f1 => f1 (Modula2Grammar l f f2) -> Modula2Grammar l f (Compose f1 f2) #

cotraverse :: Functor m => (forall (a :: k). m (p a) -> q a) -> m (Modula2Grammar l f p) -> Modula2Grammar l f q #

DistributiveTraversable (Modula2Grammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.Grammar

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Modula2Grammar l f f2) -> f1 a -> Modula2Grammar l f (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Modula2Grammar l f f2) -> Modula2Grammar l f (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f0 x) -> f1 (Modula2Grammar l f f2) -> Modula2Grammar l f f0 #

LexicalParsing (Parser (Modula2Grammar l f) Text) Source # 
Instance details

Defined in Language.Modula2.Grammar

LexicalParsing (Parser (ISOGrammar l) Text) Source # 
Instance details

Defined in Language.Modula2.ISO.Grammar

TokenParsing (Parser (Modula2Grammar l f) Text) Source # 
Instance details

Defined in Language.Modula2.Grammar

TokenParsing (Parser (ISOGrammar l) Text) Source # 
Instance details

Defined in Language.Modula2.ISO.Grammar

grammar :: forall l g. (Modula2 l, LexicalParsing (Parser g Text)) => GrammarBuilder (Modula2Grammar l NodeWrap) g Parser Text Source #

All the productions of Modula-2 grammar

moptional :: (Alternative f, Monoid (f a)) => f a -> f a Source #

data Lexeme #

Constructors

WhiteSpace 

Fields

Comment 

Fields

Token 

Instances

Instances details
Eq Lexeme 
Instance details

Defined in Language.Oberon.Grammar

Methods

(==) :: Lexeme -> Lexeme -> Bool #

(/=) :: Lexeme -> Lexeme -> Bool #

Data Lexeme 
Instance details

Defined in Language.Oberon.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lexeme -> c Lexeme #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lexeme #

toConstr :: Lexeme -> Constr #

dataTypeOf :: Lexeme -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Lexeme) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lexeme) #

gmapT :: (forall b. Data b => b -> b) -> Lexeme -> Lexeme #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lexeme -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lexeme -> r #

gmapQ :: (forall d. Data d => d -> u) -> Lexeme -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Lexeme -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lexeme -> m Lexeme #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lexeme -> m Lexeme #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lexeme -> m Lexeme #

Show Lexeme 
Instance details

Defined in Language.Oberon.Grammar

LexicalParsing (Parser (OberonGrammar l f) Text) 
Instance details

Defined in Language.Oberon.Grammar

LexicalParsing (Parser (Modula2Grammar l f) Text) Source # 
Instance details

Defined in Language.Modula2.Grammar

LexicalParsing (Parser (ISOGrammar l) Text) Source # 
Instance details

Defined in Language.Modula2.ISO.Grammar

TokenParsing (Parser (OberonGrammar l f) Text) 
Instance details

Defined in Language.Oberon.Grammar

TokenParsing (Parser (Modula2Grammar l f) Text) Source # 
Instance details

Defined in Language.Modula2.Grammar

TokenParsing (Parser (ISOGrammar l) Text) Source # 
Instance details

Defined in Language.Modula2.ISO.Grammar

newtype ParsedLexemes #

Constructors

Trailing [Lexeme] 

Instances

Instances details
Data ParsedLexemes 
Instance details

Defined in Language.Oberon.Grammar

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParsedLexemes -> c ParsedLexemes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParsedLexemes #

toConstr :: ParsedLexemes -> Constr #

dataTypeOf :: ParsedLexemes -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParsedLexemes) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParsedLexemes) #

gmapT :: (forall b. Data b => b -> b) -> ParsedLexemes -> ParsedLexemes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParsedLexemes -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParsedLexemes -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParsedLexemes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParsedLexemes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParsedLexemes -> m ParsedLexemes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParsedLexemes -> m ParsedLexemes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParsedLexemes -> m ParsedLexemes #

Show ParsedLexemes 
Instance details

Defined in Language.Oberon.Grammar

Semigroup ParsedLexemes 
Instance details

Defined in Language.Oberon.Grammar

Monoid ParsedLexemes 
Instance details

Defined in Language.Oberon.Grammar

(Ord (QualIdent l), v ~ Value l l Placed Placed) => SynthesizedField "designatorValue" (Maybe (Placed v)) (Auto ConstantFold) (Designator l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Proxy "designatorValue" -> Auto ConstantFold -> Placed (Designator l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Designator l l sem sem) -> Designator l l sem (Synthesized (Auto ConstantFold)) -> Maybe (Placed v) #

At Serialization (g Parsed Parsed) 
Instance details

Defined in Language.Oberon.Reserializer

Methods

($) :: Serialization -> Domain Serialization (g Parsed Parsed) -> Codomain Serialization (g Parsed Parsed) #

(Foldable (g (Const (Sum Int) :: Type -> Type)), Foldable (Fold Parsed (Sum Int)) g) => At PositionAdjustment (g Parsed Parsed) 
Instance details

Defined in Language.Oberon.Reserializer

Methods

($) :: PositionAdjustment -> Domain PositionAdjustment (g Parsed Parsed) -> Codomain PositionAdjustment (g Parsed Parsed) #

(Nameable l, k ~ QualIdent l, v ~ Value l l Placed Placed, Ord k, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l)) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Block l l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Nameable l, k ~ QualIdent l, v ~ Value l l Placed Placed, Ord k, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l)) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Block l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Nameable l, k ~ QualIdent l, v ~ Value l l Placed Placed, Ord k, Atts (Synthesized (Auto ConstantFold)) (ConstExpression l l Sem Sem) ~ SynCFExp l l) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Declaration l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Declaration l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Declaration l l sem sem) -> Declaration l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Modula2 l, Nameable l, k ~ QualIdent l, Ord k, v ~ Value l l Placed Placed, Export l ~ Export l, Value l ~ Value l, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Synthesized (Auto ConstantFold)) (Type l l Sem Sem) ~ SynCF' (Type l l), Atts (Synthesized (Auto ConstantFold)) (ProcedureHeading l l Sem Sem) ~ SynCF' (ProcedureHeading l l), Atts (Synthesized (Auto ConstantFold)) (FormalParameters l l Sem Sem) ~ SynCF' (FormalParameters l l), Atts (Synthesized (Auto ConstantFold)) (Block l l Sem Sem) ~ SynCFMod' l (Block l l), Atts (Synthesized (Auto ConstantFold)) (ConstExpression l l Sem Sem) ~ SynCFExp l l) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Declaration full l l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Declaration full l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Declaration full l l sem sem) -> Declaration full l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

Ord (QualIdent l) => Bequether (Auto ConstantFold) (Modules l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Ord (QualIdent l) => Synthesizer (Auto ConstantFold) (Modules l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Modules l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Modules l sem sem) -> Modules l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Modules l sem sem) #

(Nameable l, Ord (QualIdent l), Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Inherited (Auto ConstantFold)) (StatementSequence l l Sem Sem) ~ InhCF l, Atts (Inherited (Auto ConstantFold)) (Declaration l l Sem Sem) ~ InhCF l) => Bequether (Auto ConstantFold) (Block l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

bequest :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Block l l sem (Inherited (Auto ConstantFold)) #

(Nameable l, Ord (QualIdent l), Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Inherited (Auto ConstantFold)) (StatementSequence l l Sem Sem) ~ InhCF l, Atts (Inherited (Auto ConstantFold)) (Declaration l l Sem Sem) ~ InhCF l) => Bequether (Auto ConstantFold) (Block l l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

bequest :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Block l l sem (Inherited (Auto ConstantFold)) #

(Oberon l, Nameable l, Ord (QualIdent l), Show (QualIdent l), Atts (Synthesized (Auto ConstantFold)) (Block l l Sem Sem) ~ SynCFMod' l (Block l l)) => Synthesizer (Auto ConstantFold) (Module l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Module l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Module l l sem sem) -> Module l l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Module l l sem sem) #

(Oberon l, Nameable l, Ord (QualIdent l), Value l ~ Value l, InhCF l ~ InhCF λ, Pretty (Value λ λ Identity Identity), Atts (Synthesized (Auto ConstantFold)) (Expression l l Sem Sem) ~ SynCFExp l l, Atts (Synthesized (Auto ConstantFold)) (Element l l Sem Sem) ~ SynCF' (Element l l), Atts (Synthesized (Auto ConstantFold)) (Designator l l Sem Sem) ~ SynCFDesignator l) => Synthesizer (Auto ConstantFold) (Expression λ l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Expression λ l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Expression λ l sem sem) -> Expression λ l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Expression λ l sem sem) #

(Nameable l, Ord (QualIdent l), QualIdent l ~ QualIdent l, Value l ~ Value l, λ ~ Language, Coercible (QualIdent Language) (QualIdent l), Coercible (Value Language Language) (Value l l), InhCF l ~ InhCF λ, Pretty (Value l l Identity Identity), Atts (Synthesized (Auto ConstantFold)) (Expression l l Sem Sem) ~ SynCFExp l l, Atts (Synthesized (Auto ConstantFold)) (Element l l Sem Sem) ~ SynCF' (Element l l), Atts (Synthesized (Auto ConstantFold)) (Item l l Sem Sem) ~ SynCF' (Item l l), Atts (Synthesized (Auto ConstantFold)) (Designator l l Sem Sem) ~ SynCFDesignator l) => Synthesizer (Auto ConstantFold) (Expression λ l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> Type). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Expression λ l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Expression λ l sem sem) -> Expression λ l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Expression λ l sem sem) #

LexicalParsing (Parser (ISOGrammar l) Text) Source # 
Instance details

Defined in Language.Modula2.ISO.Grammar

TokenParsing (Parser (ISOGrammar l) Text) Source # 
Instance details

Defined in Language.Modula2.ISO.Grammar