eo-phi-normalizer-2.2.2: Command line normalizer of 𝜑-calculus expressions.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.EO.Phi.Syntax.Abs

Description

The abstract syntax of language Syntax.

Documentation

data Program Source #

Constructors

Program [Binding] 

Instances

Instances details
Data Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: Program -> Constr #

dataTypeOf :: Program -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Program Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Methods

fromString :: String -> Program #

Generic Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep Program :: Type -> Type #

Methods

from :: Program -> Rep Program x #

to :: Rep Program x -> Program #

Read Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> Program -> Doc Source #

ToLatex Program Source # 
Instance details

Defined in Language.EO.Phi.ToLaTeX

Eq Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

Ord Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Program Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Program = D1 ('MetaData "Program" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'False) (C1 ('MetaCons "Program" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Binding])))

data MetaId Source #

Instances

Instances details
FromJSON MetaId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: MetaId -> Constr #

dataTypeOf :: MetaId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString MetaId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Methods

fromString :: String -> MetaId #

Generic MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep MetaId :: Type -> Type #

Methods

from :: MetaId -> Rep MetaId x #

to :: Rep MetaId x -> MetaId #

Read MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> MetaId -> Doc Source #

Eq MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

Ord MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep MetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

data Object Source #

Instances

Instances details
FromJSON Object Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: Object -> Constr #

dataTypeOf :: Object -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Object Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Methods

fromString :: String -> Object #

Generic Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep Object :: Type -> Type #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

Read Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Inspectable Object Source # 
Instance details

Defined in Language.EO.Phi.Metrics.Collect

Print Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> Object -> Doc Source #

ToLatex Object Source # 
Instance details

Defined in Language.EO.Phi.ToLaTeX

Eq Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

Ord Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Object Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Object = D1 ('MetaData "Object" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'False) (((C1 ('MetaCons "Formation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Binding])) :+: C1 ('MetaCons "Application" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Binding]))) :+: (C1 ('MetaCons "ObjectDispatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attribute)) :+: (C1 ('MetaCons "GlobalObject" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThisObject" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Termination" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MetaSubstThis" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object)) :+: C1 ('MetaCons "MetaContextualize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object)))) :+: (C1 ('MetaCons "MetaObject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectMetaId)) :+: (C1 ('MetaCons "MetaTailContext" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TailMetaId)) :+: C1 ('MetaCons "MetaFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MetaFunctionName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Object))))))

data Binding Source #

Instances

Instances details
FromJSON Binding Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: Binding -> Constr #

dataTypeOf :: Binding -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Binding Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Methods

fromString :: String -> Binding #

Generic Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep Binding :: Type -> Type #

Methods

from :: Binding -> Rep Binding x #

to :: Rep Binding x -> Binding #

Read Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Inspectable Binding Source # 
Instance details

Defined in Language.EO.Phi.Metrics.Collect

Print Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> Binding -> Doc Source #

ToLatex Binding Source # 
Instance details

Defined in Language.EO.Phi.ToLaTeX

Eq Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

Ord Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print [Binding] Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> [Binding] -> Doc Source #

type Rep Binding Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

data Attribute Source #

Instances

Instances details
FromJSON Attribute Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: Attribute -> Constr #

dataTypeOf :: Attribute -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Attribute Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Generic Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep Attribute :: Type -> Type #

Read Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> Attribute -> Doc Source #

ToLatex Attribute Source # 
Instance details

Defined in Language.EO.Phi.ToLaTeX

Eq Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Attribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Attribute = D1 ('MetaData "Attribute" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'False) ((C1 ('MetaCons "Phi" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rho" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LabelId)) :+: (C1 ('MetaCons "Alpha" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AlphaIndex)) :+: C1 ('MetaCons "MetaAttr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LabelMetaId)))))

data RuleAttribute Source #

Instances

Instances details
FromJSON RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: RuleAttribute -> Constr #

dataTypeOf :: RuleAttribute -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Generic RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep RuleAttribute :: Type -> Type #

Read RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> RuleAttribute -> Doc Source #

ToLatex RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.ToLaTeX

Eq RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep RuleAttribute Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep RuleAttribute = D1 ('MetaData "RuleAttribute" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'False) (C1 ('MetaCons "ObjectAttr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attribute)) :+: (C1 ('MetaCons "DeltaAttr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LambdaAttr" 'PrefixI 'False) (U1 :: Type -> Type)))

data PeeledObject Source #

Instances

Instances details
Data PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: PeeledObject -> Constr #

dataTypeOf :: PeeledObject -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Generic PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep PeeledObject :: Type -> Type #

Read PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> PeeledObject -> Doc Source #

Eq PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep PeeledObject Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep PeeledObject = D1 ('MetaData "PeeledObject" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'False) (C1 ('MetaCons "PeeledObject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectHead) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ObjectAction])))

data ObjectHead Source #

Instances

Instances details
Data ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: ObjectHead -> Constr #

dataTypeOf :: ObjectHead -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Rules.Common

Generic ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep ObjectHead :: Type -> Type #

Read ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> ObjectHead -> Doc Source #

Eq ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep ObjectHead Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep ObjectHead = D1 ('MetaData "ObjectHead" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'False) ((C1 ('MetaCons "HeadFormation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Binding])) :+: C1 ('MetaCons "HeadGlobal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HeadThis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HeadTermination" 'PrefixI 'False) (U1 :: Type -> Type)))

data ObjectAction Source #

Instances

Instances details
Data ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: ObjectAction -> Constr #

dataTypeOf :: ObjectAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep ObjectAction :: Type -> Type #

Read ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> ObjectAction -> Doc Source #

Eq ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print [ObjectAction] Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> [ObjectAction] -> Doc Source #

type Rep ObjectAction Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep ObjectAction = D1 ('MetaData "ObjectAction" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'False) (C1 ('MetaCons "ActionApplication" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Binding])) :+: C1 ('MetaCons "ActionDispatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attribute)))

newtype Bytes Source #

Constructors

Bytes String 

Instances

Instances details
Data Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: Bytes -> Constr #

dataTypeOf :: Bytes -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

fromString :: String -> Bytes #

Generic Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep Bytes :: Type -> Type #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Read Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Print Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> Bytes -> Doc Source #

Eq Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

Ord Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

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

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

type Rep Bytes Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Bytes = D1 ('MetaData "Bytes" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "Bytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype Function Source #

Constructors

Function String 

Instances

Instances details
Data Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: Function -> Constr #

dataTypeOf :: Function -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep Function :: Type -> Type #

Methods

from :: Function -> Rep Function x #

to :: Rep Function x -> Function #

Read Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> Function -> Doc Source #

Eq Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Function Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep Function = D1 ('MetaData "Function" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "Function" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype LabelId Source #

Constructors

LabelId String 

Instances

Instances details
FromJSON LabelId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: LabelId -> Constr #

dataTypeOf :: LabelId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

fromString :: String -> LabelId #

Generic LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep LabelId :: Type -> Type #

Methods

from :: LabelId -> Rep LabelId x #

to :: Rep LabelId x -> LabelId #

Read LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> LabelId -> Doc Source #

Eq LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

Ord LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep LabelId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep LabelId = D1 ('MetaData "LabelId" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "LabelId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype AlphaIndex Source #

Constructors

AlphaIndex String 

Instances

Instances details
FromJSON AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: AlphaIndex -> Constr #

dataTypeOf :: AlphaIndex -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep AlphaIndex :: Type -> Type #

Read AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> AlphaIndex -> Doc Source #

Eq AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep AlphaIndex Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep AlphaIndex = D1 ('MetaData "AlphaIndex" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "AlphaIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype LabelMetaId Source #

Constructors

LabelMetaId String 

Instances

Instances details
FromJSON LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: LabelMetaId -> Constr #

dataTypeOf :: LabelMetaId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep LabelMetaId :: Type -> Type #

Read LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> LabelMetaId -> Doc Source #

Eq LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep LabelMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep LabelMetaId = D1 ('MetaData "LabelMetaId" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "LabelMetaId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype TailMetaId Source #

Constructors

TailMetaId String 

Instances

Instances details
FromJSON TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: TailMetaId -> Constr #

dataTypeOf :: TailMetaId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep TailMetaId :: Type -> Type #

Read TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> TailMetaId -> Doc Source #

Eq TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep TailMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep TailMetaId = D1 ('MetaData "TailMetaId" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "TailMetaId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype BindingsMetaId Source #

Constructors

BindingsMetaId String 

Instances

Instances details
FromJSON BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: BindingsMetaId -> Constr #

dataTypeOf :: BindingsMetaId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep BindingsMetaId :: Type -> Type #

Read BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> BindingsMetaId -> Doc Source #

Eq BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep BindingsMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep BindingsMetaId = D1 ('MetaData "BindingsMetaId" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "BindingsMetaId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype ObjectMetaId Source #

Constructors

ObjectMetaId String 

Instances

Instances details
FromJSON ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: ObjectMetaId -> Constr #

dataTypeOf :: ObjectMetaId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep ObjectMetaId :: Type -> Type #

Read ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> ObjectMetaId -> Doc Source #

Eq ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep ObjectMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep ObjectMetaId = D1 ('MetaData "ObjectMetaId" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "ObjectMetaId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype BytesMetaId Source #

Constructors

BytesMetaId String 

Instances

Instances details
FromJSON BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Rules.Yaml

Data BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: BytesMetaId -> Constr #

dataTypeOf :: BytesMetaId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep BytesMetaId :: Type -> Type #

Read BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Methods

prt :: Int -> BytesMetaId -> Doc Source #

Eq BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep BytesMetaId Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep BytesMetaId = D1 ('MetaData "BytesMetaId" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "BytesMetaId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

newtype MetaFunctionName Source #

Constructors

MetaFunctionName String 

Instances

Instances details
Data MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Methods

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

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

toConstr :: MetaFunctionName -> Constr #

dataTypeOf :: MetaFunctionName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Generic MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Associated Types

type Rep MetaFunctionName :: Type -> Type #

Read MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Show MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Print MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Print

Eq MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

Ord MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep MetaFunctionName Source # 
Instance details

Defined in Language.EO.Phi.Syntax.Abs

type Rep MetaFunctionName = D1 ('MetaData "MetaFunctionName" "Language.EO.Phi.Syntax.Abs" "eo-phi-normalizer-2.2.2-HCiAPEhyNyPA9TYfe0v2V6" 'True) (C1 ('MetaCons "MetaFunctionName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))