language-oberon-0.3.3: Parser, pretty-printer, and more for the Oberon programming language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Oberon.AST

Description

Concrete data types for Oberon constructs that make up its Abstract Syntax Tree. Every data type from this module is an instance of a type family declared in Language.Oberon.Abstract. This way it can be replaced by another data type for another language while leaving other types to be reused.

Synopsis

Documentation

data ConditionalBranch λ l f' f Source #

Constructors

ConditionalBranch (f (Expression l l f' f')) (f (StatementSequence l l f' f')) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

(Pretty (Expression l l Identity Identity), Pretty (StatementSequence l l Identity Identity)) => Pretty (ConditionalBranch λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (ConditionalBranch l l _1 _2) Source # 
Instance details

Defined in Language.Oberon.ConstantFolder

data CaseLabels λ l f' f Source #

Constructors

SingleLabel (f (ConstExpression l l f' f')) 
LabelRange (f (ConstExpression l l f' f')) (f (ConstExpression l l f' f')) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

data Case λ l f' f Source #

Constructors

Case (f (CaseLabels l l f' f')) (ZipList (f (CaseLabels l l f' f'))) (f (StatementSequence l l f' f')) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Functor t (CaseLabels l l), Functor t (CaseLabels l l), Functor t (StatementSequence l l)) => Functor t (Case λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

(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 (StatementSequence l l f' f')) => Foldable t (Case λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

(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 (StatementSequence l l f' f')) => Traversable t (Case λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show (f (CaseLabels l l f' f')), Show (f (StatementSequence l l f' f'))) => Show (Case λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

(Pretty (CaseLabels l l Identity Identity), Pretty (ConstExpression l l Identity Identity), Pretty (StatementSequence l l Identity Identity)) => Pretty (Case λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

Methods

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

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

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Case l l _1 _2) = SynCF' (Case l l)

data WithAlternative λ l f' f Source #

Constructors

WithAlternative (QualIdent l) (QualIdent l) (f (StatementSequence l l f' f')) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Functor t (StatementSequence l l)) => Functor t (WithAlternative λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (QualIdent l), Data (f (Designator l l f' f')), Data (f (StatementSequence l l f' f'))) => Data (WithAlternative λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show (QualIdent l), Show (f (StatementSequence l l f' f'))) => Show (WithAlternative λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

(Pretty (QualIdent l), Pretty (StatementSequence l l Identity Identity)) => Pretty (WithAlternative λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (WithAlternative l l _1 _2) Source # 
Instance details

Defined in Language.Oberon.ConstantFolder

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 (WithAlternative l l f' f')) (ZipList (f (WithAlternative l l f' f'))) (Maybe (f (StatementSequence l l f' f'))) 
Exit 
Return (Maybe (f (Expression l l f' f'))) 

Instances

Instances details
(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 (WithAlternative l l), Foldable t (WithAlternative l l), Foldable t (StatementSequence l l), Foldable t (Expression l l)) => Foldable t (Statement λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

(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 (WithAlternative l l), Functor t (WithAlternative l l), Functor t (StatementSequence l l), Functor t (Expression l l)) => Functor t (Statement λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

(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 (WithAlternative l l), Traversable t (WithAlternative l l), Traversable t (StatementSequence l l), Traversable t (Expression l l)) => Traversable t (Statement λ l) Source # 
Instance details

Defined in Language.Oberon.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, 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 (WithAlternative l l f' f'), At t (WithAlternative 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.Oberon.AST

Methods

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

(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 (WithAlternative l l f' f'), At t (WithAlternative 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.Oberon.AST

Methods

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

(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 (WithAlternative l l f' f'), At t (WithAlternative 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.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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 #

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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) #

(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 (WithAlternative 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.Oberon.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 (WithAlternative 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.Oberon.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 λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

newtype StatementSequence λ l f' f Source #

Constructors

StatementSequence (ZipList (f (Statement l l f' f'))) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Functor t (Statement l l)) => Functor t (StatementSequence λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Show (f (Statement l l f' f')) => Show (StatementSequence λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

Pretty (Statement l l Identity Identity) => Pretty (StatementSequence λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (StatementSequence l l _1 _2) Source # 
Instance details

Defined in Language.Oberon.ConstantFolder

data Block λ l f' f Source #

Constructors

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

Instances

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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.Oberon.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). 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, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (Declaration l l f' f'), At t (StatementSequence l l f' f')) => Foldable t (Block λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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 #

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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) #

(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.Oberon.ConstantFolder

Methods

bequest :: forall (sem :: Type -> TYPE LiftedRep). 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)) #

(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.Oberon.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.Oberon.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.Oberon.Pretty

Methods

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

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

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

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

data FPSection λ l f' f Source #

Constructors

FPSection Bool [Ident] (f (Type l l f' f')) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Functor t (Type l l)) => Functor t (FPSection λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show (f (Type l l f' f')), Show (f (Expression l l f' f'))) => Show (FPSection λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

Pretty (Type l l Identity Identity) => Pretty (FPSection λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

data FormalParameters λ l f' f Source #

Constructors

FormalParameters (ZipList (f (FPSection l l f' f'))) (Maybe (ReturnType l)) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Functor t (FPSection l l)) => Functor t (FormalParameters λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show (f (FPSection l l f' f')), Show (ReturnType l), Show (f (Expression l l f' f'))) => Show (FormalParameters λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

(Pretty (FPSection l l Identity Identity), Pretty (ReturnType l)) => Pretty (FormalParameters λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (FormalParameters l l _1 _2) Source # 
Instance details

Defined in Language.Oberon.ConstantFolder

data ProcedureHeading λ l f' f Source #

Instances

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Functor t (FormalParameters l l), Functor t (FormalParameters l l)) => Functor t (ProcedureHeading λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (IdentDef l), Data (f (FormalParameters l l f' f'))) => Data (ProcedureHeading λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show (IdentDef l), Show (f (FormalParameters l l f' f'))) => Show (ProcedureHeading λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

(Pretty (IdentDef l), Pretty (FormalParameters l l Identity Identity), Pretty (Type l l Identity Identity)) => Pretty (ProcedureHeading λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (ProcedureHeading l l _1 _2) Source # 
Instance details

Defined in Language.Oberon.ConstantFolder

data FieldList λ l f' f Source #

Constructors

FieldList (IdentList l) (f (Type l l f' f')) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show (IdentDef l), Show (f (Type l l f' f')), Show (f (Expression l l f' f'))) => Show (FieldList λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

(Pretty (IdentDef l), Pretty (Type l l Identity Identity)) => Pretty (FieldList λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

data Type λ l f' f Source #

Constructors

TypeReference (QualIdent l) 
ArrayType (ZipList (f (ConstExpression l l f' f'))) (f (Type l l f' f')) 
RecordType (Maybe (BaseType l)) (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, Codomain t ~ (Const m :: Type -> Type), Monoid m, Foldable t (ConstExpression 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.Oberon.AST

Methods

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

(Transformation t, Functor t (ConstExpression 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.Oberon.AST

Methods

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

(Transformation t, Codomain t ~ Compose m f, Applicative m, Traversable t (ConstExpression 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.Oberon.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, Codomain t ~ (Const m :: Type -> Type), Monoid m, At t (ConstExpression 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.Oberon.AST

Methods

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

(Transformation t, At t (ConstExpression 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.Oberon.AST

Methods

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

(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 (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.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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 #

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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) #

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (QualIdent 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.Oberon.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 (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.Oberon.AST

Methods

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

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

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

(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 λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

Methods

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

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

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

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

data Designator λ l f' f Source #

Constructors

Variable (QualIdent l) 
Field (f (Designator l l f' f')) Ident 
Index (f (Designator l l f' f')) (f (Expression l l f' f')) (ZipList (f (Expression l l f' f'))) 
TypeGuard (f (Designator l l f' f')) (QualIdent l) 
Dereference (f (Designator l l f' f')) 

Instances

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

Defined in Language.Oberon.ConstantFolder

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Codomain t ~ (Const m :: Type -> Type), Monoid m, 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 (Designator l l f' f'), At t (Designator l l f' f')) => Foldable t (Designator λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

(Transformation t, 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 (Designator l l f' f'), At t (Designator l l f' f')) => Functor t (Designator λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Codomain t ~ Compose m f, Applicative m, 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 (Designator l l f' f'), At t (Designator l l f' f')) => Traversable t (Designator λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

data Value λ l (f' :: * -> *) (f :: * -> *) Source #

Instances

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

Defined in Language.Oberon.AST

Methods

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

Transformation t => Functor t (Value λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

Transformation t => Functor t (Value λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Show (Value λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

Eq (Value λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.Pretty

type Atts (Inherited ConstantFold) (Value l l _1 _2) Source # 
Instance details

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Value l l _1 _2) = SynCF' (Value l l)

data Element λ l f' f Source #

Constructors

Element (f (Expression l l f' f')) 
Range (f (Expression l l f' f')) (f (Expression l l f' f')) 

Instances

Instances details
(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 (Element λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

(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 (Element λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

(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')) => Foldable t (Element λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

(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')) => Traversable t (Element λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Pretty (Expression l l Identity Identity) => Pretty (Element λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

Methods

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

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

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Element l l _1 _2) = SynCF' (Element l l)

data Expression λ l f' f Source #

Constructors

Relation RelOp (f (Expression l l f' f')) (f (Expression l l f' f')) 
IsA (f (Expression l l f' f')) (QualIdent l) 
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')) 
And (f (Expression l l f' f')) (f (Expression l l f' f')) 
Set (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, 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 (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.Oberon.AST

Methods

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

(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 (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.Oberon.AST

Methods

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

(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 (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.Oberon.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, 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 (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.Oberon.AST

Methods

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

(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 (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.Oberon.AST

Methods

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

(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 (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.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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 #

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.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) #

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

Defined in Language.Oberon.Pretty

(Oberon λ, Nameable l, Ord (QualIdent l), Value l ~ Value l, 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)) (Designator l l Sem Sem) ~ SynCFDesignator l) => Synthesizer (Auto ConstantFold) (Expression λ l) Sem Placed Source # 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> TYPE LiftedRep). 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) #

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

Defined in Language.Oberon.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 (Value l l f' f')), Show (f (Designator l l f' f')), Show (f (Element l l f' f')), Show (f (Expression l l f' f'))) => Show (Expression λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

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

data AccessMode Source #

Constructors

Exported 
ReadOnly 
PrivateOnly 

Instances

Instances details
Data AccessMode Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

toConstr :: AccessMode -> Constr #

dataTypeOf :: AccessMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AccessMode Source # 
Instance details

Defined in Language.Oberon.AST

Eq AccessMode Source # 
Instance details

Defined in Language.Oberon.AST

Ord AccessMode Source # 
Instance details

Defined in Language.Oberon.AST

data IdentDef l Source #

Constructors

IdentDef Ident AccessMode 

Instances

Instances details
Data l => Data (IdentDef l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

toConstr :: IdentDef l -> Constr #

dataTypeOf :: IdentDef l -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (IdentDef l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

show :: IdentDef l -> String #

showList :: [IdentDef l] -> ShowS #

Eq (IdentDef l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

(==) :: IdentDef l -> IdentDef l -> Bool #

(/=) :: IdentDef l -> IdentDef l -> Bool #

Ord (IdentDef l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

compare :: IdentDef l -> IdentDef l -> Ordering #

(<) :: IdentDef l -> IdentDef l -> Bool #

(<=) :: IdentDef l -> IdentDef l -> Bool #

(>) :: IdentDef l -> IdentDef l -> Bool #

(>=) :: IdentDef l -> IdentDef l -> Bool #

max :: IdentDef l -> IdentDef l -> IdentDef l #

min :: IdentDef l -> IdentDef l -> IdentDef l #

Pretty (IdentDef l) Source # 
Instance details

Defined in Language.Oberon.Pretty

Methods

pretty :: IdentDef l -> Doc ann #

prettyList :: [IdentDef l] -> Doc ann #

data QualIdent l Source #

Instances

Instances details
Data l => Data (QualIdent l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

toConstr :: QualIdent l -> Constr #

dataTypeOf :: QualIdent l -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (QualIdent l) Source # 
Instance details

Defined in Language.Oberon.AST

Eq (QualIdent l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

(==) :: QualIdent l -> QualIdent l -> Bool #

(/=) :: QualIdent l -> QualIdent l -> Bool #

Ord (QualIdent l) Source # 
Instance details

Defined in Language.Oberon.AST

Pretty (QualIdent l) Source # 
Instance details

Defined in Language.Oberon.Pretty

Methods

pretty :: QualIdent l -> Doc ann #

prettyList :: [QualIdent l] -> Doc ann #

data Declaration λ l f' f Source #

Constructors

ConstantDeclaration (IdentDef l) (f (ConstExpression l l f' f')) 
TypeDeclaration (IdentDef l) (f (Type l l f' f')) 
VariableDeclaration (IdentList l) (f (Type l l f' f')) 
ProcedureDeclaration (f (ProcedureHeading l l f' f')) (f (Block l l f' f')) 
ForwardDeclaration (IdentDef l) (Maybe (f (FormalParameters l l f' f'))) 

Instances

Instances details
(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 (ProcedureHeading l l), Foldable t (Block l l), Foldable t (FormalParameters l l)) => Foldable t (Declaration λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

(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 (ProcedureHeading l l), Traversable t (Block l l), Traversable t (FormalParameters l l)) => Traversable t (Declaration λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.ConstantFolder

Methods

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

(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 (ProcedureHeading l l f' f'), At t (Block l l f' f'), At t (FormalParameters l l f' f')) => Foldable t (Declaration λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

(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 (ProcedureHeading l l f' f'), At t (Block l l f' f'), At t (FormalParameters l l f' f')) => Functor t (Declaration λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

(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 (ProcedureHeading l l f' f'), At t (Block l l f' f'), At t (FormalParameters l l f' f')) => Traversable t (Declaration λ l f') Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (f (Type l l f' f')), Data (f (ConstExpression l l f' f')), Data (f (FormalParameters l l f' f')), Data (f (ProcedureHeading l l f' f')), Data (f (Block l l f' f')), Data (IdentDef l)) => Data (Declaration λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Declaration λ l f' f -> m (Declaration λ 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 (IdentDef l)) => Show (Declaration λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

(Nameable l, Pretty (IdentDef 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 λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

data Module λ l f' f Source #

Constructors

Module Ident [Import l] (f (Block l l f' f')) 

Instances

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

Defined in Language.Oberon.AST

Methods

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

(Transformation t, Functor t (Block l l)) => Functor t (Module λ l) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.ConstantFolder

Methods

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

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

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

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

Defined in Language.Oberon.TypeChecker

Methods

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

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

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

Defined in Language.Oberon.AST

Methods

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

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

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

Defined in Language.Oberon.ConstantFolder

Methods

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

(Typeable λ, Typeable l, Typeable f, Typeable f', Data (Import l), Data (f (Block l l f' f'))) => Data (Module λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Show (Import l), Show (f (Block l l f' f'))) => Show (Module λ l f' f) Source # 
Instance details

Defined in Language.Oberon.AST

Methods

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

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

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

(Pretty (Import l), Pretty (Block l l Identity Identity)) => Pretty (Module λ l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

Methods

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

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

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

Defined in Language.Oberon.ConstantFolder

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

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Module l l _1 _2) = SynCFMod' l (Module l l)

data Language Source #

Data type representing the Oberon language, both versions of it.

Constructors

Language 

Instances

Instances details
Data Language Source # 
Instance details

Defined in Language.Oberon.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 #

CoWirthy Language Source # 
Instance details

Defined in Language.Oberon.AST

Associated Types

type TargetClass Language :: Type -> Constraint Source #

Methods

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

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

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

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

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

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

Nameable Language Source # 
Instance details

Defined in Language.Oberon.AST

Oberon Language Source # 
Instance details

Defined in Language.Oberon.AST

Associated Types

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

Methods

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

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

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

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

exported :: Ident -> IdentDef Language Source #

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

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

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

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

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

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

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

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

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

Oberon2 Language Source # 
Instance details

Defined in Language.Oberon.AST

Methods

readOnly :: Ident -> IdentDef Language Source #

typeBoundHeading :: forall l' f (f' :: Type -> Type). Bool -> Ident -> Ident -> Bool -> IdentDef l' -> Maybe (f (FormalParameters l' l' f' f')) -> ProcedureHeading 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 #

variantWithStatement :: forall f l' (f' :: Type -> Type). NonEmpty (f (WithAlternative l' l' f' f')) -> Maybe (f (StatementSequence l' l' f' f')) -> Statement Language l' f' f Source #

Wirthy Language Source # 
Instance details

Defined in Language.Oberon.AST

Associated Types

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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 Source #

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

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

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

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

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

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 Source #

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

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

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 Source #

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

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 Source #

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

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

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

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

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 Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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 Source #

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

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

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

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

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

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

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

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

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

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

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

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

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 Source #

dereference :: forall f l' (f' :: Type -> Type). f (Designator l' l' f' f') -> Designator Language l' f' f Source #

identDef :: Ident -> IdentDef Language Source #

nonQualIdent :: Ident -> QualIdent Language Source #

Pretty (Value Language l Identity Identity) Source # 
Instance details

Defined in Language.Oberon.Pretty

type Block Language Source # 
Instance details

Defined in Language.Oberon.AST

type Case Language Source # 
Instance details

Defined in Language.Oberon.AST

type CaseLabels Language Source # 
Instance details

Defined in Language.Oberon.AST

type ConditionalBranch Language Source # 
Instance details

Defined in Language.Oberon.AST

type Declaration Language Source # 
Instance details

Defined in Language.Oberon.AST

type Designator Language Source # 
Instance details

Defined in Language.Oberon.AST

type Element Language Source # 
Instance details

Defined in Language.Oberon.AST

type Expression Language Source # 
Instance details

Defined in Language.Oberon.AST

type FPSection Language Source # 
Instance details

Defined in Language.Oberon.AST

type FieldList Language Source # 
Instance details

Defined in Language.Oberon.AST

type FormalParameters Language Source # 
Instance details

Defined in Language.Oberon.AST

type IdentDef Language Source # 
Instance details

Defined in Language.Oberon.AST

type Import Language Source # 
Instance details

Defined in Language.Oberon.AST

type Module Language Source # 
Instance details

Defined in Language.Oberon.AST

type ProcedureHeading Language Source # 
Instance details

Defined in Language.Oberon.AST

type QualIdent Language Source # 
Instance details

Defined in Language.Oberon.AST

type Statement Language Source # 
Instance details

Defined in Language.Oberon.AST

type StatementSequence Language Source # 
Instance details

Defined in Language.Oberon.AST

type TargetClass Language Source # 
Instance details

Defined in Language.Oberon.AST

type Type Language Source # 
Instance details

Defined in Language.Oberon.AST

type Value Language Source # 
Instance details

Defined in Language.Oberon.AST

type WithAlternative Language Source # 
Instance details

Defined in Language.Oberon.AST

data RelOp Source #

Relational operators

Instances

Instances details
Data RelOp Source # 
Instance details

Defined in Language.Oberon.Abstract

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelOp -> c RelOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RelOp #

toConstr :: RelOp -> Constr #

dataTypeOf :: RelOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RelOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RelOp) #

gmapT :: (forall b. Data b => b -> b) -> RelOp -> RelOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> RelOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RelOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RelOp -> m RelOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RelOp -> m RelOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RelOp -> m RelOp #

Show RelOp Source # 
Instance details

Defined in Language.Oberon.Abstract

Methods

showsPrec :: Int -> RelOp -> ShowS #

show :: RelOp -> String #

showList :: [RelOp] -> ShowS #

Eq RelOp Source # 
Instance details

Defined in Language.Oberon.Abstract

Methods

(==) :: RelOp -> RelOp -> Bool #

(/=) :: RelOp -> RelOp -> Bool #

Pretty RelOp Source # 
Instance details

Defined in Language.Oberon.Pretty

Methods

pretty :: RelOp -> Doc ann #

prettyList :: [RelOp] -> Doc ann #