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

Language.Modula2.ISO.AST

Description

ISO Modula-2 Abstract Syntax Tree definitions

Synopsis

Documentation

data Language Source #

Data type representing the Modula-2 language, as specified by the ISO standard.

Constructors

Language 

Instances

Instances details
Data Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

toConstr :: Language -> Constr #

dataTypeOf :: Language -> DataType #

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

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

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

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

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

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

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

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

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

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

Wirthy Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Associated Types

type Module Language = (m :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Declaration Language = (d :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Type Language = (t :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Statement Language = (s :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Expression Language = (e :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Designator Language = (d :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Value Language = (v :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type FieldList Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type ProcedureHeading Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type FormalParameters Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type FPSection Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Block Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type StatementSequence Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Case Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type CaseLabels Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type ConditionalBranch Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Element Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

type Import Language = (x :: Type) #

type IdentDef Language = (x :: Type) #

type QualIdent Language = (x :: Type) #

Methods

constantDeclaration :: forall l' f (f' :: Type -> Type). IdentDef l' -> f (ConstExpression l' l' f' f') -> Declaration Language l' f' f #

typeDeclaration :: forall l' f (f' :: Type -> Type). IdentDef l' -> f (Type l' l' f' f') -> Declaration Language l' f' f #

variableDeclaration :: forall l' f (f' :: Type -> Type). IdentList l' -> f (Type l' l' f' f') -> Declaration Language l' f' f #

procedureDeclaration :: forall f l' (f' :: Type -> Type). f (ProcedureHeading l' l' f' f') -> f (Block l' l' f' f') -> Declaration Language l' f' f #

formalParameters :: forall f l' (f' :: Type -> Type). [f (FPSection l' l' f' f')] -> Maybe (ReturnType l') -> FormalParameters Language l' f' f #

fpSection :: forall f l' (f' :: Type -> Type). Bool -> [Ident] -> f (Type l' l' f' f') -> FPSection Language l' f' f #

block :: forall f l' (f' :: Type -> Type). [f (Declaration l' l' f' f')] -> Maybe (f (StatementSequence l' l' f' f')) -> Block Language l' f' f #

fieldList :: forall l' f (f' :: Type -> Type). NonEmpty (IdentDef l') -> f (Type l' l' f' f') -> FieldList Language l' f' f #

pointerType :: forall f l' (f' :: Type -> Type). f (Type l' l' f' f') -> Type Language l' f' f #

procedureType :: forall f l' (f' :: Type -> Type). Maybe (f (FormalParameters l' l' f' f')) -> Type Language l' f' f #

typeReference :: forall l' (f' :: Type -> Type) (f :: Type -> Type). QualIdent l' -> Type Language l' f' f #

assignment :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> f (Expression l' l' f' f') -> Statement Language l' f' f #

caseStatement :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> [f (Case l' l' f' f')] -> Maybe (f (StatementSequence l' l' f' f')) -> Statement Language l' f' f #

emptyStatement :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Statement Language l' f' f #

exitStatement :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Statement Language l' f' f #

ifStatement :: forall f l' (f' :: Type -> Type). NonEmpty (f (ConditionalBranch l' l' f' f')) -> Maybe (f (StatementSequence l' l' f' f')) -> Statement Language l' f' f #

loopStatement :: forall f l' (f' :: Type -> Type). f (StatementSequence l' l' f' f') -> Statement Language l' f' f #

procedureCall :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> Maybe [f (Expression l' l' f' f')] -> Statement Language l' f' f #

repeatStatement :: forall f l' (f' :: Type -> Type). f (StatementSequence l' l' f' f') -> f (Expression l' l' f' f') -> Statement Language l' f' f #

returnStatement :: forall f l' (f' :: Type -> Type). Maybe (f (Expression l' l' f' f')) -> Statement Language l' f' f #

whileStatement :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (StatementSequence l' l' f' f') -> Statement Language l' f' f #

conditionalBranch :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (StatementSequence l' l' f' f') -> ConditionalBranch Language l' f' f #

caseAlternative :: forall f l' (f' :: Type -> Type). NonEmpty (f (CaseLabels l' l' f' f')) -> f (StatementSequence l' l' f' f') -> Case Language l' f' f #

singleLabel :: forall f l' (f' :: Type -> Type). f (ConstExpression l' l' f' f') -> CaseLabels Language l' f' f #

labelRange :: forall f l' (f' :: Type -> Type). f (ConstExpression l' l' f' f') -> f (ConstExpression l' l' f' f') -> CaseLabels Language l' f' f #

statementSequence :: forall f l' (f' :: Type -> Type). [f (Statement l' l' f' f')] -> StatementSequence Language l' f' f #

add :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

subtract :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

and :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

or :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

divide :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

integerDivide :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

modulo :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

multiply :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

functionCall :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> [f (Expression l' l' f' f')] -> Expression Language l' f' f #

literal :: forall f l' (f' :: Type -> Type). f (Value l' l' f' f') -> Expression Language l' f' f #

negative :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> Expression Language l' f' f #

positive :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> Expression Language l' f' f #

not :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> Expression Language l' f' f #

read :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> Expression Language l' f' f #

relation :: forall f l' (f' :: Type -> Type). RelOp -> f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f #

element :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> Element Language l' f' f #

range :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Element Language l' f' f #

integer :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Integer -> Value Language l' f' f #

nil :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Value Language l' f' f #

false :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Value Language l' f' f #

true :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Value Language l' f' f #

real :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Double -> Value Language l' f' f #

string :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Text -> Value Language l' f' f #

charCode :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Int -> Value Language l' f' f #

builtin :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Text -> Value Language l' f' f #

variable :: forall l' (f' :: Type -> Type) (f :: Type -> Type). QualIdent l' -> Designator Language l' f' f #

field :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> Ident -> Designator Language l' f' f #

index :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> NonEmpty (f (Expression l' l' f' f')) -> Designator Language l' f' f #

dereference :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> Designator Language l' f' f #

identDef :: Ident -> IdentDef Language #

nonQualIdent :: Ident -> QualIdent Language #

CoWirthy Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Associated Types

type TargetClass Language :: Type -> Constraint #

Methods

coDeclaration :: forall l' l'' (f' :: Type -> Type) (f :: Type -> Type). TargetClass Language l' => Declaration Language l'' f' f -> Declaration l' l'' f' f #

coType :: forall l' l'' (f' :: Type -> Type) (f :: Type -> Type). TargetClass Language l' => Type Language l'' f' f -> Type l' l'' f' f #

coStatement :: forall l' l'' (f' :: Type -> Type) (f :: Type -> Type). TargetClass Language l' => Statement Language l'' f' f -> Statement l' l'' f' f #

coExpression :: forall l' l'' (f' :: Type -> Type) (f :: Type -> Type). TargetClass Language l' => Expression Language l'' f' f -> Expression l' l'' f' f #

coDesignator :: forall l' l'' (f' :: Type -> Type) (f :: Type -> Type). TargetClass Language l' => Designator Language l'' f' f -> Designator l' l'' f' f #

coValue :: forall l' l'' (f' :: Type -> Type) (f :: Type -> Type). TargetClass Language l' => Value Language l'' f' f -> Value l' l'' f' f #

Nameable Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Oberon Language Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

Associated Types

type WithAlternative Language = (x :: Type -> (Type -> Type) -> (Type -> Type) -> Type) #

Methods

moduleUnit :: forall f l' (f' :: Type -> Type). Ident -> [Import Language] -> f (Block l' l' f' f') -> Module Language l' f' f #

moduleImport :: Maybe Ident -> Ident -> Import Language #

qualIdent :: Ident -> Ident -> QualIdent Language #

getQualIdentNames :: QualIdent Language -> Maybe (Ident, Ident) #

exported :: Ident -> IdentDef Language #

forwardDeclaration :: forall l' f (f' :: Type -> Type). IdentDef l' -> Maybe (f (FormalParameters l' l' f' f')) -> Declaration Language l' f' f #

procedureHeading :: forall l' f (f' :: Type -> Type). Bool -> IdentDef l' -> Maybe (f (FormalParameters l' l' f' f')) -> ProcedureHeading Language l' f' f #

arrayType :: forall f l' (f' :: Type -> Type). [f (ConstExpression l' l' f' f')] -> f (Type l' l' f' f') -> Type Language l' f' f #

recordType :: forall l' f (f' :: Type -> Type). Maybe (BaseType l') -> [f (FieldList l' l' f' f')] -> Type Language l' f' f #

withStatement :: forall f l' (f' :: Type -> Type). f (WithAlternative l' l' f' f') -> Statement Language l' f' f #

withAlternative :: forall l' f (f' :: Type -> Type). QualIdent l' -> QualIdent l' -> f (StatementSequence l' l' f' f') -> WithAlternative Language l' f' f #

is :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> QualIdent l' -> Expression Language l' f' f #

set :: forall f l' (f' :: Type -> Type). [f (Element l' l' f' f')] -> Expression Language l' f' f #

typeGuard :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> QualIdent l' -> Designator Language l' f' f #

Modula2 Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Associated Types

type Export Language = (x :: Type) Source #

type Definition Language = (d :: Type -> (Type -> Type) -> (Type -> Type) -> Type) Source #

type Variant Language = (v :: Type -> (Type -> Type) -> (Type -> Type) -> Type) Source #

Methods

definitionModule :: forall l' f (f' :: Type -> Type). Ident -> [Import l'] -> Maybe (Export l') -> [f (Definition l' l' f' f')] -> Module Language l' f' f Source #

implementationModule :: forall f l' (f' :: Type -> Type). Ident -> Maybe (f (Priority l' l' f' f')) -> [Import l'] -> f (Block l' l' f' f') -> Module Language l' f' f Source #

programModule :: forall f l' (f' :: Type -> Type). Ident -> Maybe (f (Priority l' l' f' f')) -> [Import l'] -> f (Block l' l' f' f') -> Module Language l' f' f Source #

moduleExport :: Bool -> NonEmpty Ident -> Export Language Source #

moduleImport :: Maybe Ident -> NonEmpty Ident -> Import Language Source #

constantDefinition :: forall l' f (f' :: Type -> Type). IdentDef l' -> f (ConstExpression l' l' f' f') -> Definition Language l' f' f Source #

typeDefinition :: forall l' f (f' :: Type -> Type). IdentDef l' -> Maybe (f (Type l' l' f' f')) -> Definition Language l' f' f Source #

variableDefinition :: forall l' f (f' :: Type -> Type). IdentList l' -> f (Type l' l' f' f') -> Definition Language l' f' f Source #

procedureDefinition :: forall f l' (f' :: Type -> Type). f (ProcedureHeading l' l' f' f') -> Definition Language l' f' f Source #

moduleDeclaration :: forall f l' (f' :: Type -> Type). Ident -> Maybe (f (Priority l' l' f' f')) -> [Import l'] -> Maybe (Export l') -> f (Block l' l' f' f') -> Declaration Language l' f' f Source #

procedureHeading :: forall f l' (f' :: Type -> Type). Ident -> Maybe (f (FormalParameters l' l' f' f')) -> ProcedureHeading Language l' f' f Source #

caseFieldList :: forall l' f (f' :: Type -> Type). Maybe Ident -> QualIdent l' -> NonEmpty (f (Variant l' l' f' f')) -> [f (FieldList l' l' f' f')] -> FieldList Language l' f' f Source #

variant :: forall f l' (f' :: Type -> Type). NonEmpty (f (CaseLabels l' l' f' f')) -> [f (FieldList l' l' f' f')] -> Variant Language l' f' f Source #

enumeration :: forall l' (f' :: Type -> Type) (f :: Type -> Type). IdentList l' -> Type Language l' f' f Source #

subRange :: forall l' f (f' :: Type -> Type). Maybe (QualIdent l') -> f (ConstExpression l' l' f' f') -> f (ConstExpression l' l' f' f') -> Type Language l' f' f Source #

arrayType :: forall f l' (f' :: Type -> Type). [f (Type l' l' f' f')] -> f (Type l' l' f' f') -> Type Language l' f' f Source #

setType :: forall f l' (f' :: Type -> Type). f (Type l' l' f' f') -> Type Language l' f' f Source #

recordType :: forall f l' (f' :: Type -> Type). [f (FieldList l' l' f' f')] -> Type Language l' f' f Source #

withStatement :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> f (StatementSequence l' l' f' f') -> Statement Language l' f' f Source #

forStatement :: forall f l' (f' :: Type -> Type). Ident -> f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Maybe (f (Expression l' l' f' f')) -> f (StatementSequence l' l' f' f') -> Statement Language l' f' f Source #

set :: forall l' f (f' :: Type -> Type). Maybe (QualIdent l') -> [f (Element l' l' f' f')] -> Expression Language l' f' f Source #

qualIdent :: [Ident] -> Ident -> QualIdent Language Source #

Modula2 Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Associated Types

type AddressedIdent Language = (d :: Type -> (Type -> Type) -> (Type -> Type) -> Type) Source #

type Item Language = (i :: Type -> (Type -> Type) -> (Type -> Type) -> Type) Source #

Methods

emptyVariant :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Variant Language l' f' f Source #

addressedVariableDeclaration :: forall f l' (f' :: Type -> Type). NonEmpty (f (AddressedIdent l' l' f' f')) -> f (Type l' l' f' f') -> Declaration Language l' f' f Source #

forwardProcedureDeclaration :: forall f l' (f' :: Type -> Type). f (ProcedureHeading l' l' f' f') -> Declaration Language l' f' f Source #

exceptionHandlingBlock :: forall f l' (f' :: Type -> Type). [f (Declaration l' l' f' f')] -> Maybe (f (StatementSequence l' l' f' f')) -> Maybe (f (StatementSequence l' l' f' f')) -> Maybe (f (StatementSequence l' l' f' f')) -> Block Language l' f' f Source #

addressedIdent :: forall f l' (f' :: Type -> Type). Ident -> f (ConstExpression l' l' f' f') -> AddressedIdent Language l' f' f Source #

unaddressedIdent :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Ident -> AddressedIdent Language l' f' f Source #

packedSetType :: forall f l' (f' :: Type -> Type). f (Type l' l' f' f') -> Type Language l' f' f Source #

retryStatement :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Statement Language l' f' f Source #

array :: forall l' f (f' :: Type -> Type). Maybe (QualIdent l') -> [f (Item l' l' f' f')] -> Expression Language l' f' f Source #

record :: forall l' f (f' :: Type -> Type). Maybe (QualIdent l') -> [f (Expression l' l' f' f')] -> Expression Language l' f' f Source #

remainder :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression Language l' f' f Source #

single :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> Item Language l' f' f Source #

repeated :: forall f l' (f' :: Type -> Type). f (Expression l' l' f' f') -> f (ConstExpression l' l' f' f') -> Item Language l' f' f Source #

(Pretty (Precedence (Expression l l Identity Identity)), Pretty (Expression l l Identity Identity), Pretty (Value l l Identity Identity), Pretty (Element l l Identity Identity), Pretty (Item l l Identity Identity), Pretty (Designator l l Identity Identity), Pretty (QualIdent l)) => Pretty (Precedence (Expression Language l Identity Identity)) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

Pretty (Value l l Identity Identity) => Pretty (Value Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Pretty (IdentDef l), Pretty (QualIdent l), Pretty (Type l l Identity Identity), Pretty (Value l l Identity Identity), Pretty (FieldList l l Identity Identity), Pretty (Variant l l Identity Identity)) => Pretty (FieldList Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Pretty (QualIdent l), Pretty (Designator l l Identity Identity), Pretty (Expression l l Identity Identity)) => Pretty (Designator Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Pretty (ConstExpression l l Identity Identity), Pretty (Designator l l Identity Identity), Pretty (Case l l Identity Identity), Pretty (ConditionalBranch l l Identity Identity), Pretty (WithAlternative l l Identity Identity), Pretty (StatementSequence l l Identity Identity)) => Pretty (Statement Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

Pretty (Expression l l Identity Identity) => Pretty (Item Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Pretty (Precedence (Expression l l Identity Identity)), Pretty (Expression l l Identity Identity), Pretty (Value l l Identity Identity), Pretty (Element l l Identity Identity), Pretty (Item l l Identity Identity), Pretty (Designator l l Identity Identity), Pretty (QualIdent l)) => Pretty (Expression Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Pretty (IdentDef l), Pretty (FormalParameters l l Identity Identity), Pretty (FieldList l l Identity Identity), Pretty (ConstExpression l l Identity Identity), Pretty (Type l l Identity Identity), Pretty (BaseType l)) => Pretty (Type Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Nameable l, Pretty (IdentDef l), Pretty (Export l), Pretty (Import l), Pretty (Type l l Identity Identity), Pretty (Declaration l l Identity Identity), Pretty (Expression l l Identity Identity), Pretty (FormalParameters l l Identity Identity), Pretty (ProcedureHeading l l Identity Identity), Pretty (Block l l Identity Identity)) => Pretty (Declaration 'False Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Nameable l, Pretty (IdentDef l), Pretty (Export l), Pretty (Import l), Pretty (AddressedIdent l l Identity Identity), Pretty (Type l l Identity Identity), Pretty (Declaration l l Identity Identity), Pretty (Expression l l Identity Identity), Pretty (FormalParameters l l Identity Identity), Pretty (ProcedureHeading l l Identity Identity), Pretty (Block l l Identity Identity)) => Pretty (Declaration 'True Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type QualIdent Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type IdentDef Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Import Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Element Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type ConditionalBranch Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type CaseLabels Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Case Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type StatementSequence Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Block Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type FPSection Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type FormalParameters Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type ProcedureHeading Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type FieldList Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Value Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Designator Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Expression Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Statement Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Type Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Declaration Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Module Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type TargetClass Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type WithAlternative Language Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type Export Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Definition Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Variant Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type AddressedIdent Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

type Item Language Source # 
Instance details

Defined in Language.Modula2.ISO.AST

data Declaration (full :: Bool) λ l (f' :: * -> *) (f :: * -> *) where Source #

Constructors

ConstantDeclaration :: IdentDef l -> f (ConstExpression l l f' f') -> Declaration x λ l f' f 
TypeDeclaration :: IdentDef l -> f (Type l l f' f') -> Declaration x λ l f' f 
OpaqueTypeDeclaration :: IdentDef l -> Declaration False λ l f' f 
VariableDeclaration :: IdentList l -> f (Type l l f' f') -> Declaration x λ l f' f 
AddressedVariableDeclaration :: f (AddressedIdent l l f' f') -> ZipList (f (AddressedIdent l l f' f')) -> f (Type l l f' f') -> Declaration True λ l f' f 
ProcedureDeclaration :: f (ProcedureHeading l l f' f') -> f (Block l l f' f') -> Declaration True λ l f' f 
ProcedureDefinition :: f (ProcedureHeading l l f' f') -> Declaration False λ l f' f 
ForwardProcedureDeclaration :: f (ProcedureHeading l l f' f') -> Declaration True λ l f' f 
ModuleDeclaration :: Ident -> Maybe (f (Priority l l f' f')) -> [Import l] -> Maybe (Export l) -> f (Block l l f' f') -> Declaration True λ l f' f 

Instances

Instances details
(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) #

(Transformation t, Functor t (ConstExpression l l), Functor t (Type l l), Functor t (Type l l), Functor t (AddressedIdent l l), Functor t (AddressedIdent l l), Functor t (Type l l), Functor t (ProcedureHeading l l), Functor t (Block l l), Functor t (ProcedureHeading l l), Functor t (ProcedureHeading l l), Functor t (Priority l l), Functor t (Block l l)) => Functor t (Declaration full λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Declaration full λ l (Domain t) (Domain t) -> Declaration full λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (ConstExpression l l), Foldable t (Type l l), Foldable t (Type l l), Foldable t (AddressedIdent l l), Foldable t (AddressedIdent l l), Foldable t (Type l l), Foldable t (ProcedureHeading l l), Foldable t (Block l l), Foldable t (ProcedureHeading l l), Foldable t (ProcedureHeading l l), Foldable t (Priority l l), Foldable t (Block l l)) => Foldable t (Declaration full λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Declaration full λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (ConstExpression l l), Traversable t (Type l l), Traversable t (Type l l), Traversable t (AddressedIdent l l), Traversable t (AddressedIdent l l), Traversable t (Type l l), Traversable t (ProcedureHeading l l), Traversable t (Block l l), Traversable t (ProcedureHeading l l), Traversable t (ProcedureHeading l l), Traversable t (Priority l l), Traversable t (Block l l)) => Traversable t (Declaration full λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Declaration full λ l (Domain t) (Domain t) -> m (Declaration full λ l f f) #

(Transformation t, At t (ConstExpression l l f' f'), At t (Type l l f' f'), At t (Type l l f' f'), At t (AddressedIdent l l f' f'), At t (AddressedIdent l l f' f'), At t (Type l l f' f'), At t (ProcedureHeading l l f' f'), At t (Block l l f' f'), At t (ProcedureHeading l l f' f'), At t (ProcedureHeading l l f' f'), At t (Priority l l f' f'), At t (Block l l f' f')) => Functor t (Declaration full λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Declaration full λ l f' (Domain t) -> Declaration full λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (ConstExpression l l f' f'), At t (Type l l f' f'), At t (Type l l f' f'), At t (AddressedIdent l l f' f'), At t (AddressedIdent l l f' f'), At t (Type l l f' f'), At t (ProcedureHeading l l f' f'), At t (Block l l f' f'), At t (ProcedureHeading l l f' f'), At t (ProcedureHeading l l f' f'), At t (Priority l l f' f'), At t (Block l l f' f')) => Foldable t (Declaration full λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Declaration full λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (ConstExpression l l f' f'), At t (Type l l f' f'), At t (Type l l f' f'), At t (AddressedIdent l l f' f'), At t (AddressedIdent l l f' f'), At t (Type l l f' f'), At t (ProcedureHeading l l f' f'), At t (Block l l f' f'), At t (ProcedureHeading l l f' f'), At t (ProcedureHeading l l f' f'), At t (Priority l l f' f'), At t (Block l l f' f')) => Traversable t (Declaration full λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Declaration full λ l f' (Domain t) -> m (Declaration full λ l f' f) #

(Functor (Auto ConstantFold) (Declaration full l l), At (Auto ConstantFold) (Declaration full l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (Declaration full l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Functor (Declaration full λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Declaration full λ l f' p -> Declaration full λ l f' q #

Foldable (Declaration full λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Declaration full λ l f' p -> m #

Traversable (Declaration full λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Declaration full λ l f' p -> m (Declaration full λ l f' q) #

sequence :: forall m (p :: k -> Type). Applicative m => Declaration full λ l f' (Compose m p) -> m (Declaration full λ l f' p) #

Apply (Declaration full λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Declaration full λ l f' (p ~> q) -> Declaration full λ l f' p -> Declaration full λ l f' q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Declaration full λ l f' p -> Declaration full λ l f' q -> Declaration full λ l f' r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Declaration full λ l f' p -> Declaration full λ l f' q -> Declaration full λ l f' r -> Declaration full λ l f' s #

Attribution (Auto ConstantFold) (Declaration full l l) Sem Placed => At (Auto ConstantFold) (Declaration full l l Sem Sem) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(Show (Export l), Show (Import l), Show (f (AddressedIdent l l f' f')), Show (f (Type l l f' f')), Show (f (ConstExpression l l f' f')), Show (f (FormalParameters l l f' f')), Show (f (ProcedureHeading l l f' f')), Show (f (Block l l f' f')), Show (f (Block l l f' f')), Show (IdentDef l)) => Show (Declaration x λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> Declaration x λ l f' f -> ShowS #

show :: Declaration x λ l f' f -> String #

showList :: [Declaration x λ l f' f] -> ShowS #

(Nameable l, Pretty (IdentDef l), Pretty (Export l), Pretty (Import l), Pretty (Type l l Identity Identity), Pretty (Declaration l l Identity Identity), Pretty (Expression l l Identity Identity), Pretty (FormalParameters l l Identity Identity), Pretty (ProcedureHeading l l Identity Identity), Pretty (Block l l Identity Identity)) => Pretty (Declaration 'False Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Nameable l, Pretty (IdentDef l), Pretty (Export l), Pretty (Import l), Pretty (AddressedIdent l l Identity Identity), Pretty (Type l l Identity Identity), Pretty (Declaration l l Identity Identity), Pretty (Expression l l Identity Identity), Pretty (FormalParameters l l Identity Identity), Pretty (ProcedureHeading l l Identity Identity), Pretty (Block l l Identity Identity)) => Pretty (Declaration 'True Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type Atts (Inherited (Auto ConstantFold)) (Declaration full λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (Declaration full λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (Declaration full λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized (Auto ConstantFold)) (Declaration full λ l _1 _2) = SynCFMod' l (Declaration full l l)

data AddressedIdent λ l f' f Source #

Instances

Instances details
(Transformation t, Functor t (ConstExpression l l)) => Functor t (AddressedIdent λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> AddressedIdent λ l (Domain t) (Domain t) -> AddressedIdent λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (ConstExpression l l)) => Foldable t (AddressedIdent λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> AddressedIdent λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (ConstExpression l l)) => Traversable t (AddressedIdent λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> AddressedIdent λ l (Domain t) (Domain t) -> m (AddressedIdent λ l f f) #

(Transformation t, At t (ConstExpression l l f' f')) => Functor t (AddressedIdent λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> AddressedIdent λ l f' (Domain t) -> AddressedIdent λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (ConstExpression l l f' f')) => Foldable t (AddressedIdent λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> AddressedIdent λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (ConstExpression l l f' f')) => Traversable t (AddressedIdent λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> AddressedIdent λ l f' (Domain t) -> m (AddressedIdent λ l f' f) #

(Functor (Auto ConstantFold) (AddressedIdent l l), At (Auto ConstantFold) (AddressedIdent l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (AddressedIdent l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Functor (AddressedIdent λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Foldable (AddressedIdent λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Traversable (AddressedIdent λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

Apply (AddressedIdent λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Attribution (Auto ConstantFold) (AddressedIdent l l) Sem Placed => At (Auto ConstantFold) (AddressedIdent l l (Semantics (Auto ConstantFold)) (Semantics (Auto ConstantFold))) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (f (ConstExpression l l f' f'))) => Data (AddressedIdent λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddressedIdent λ l f' f -> c (AddressedIdent λ l f' f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AddressedIdent λ l f' f) #

toConstr :: AddressedIdent λ l f' f -> Constr #

dataTypeOf :: AddressedIdent λ l f' f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AddressedIdent λ l f' f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AddressedIdent λ l f' f)) #

gmapT :: (forall b. Data b => b -> b) -> AddressedIdent λ l f' f -> AddressedIdent λ l f' f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddressedIdent λ l f' f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddressedIdent λ l f' f -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddressedIdent λ l f' f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddressedIdent λ l f' f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddressedIdent λ l f' f -> m (AddressedIdent λ l f' f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressedIdent λ l f' f -> m (AddressedIdent λ l f' f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressedIdent λ l f' f -> m (AddressedIdent λ l f' f) #

Show (f (ConstExpression l l f' f')) => Show (AddressedIdent λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> AddressedIdent λ l f' f -> ShowS #

show :: AddressedIdent λ l f' f -> String #

showList :: [AddressedIdent λ l f' f] -> ShowS #

Pretty (ConstExpression l l Identity Identity) => Pretty (AddressedIdent l l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type Atts (Inherited (Auto ConstantFold)) (AddressedIdent λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (AddressedIdent λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (AddressedIdent λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

data Type λ l f' f Source #

Constructors

TypeReference (QualIdent l) 
ArrayType (ZipList (f (Type l l f' f'))) (f (Type l l f' f')) 
EnumerationType (IdentList l) 
SubrangeType (Maybe (QualIdent l)) (f (ConstExpression l l f' f')) (f (ConstExpression l l f' f')) 
SetType (f (Type l l f' f')) 
PackedSetType (f (Type l l f' f')) 
RecordType (ZipList (f (FieldList l l f' f'))) 
PointerType (f (Type l l f' f')) 
ProcedureType (Maybe (f (FormalParameters l l f' f'))) 

Instances

Instances details
(Transformation t, Functor t (Type l l), Functor t (Type l l), Functor t (ConstExpression l l), Functor t (ConstExpression l l), Functor t (Type l l), Functor t (Type l l), Functor t (FieldList l l), Functor t (Type l l), Functor t (FormalParameters l l)) => Functor t (Type λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Type λ l (Domain t) (Domain t) -> Type λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (Type l l), Foldable t (Type l l), Foldable t (ConstExpression l l), Foldable t (ConstExpression l l), Foldable t (Type l l), Foldable t (Type l l), Foldable t (FieldList l l), Foldable t (Type l l), Foldable t (FormalParameters l l)) => Foldable t (Type λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Type λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (Type l l), Traversable t (Type l l), Traversable t (ConstExpression l l), Traversable t (ConstExpression l l), Traversable t (Type l l), Traversable t (Type l l), Traversable t (FieldList l l), Traversable t (Type l l), Traversable t (FormalParameters l l)) => Traversable t (Type λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type0 -> Type0). Codomain t ~ Compose m f => t -> Type λ l (Domain t) (Domain t) -> m (Type λ l f f) #

(Transformation t, At t (Type l l f' f'), At t (Type l l f' f'), At t (ConstExpression l l f' f'), At t (ConstExpression l l f' f'), At t (Type l l f' f'), At t (Type l l f' f'), At t (FieldList l l f' f'), At t (Type l l f' f'), At t (FormalParameters l l f' f')) => Functor t (Type λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Type λ l f' (Domain t) -> Type λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (Type l l f' f'), At t (Type l l f' f'), At t (ConstExpression l l f' f'), At t (ConstExpression l l f' f'), At t (Type l l f' f'), At t (Type l l f' f'), At t (FieldList l l f' f'), At t (Type l l f' f'), At t (FormalParameters l l f' f')) => Foldable t (Type λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Type λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (Type l l f' f'), At t (Type l l f' f'), At t (ConstExpression l l f' f'), At t (ConstExpression l l f' f'), At t (Type l l f' f'), At t (Type l l f' f'), At t (FieldList l l f' f'), At t (Type l l f' f'), At t (FormalParameters l l f' f')) => Traversable t (Type λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type0 -> Type0). Codomain t ~ Compose m f => t -> Type λ l f' (Domain t) -> m (Type λ l f' f) #

(Functor (Auto ConstantFold) (Type l l), At (Auto ConstantFold) (Type l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (Type l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Functor (Type λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

Defined in Language.Modula2.ISO.AST

Methods

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

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

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Attribution (Auto ConstantFold) (Type l l) Sem Placed => At (Auto ConstantFold) (Type l l (Semantics (Auto ConstantFold)) (Semantics (Auto ConstantFold))) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (QualIdent l), Data (IdentList l), Data (f (Type l l f' f')), Data (f (ConstExpression l l f' f')), Data (f (FormalParameters l l f' f')), Data (f (FieldList l l f' f'))) => Data (Type λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type λ l f' f -> c (Type λ l f' f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Type λ l f' f) #

toConstr :: Type λ l f' f -> Constr #

dataTypeOf :: Type λ l f' f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Type λ l f' f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Type λ l f' f)) #

gmapT :: (forall b. Data b => b -> b) -> Type λ l f' f -> Type λ l f' f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type λ l f' f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type λ l f' f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Type λ l f' f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type λ l f' f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type λ l f' f -> m (Type λ l f' f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type λ l f' f -> m (Type λ l f' f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type λ l f' f -> m (Type λ l f' f) #

(Show (QualIdent l), Show (IdentList l), Show (f (Type l l f' f')), Show (f (ConstExpression l l f' f')), Show (f (FormalParameters l l f' f')), Show (f (FieldList l l f' f'))) => Show (Type λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> Type λ l f' f -> ShowS #

show :: Type λ l f' f -> String #

showList :: [Type λ l f' f] -> ShowS #

(Pretty (IdentDef l), Pretty (FormalParameters l l Identity Identity), Pretty (FieldList l l Identity Identity), Pretty (ConstExpression l l Identity Identity), Pretty (Type l l Identity Identity), Pretty (BaseType l)) => Pretty (Type Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type Atts (Inherited (Auto ConstantFold)) (Type λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (Type λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (Type λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized (Auto ConstantFold)) (Type λ l _1 _2) = SynCF' (Type l l)

data Expression λ l f' f Source #

Constructors

Relation RelOp (f (Expression l l f' f')) (f (Expression l l f' f')) 
Positive (f (Expression l l f' f')) 
Negative (f (Expression l l f' f')) 
Add (f (Expression l l f' f')) (f (Expression l l f' f')) 
Subtract (f (Expression l l f' f')) (f (Expression l l f' f')) 
Or (f (Expression l l f' f')) (f (Expression l l f' f')) 
Multiply (f (Expression l l f' f')) (f (Expression l l f' f')) 
Divide (f (Expression l l f' f')) (f (Expression l l f' f')) 
IntegerDivide (f (Expression l l f' f')) (f (Expression l l f' f')) 
Modulo (f (Expression l l f' f')) (f (Expression l l f' f')) 
Remainder (f (Expression l l f' f')) (f (Expression l l f' f')) 
And (f (Expression l l f' f')) (f (Expression l l f' f')) 
Array (Maybe (QualIdent l)) [f (Item l l f' f')] 
Record (Maybe (QualIdent l)) [f (Expression l l f' f')] 
Set (Maybe (QualIdent l)) (ZipList (f (Element l l f' f'))) 
Read (f (Designator l l f' f')) 
FunctionCall (f (Designator l l f' f')) (ZipList (f (Expression l l f' f'))) 
Not (f (Expression l l f' f')) 
Literal (f (Value l l f' f')) 

Instances

Instances details
(Transformation t, Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Item l l), Functor t (Expression l l), Functor t (Element l l), Functor t (Designator l l), Functor t (Designator l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Value l l)) => Functor t (Expression λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Expression λ l (Domain t) (Domain t) -> Expression λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Item l l), Foldable t (Expression l l), Foldable t (Element l l), Foldable t (Designator l l), Foldable t (Designator l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Value l l)) => Foldable t (Expression λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Expression λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Item l l), Traversable t (Expression l l), Traversable t (Element l l), Traversable t (Designator l l), Traversable t (Designator l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Value l l)) => Traversable t (Expression λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Expression λ l (Domain t) (Domain t) -> m (Expression λ l f f) #

(Transformation t, At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Item l l f' f'), At t (Expression l l f' f'), At t (Element l l f' f'), At t (Designator l l f' f'), At t (Designator l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Value l l f' f')) => Functor t (Expression λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Expression λ l f' (Domain t) -> Expression λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Item l l f' f'), At t (Expression l l f' f'), At t (Element l l f' f'), At t (Designator l l f' f'), At t (Designator l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Value l l f' f')) => Foldable t (Expression λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Expression λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Item l l f' f'), At t (Expression l l f' f'), At t (Element l l f' f'), At t (Designator l l f' f'), At t (Designator l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Value l l f' f')) => Traversable t (Expression λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Expression λ l f' (Domain t) -> m (Expression λ l f' f) #

(Pretty (Precedence (Expression l l Identity Identity)), Pretty (Expression l l Identity Identity), Pretty (Value l l Identity Identity), Pretty (Element l l Identity Identity), Pretty (Item l l Identity Identity), Pretty (Designator l l Identity Identity), Pretty (QualIdent l)) => Pretty (Precedence (Expression Language l Identity Identity)) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

(Functor (Auto ConstantFold) (Expression l l), At (Auto ConstantFold) (Expression l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (Expression l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(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) #

Functor (Expression λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Foldable (Expression λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Traversable (Expression λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

Apply (Expression λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Attribution (Auto ConstantFold) (Expression l l) Sem Placed => At (Auto ConstantFold) (Expression l l (Semantics (Auto ConstantFold)) (Semantics (Auto ConstantFold))) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(Eq (QualIdent l), Eq (f (Designator l l f' f')), Eq (f (Element l l f' f')), Eq (f (Item l l f' f')), Eq (f (Value l l f' f')), Eq (f (Expression l l f' f'))) => Eq (Expression λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(==) :: Expression λ l f' f -> Expression λ l f' f -> Bool #

(/=) :: Expression λ l f' f -> Expression λ l f' f -> Bool #

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (QualIdent l), Data (f (Designator l l f' f')), Data (f (Element l l f' f')), Data (f (Item l l f' f')), Data (f (Value l l f' f')), Data (f (Expression l l f' f'))) => Data (Expression λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expression λ l f' f -> c (Expression λ l f' f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Expression λ l f' f) #

toConstr :: Expression λ l f' f -> Constr #

dataTypeOf :: Expression λ l f' f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Expression λ l f' f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Expression λ l f' f)) #

gmapT :: (forall b. Data b => b -> b) -> Expression λ l f' f -> Expression λ l f' f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expression λ l f' f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expression λ l f' f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expression λ l f' f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expression λ l f' f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expression λ l f' f -> m (Expression λ l f' f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expression λ l f' f -> m (Expression λ l f' f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expression λ l f' f -> m (Expression λ l f' f) #

(Show (QualIdent l), Show (f (Designator l l f' f')), Show (f (Element l l f' f')), Show (f (Item l l f' f')), Show (f (Value l l f' f')), Show (f (Expression l l f' f'))) => Show (Expression λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> Expression λ l f' f -> ShowS #

show :: Expression λ l f' f -> String #

showList :: [Expression λ l f' f] -> ShowS #

(Pretty (Precedence (Expression l l Identity Identity)), Pretty (Expression l l Identity Identity), Pretty (Value l l Identity Identity), Pretty (Element l l Identity Identity), Pretty (Item l l Identity Identity), Pretty (Designator l l Identity Identity), Pretty (QualIdent l)) => Pretty (Expression Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type Atts (Inherited (Auto ConstantFold)) (Expression λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (Expression λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (Expression λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized (Auto ConstantFold)) (Expression λ l _1 _2) = SynCFExp λ l

data Item λ l f' f Source #

Constructors

Single (f (Expression l l f' f')) 
Repeated (f (Expression l l f' f')) (f (ConstExpression l l f' f')) 

Instances

Instances details
(Transformation t, Functor t (Expression l l), Functor t (Expression l l), Functor t (ConstExpression l l)) => Functor t (Item λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Item λ l (Domain t) (Domain t) -> Item λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (ConstExpression l l)) => Foldable t (Item λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Item λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (ConstExpression l l)) => Traversable t (Item λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Item λ l (Domain t) (Domain t) -> m (Item λ l f f) #

(Transformation t, At t (Expression l l f' f'), At t (Expression l l f' f'), At t (ConstExpression l l f' f')) => Functor t (Item λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Item λ l f' (Domain t) -> Item λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (Expression l l f' f'), At t (Expression l l f' f'), At t (ConstExpression l l f' f')) => Foldable t (Item λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Item λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (Expression l l f' f'), At t (Expression l l f' f'), At t (ConstExpression l l f' f')) => Traversable t (Item λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Item λ l f' (Domain t) -> m (Item λ l f' f) #

(Functor (Auto ConstantFold) (Item l l), At (Auto ConstantFold) (Item l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (Item l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Functor (Item λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Foldable (Item λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Traversable (Item λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

Apply (Item λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Attribution (Auto ConstantFold) (Item l l) Sem Placed => At (Auto ConstantFold) (Item l l (Semantics (Auto ConstantFold)) (Semantics (Auto ConstantFold))) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Eq (f (Expression l l f' f')) => Eq (Item λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(==) :: Item λ l f' f -> Item λ l f' f -> Bool #

(/=) :: Item λ l f' f -> Item λ l f' f -> Bool #

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (f (Expression l l f' f')), Data (f (Expression l l f' f'))) => Data (Item λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Item λ l f' f -> c (Item λ l f' f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Item λ l f' f) #

toConstr :: Item λ l f' f -> Constr #

dataTypeOf :: Item λ l f' f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Item λ l f' f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Item λ l f' f)) #

gmapT :: (forall b. Data b => b -> b) -> Item λ l f' f -> Item λ l f' f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Item λ l f' f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Item λ l f' f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Item λ l f' f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Item λ l f' f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Item λ l f' f -> m (Item λ l f' f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Item λ l f' f -> m (Item λ l f' f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Item λ l f' f -> m (Item λ l f' f) #

Show (f (Expression l l f' f')) => Show (Item λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> Item λ l f' f -> ShowS #

show :: Item λ l f' f -> String #

showList :: [Item λ l f' f] -> ShowS #

Pretty (Expression l l Identity Identity) => Pretty (Item Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type Atts (Inherited (Auto ConstantFold)) (Item λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (Item λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (Item λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized (Auto ConstantFold)) (Item λ l _1 _2) = SynCF' (Item l l)

data Variant λ l f' f Source #

Constructors

Variant (f (CaseLabels l l f' f')) (ZipList (f (CaseLabels l l f' f'))) (ZipList (f (FieldList l l f' f'))) 
EmptyVariant 

Instances

Instances details
(Transformation t, Functor t (CaseLabels l l), Functor t (CaseLabels l l), Functor t (FieldList l l)) => Functor t (Variant λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Variant λ l (Domain t) (Domain t) -> Variant λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (CaseLabels l l), Foldable t (CaseLabels l l), Foldable t (FieldList l l)) => Foldable t (Variant λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Variant λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (CaseLabels l l), Traversable t (CaseLabels l l), Traversable t (FieldList l l)) => Traversable t (Variant λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Variant λ l (Domain t) (Domain t) -> m (Variant λ l f f) #

(Transformation t, At t (CaseLabels l l f' f'), At t (CaseLabels l l f' f'), At t (FieldList l l f' f')) => Functor t (Variant λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Variant λ l f' (Domain t) -> Variant λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (CaseLabels l l f' f'), At t (CaseLabels l l f' f'), At t (FieldList l l f' f')) => Foldable t (Variant λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Variant λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (CaseLabels l l f' f'), At t (CaseLabels l l f' f'), At t (FieldList l l f' f')) => Traversable t (Variant λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Variant λ l f' (Domain t) -> m (Variant λ l f' f) #

(Functor (Auto ConstantFold) (Variant l l), At (Auto ConstantFold) (Variant l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (Variant l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Functor (Variant λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Foldable (Variant λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Traversable (Variant λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

Apply (Variant λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Attribution (Auto ConstantFold) (Variant l l) Sem Placed => At (Auto ConstantFold) (Variant l l (Semantics (Auto ConstantFold)) (Semantics (Auto ConstantFold))) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (f (CaseLabels l l f' f')), Data (f (FieldList l l f' f'))) => Data (Variant λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Variant λ l f' f -> c (Variant λ l f' f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Variant λ l f' f) #

toConstr :: Variant λ l f' f -> Constr #

dataTypeOf :: Variant λ l f' f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Variant λ l f' f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Variant λ l f' f)) #

gmapT :: (forall b. Data b => b -> b) -> Variant λ l f' f -> Variant λ l f' f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Variant λ l f' f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Variant λ l f' f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Variant λ l f' f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Variant λ l f' f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Variant λ l f' f -> m (Variant λ l f' f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Variant λ l f' f -> m (Variant λ l f' f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Variant λ l f' f -> m (Variant λ l f' f) #

(Show (f (CaseLabels l l f' f')), Show (f (FieldList l l f' f'))) => Show (Variant λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> Variant λ l f' f -> ShowS #

show :: Variant λ l f' f -> String #

showList :: [Variant λ l f' f] -> ShowS #

(Pretty (CaseLabels l l Identity Identity), Pretty (FieldList l l Identity Identity)) => Pretty (Variant λ l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

Methods

pretty :: Variant λ l Identity Identity -> Doc ann #

prettyList :: [Variant λ l Identity Identity] -> Doc ann #

type Atts (Inherited (Auto ConstantFold)) (Variant λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (Variant λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (Variant λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized (Auto ConstantFold)) (Variant λ l _1 _2) = SynCF' (Variant l l)

data Block λ l f' f Source #

Constructors

Block (ZipList (f (Declaration l l f' f'))) (Maybe (f (StatementSequence l l f' f'))) 
ExceptionHandlingBlock (ZipList (f (Declaration l l f' f'))) (Maybe (f (StatementSequence l l f' f'))) (Maybe (f (StatementSequence l l f' f'))) (Maybe (f (StatementSequence l l f' f'))) 

Instances

Instances details
(Transformation t, Functor t (Declaration l l), Functor t (StatementSequence l l), Functor t (Declaration l l), Functor t (StatementSequence l l), Functor t (StatementSequence l l), Functor t (StatementSequence l l)) => Functor t (Block λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Block λ l (Domain t) (Domain t) -> Block λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (Declaration l l), Foldable t (StatementSequence l l), Foldable t (Declaration l l), Foldable t (StatementSequence l l), Foldable t (StatementSequence l l), Foldable t (StatementSequence l l)) => Foldable t (Block λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Block λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (Declaration l l), Traversable t (StatementSequence l l), Traversable t (Declaration l l), Traversable t (StatementSequence l l), Traversable t (StatementSequence l l), Traversable t (StatementSequence l l)) => Traversable t (Block λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Block λ l (Domain t) (Domain t) -> m (Block λ l f f) #

(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) #

(Transformation t, At t (Declaration l l f' f'), At t (StatementSequence l l f' f'), At t (Declaration l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f')) => Functor t (Block λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Block λ l f' (Domain t) -> Block λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (Declaration l l f' f'), At t (StatementSequence l l f' f'), At t (Declaration l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f')) => Foldable t (Block λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Block λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (Declaration l l f' f'), At t (StatementSequence l l f' f'), At t (Declaration l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f')) => Traversable t (Block λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Block λ l f' (Domain t) -> m (Block λ l f' f) #

(Functor (Auto ConstantFold) (Block l l), At (Auto ConstantFold) (Block l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (Block l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(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)) #

Functor (Block λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Foldable (Block λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Traversable (Block λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

Apply (Block λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Attribution (Auto ConstantFold) (Block l l) Sem Placed => At (Auto ConstantFold) (Block l l (Semantics (Auto ConstantFold)) (Semantics (Auto ConstantFold))) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (f (Declaration l l f' f')), Data (f (Designator l l f' f')), Data (f (Expression l l f' f')), Data (f (StatementSequence l l f' f'))) => Data (Block λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block λ l f' f -> c (Block λ l f' f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Block λ l f' f) #

toConstr :: Block λ l f' f -> Constr #

dataTypeOf :: Block λ l f' f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Block λ l f' f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Block λ l f' f)) #

gmapT :: (forall b. Data b => b -> b) -> Block λ l f' f -> Block λ l f' f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block λ l f' f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block λ l f' f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Block λ l f' f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Block λ l f' f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block λ l f' f -> m (Block λ l f' f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block λ l f' f -> m (Block λ l f' f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block λ l f' f -> m (Block λ l f' f) #

(Show (f (Declaration l l f' f')), Show (f (Designator l l f' f')), Show (f (Expression l l f' f')), Show (f (StatementSequence l l f' f'))) => Show (Block λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> Block λ l f' f -> ShowS #

show :: Block λ l f' f -> String #

showList :: [Block λ l f' f] -> ShowS #

(Pretty (Declaration l l Identity Identity), Pretty (StatementSequence l l Identity Identity)) => Pretty (Block λ l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

Methods

pretty :: Block λ l Identity Identity -> Doc ann #

prettyList :: [Block λ l Identity Identity] -> Doc ann #

type Atts (Inherited (Auto ConstantFold)) (Block λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (Block λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (Block λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized (Auto ConstantFold)) (Block λ l _1 _2) = SynCFMod' l (Block l l)

data Statement λ l f' f Source #

Constructors

EmptyStatement 
Assignment (f (Designator l l f' f')) (f (Expression l l f' f')) 
ProcedureCall (f (Designator l l f' f')) (Maybe (ZipList (f (Expression l l f' f')))) 
If (f (ConditionalBranch l l f' f')) (ZipList (f (ConditionalBranch l l f' f'))) (Maybe (f (StatementSequence l l f' f'))) 
CaseStatement (f (Expression l l f' f')) (ZipList (f (Case l l f' f'))) (Maybe (f (StatementSequence l l f' f'))) 
While (f (Expression l l f' f')) (f (StatementSequence l l f' f')) 
Repeat (f (StatementSequence l l f' f')) (f (Expression l l f' f')) 
For Ident (f (Expression l l f' f')) (f (Expression l l f' f')) (Maybe (f (Expression l l f' f'))) (f (StatementSequence l l f' f')) 
Loop (f (StatementSequence l l f' f')) 
With (f (Designator l l f' f')) (f (StatementSequence l l f' f')) 
Exit 
Return (Maybe (f (Expression l l f' f'))) 
RetryStatement 

Instances

Instances details
(Transformation t, Functor t (Designator l l), Functor t (Expression l l), Functor t (Designator l l), Functor t (Expression l l), Functor t (ConditionalBranch l l), Functor t (ConditionalBranch l l), Functor t (StatementSequence l l), Functor t (Expression l l), Functor t (Case l l), Functor t (StatementSequence l l), Functor t (Expression l l), Functor t (StatementSequence l l), Functor t (StatementSequence l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (Expression l l), Functor t (StatementSequence l l), Functor t (StatementSequence l l), Functor t (Designator l l), Functor t (StatementSequence l l), Functor t (Expression l l)) => Functor t (Statement λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Statement λ l (Domain t) (Domain t) -> Statement λ l (Codomain t) (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (Designator l l), Foldable t (Expression l l), Foldable t (Designator l l), Foldable t (Expression l l), Foldable t (ConditionalBranch l l), Foldable t (ConditionalBranch l l), Foldable t (StatementSequence l l), Foldable t (Expression l l), Foldable t (Case l l), Foldable t (StatementSequence l l), Foldable t (Expression l l), Foldable t (StatementSequence l l), Foldable t (StatementSequence l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (Expression l l), Foldable t (StatementSequence l l), Foldable t (StatementSequence l l), Foldable t (Designator l l), Foldable t (StatementSequence l l), Foldable t (Expression l l)) => Foldable t (Statement λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Statement λ l (Domain t) (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (Designator l l), Traversable t (Expression l l), Traversable t (Designator l l), Traversable t (Expression l l), Traversable t (ConditionalBranch l l), Traversable t (ConditionalBranch l l), Traversable t (StatementSequence l l), Traversable t (Expression l l), Traversable t (Case l l), Traversable t (StatementSequence l l), Traversable t (Expression l l), Traversable t (StatementSequence l l), Traversable t (StatementSequence l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (Expression l l), Traversable t (StatementSequence l l), Traversable t (StatementSequence l l), Traversable t (Designator l l), Traversable t (StatementSequence l l), Traversable t (Expression l l)) => Traversable t (Statement λ l) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Statement λ l (Domain t) (Domain t) -> m (Statement λ l f f) #

(Transformation t, At t (Designator l l f' f'), At t (Expression l l f' f'), At t (Designator l l f' f'), At t (Expression l l f' f'), At t (ConditionalBranch l l f' f'), At t (ConditionalBranch l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (Case l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (Designator l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f')) => Functor t (Statement λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

(<$>) :: t -> Statement λ l f' (Domain t) -> Statement λ l f' (Codomain t) #

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (Designator l l f' f'), At t (Expression l l f' f'), At t (Designator l l f' f'), At t (Expression l l f' f'), At t (ConditionalBranch l l f' f'), At t (ConditionalBranch l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (Case l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (Designator l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f')) => Foldable t (Statement λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Statement λ l f' (Domain t) -> m #

(Transformation t, Codomain t ~ Compose m f, Applicative m, At t (Designator l l f' f'), At t (Expression l l f' f'), At t (Designator l l f' f'), At t (Expression l l f' f'), At t (ConditionalBranch l l f' f'), At t (ConditionalBranch l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (Case l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (Expression l l f' f'), At t (StatementSequence l l f' f'), At t (StatementSequence l l f' f'), At t (Designator l l f' f'), At t (StatementSequence l l f' f'), At t (Expression l l f' f')) => Traversable t (Statement λ l f') Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Statement λ l f' (Domain t) -> m (Statement λ l f' f) #

(Functor (Auto ConstantFold) (Statement l l), At (Auto ConstantFold) (Statement l l (Codomain (Auto ConstantFold)) (Codomain (Auto ConstantFold)))) => Functor (Auto ConstantFold) (Statement l l) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Functor (Statement λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Foldable (Statement λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

Traversable (Statement λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

Apply (Statement λ l f' :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

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

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

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

Attribution (Auto ConstantFold) (Statement l l) Sem Placed => At (Auto ConstantFold) (Statement l l (Semantics (Auto ConstantFold)) (Semantics (Auto ConstantFold))) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (f (Designator l l f' f')), Data (f (Expression l l f' f')), Data (f (Case l l f' f')), Data (f (ConditionalBranch l l f' f')), Data (f (StatementSequence l l f' f'))) => Data (Statement λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Statement λ l f' f -> c (Statement λ l f' f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Statement λ l f' f) #

toConstr :: Statement λ l f' f -> Constr #

dataTypeOf :: Statement λ l f' f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Statement λ l f' f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Statement λ l f' f)) #

gmapT :: (forall b. Data b => b -> b) -> Statement λ l f' f -> Statement λ l f' f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Statement λ l f' f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Statement λ l f' f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Statement λ l f' f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Statement λ l f' f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Statement λ l f' f -> m (Statement λ l f' f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement λ l f' f -> m (Statement λ l f' f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement λ l f' f -> m (Statement λ l f' f) #

(Show (f (Designator l l f' f')), Show (f (Expression l l f' f')), Show (f (Case l l f' f')), Show (f (ConditionalBranch l l f' f')), Show (f (StatementSequence l l f' f'))) => Show (Statement λ l f' f) Source # 
Instance details

Defined in Language.Modula2.ISO.AST

Methods

showsPrec :: Int -> Statement λ l f' f -> ShowS #

show :: Statement λ l f' f -> String #

showList :: [Statement λ l f' f] -> ShowS #

(Pretty (ConstExpression l l Identity Identity), Pretty (Designator l l Identity Identity), Pretty (Case l l Identity Identity), Pretty (ConditionalBranch l l Identity Identity), Pretty (WithAlternative l l Identity Identity), Pretty (StatementSequence l l Identity Identity)) => Pretty (Statement Language l Identity Identity) Source # 
Instance details

Defined in Language.Modula2.ISO.Pretty

type Atts (Inherited (Auto ConstantFold)) (Statement λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited (Auto ConstantFold)) (Statement λ l _1 _2) = InhCF λ
type Atts (Synthesized (Auto ConstantFold)) (Statement λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder