language-Modula2-0.1.3: Parser, pretty-printer, and more for the Modula-2 programming language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Modula2.ISO.Abstract

Description

ISO Modula-2 Finally Tagless Abstract Syntax Tree definitions

Synopsis

Documentation

class Modula2 l => Modula2 l where Source #

The additional finally-tagless associated types and methods relevant to the ISO Modula-2 language.

Associated Types

type AddressedIdent l = (d :: * -> (* -> *) -> (* -> *) -> *) | d -> l Source #

type Item l = (i :: * -> (* -> *) -> (* -> *) -> *) | i -> l Source #

Methods

emptyVariant :: Variant l l' f' f Source #

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

forwardProcedureDeclaration :: f (ProcedureHeading l' l' f' f') -> Declaration l l' f' f Source #

exceptionHandlingBlock :: [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 l l' f' f Source #

addressedIdent :: Ident -> f (ConstExpression l' l' f' f') -> AddressedIdent l l' f' f Source #

unaddressedIdent :: Ident -> AddressedIdent l l' f' f Source #

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

retryStatement :: Statement l l' f' f Source #

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

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

remainder :: f (Expression l' l' f' f') -> f (Expression l' l' f' f') -> Expression l l' f' f Source #

single :: f (Expression l' l' f' f') -> Item l l' f' f Source #

repeated :: f (Expression l' l' f' f') -> f (ConstExpression l' l' f' f') -> Item l l' f' f Source #

Instances

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

Wirthy l => Modula2 (WirthySubsetOf l) Source # 
Instance details

Defined in Language.Modula2.ISO.Abstract

Associated Types

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

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

Methods

emptyVariant :: forall l' (f' :: Type -> Type) (f :: Type -> Type). Variant (WirthySubsetOf l) 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 (WirthySubsetOf l) l' f' f Source #

forwardProcedureDeclaration :: forall f l' (f' :: Type -> Type). f (ProcedureHeading l' l' f' f') -> Declaration (WirthySubsetOf l) 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 (WirthySubsetOf l) l' f' f Source #

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

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

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

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

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

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

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

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

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