hascalam-0.1.1.2: Haskell to and from Scalameta
Safe HaskellSafe-Inferred
LanguageGHC2021

HaScalaM.Classes

Documentation

class (Init m n t' t ac i, Tree a) => Annot m n t' t ac i a where Source #

Methods

init :: a -> i Source #

Instances

Instances details
(m ~ SmMod, n ~ SmName, t' ~ SmType', t ~ SmTerm, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, Init m n t' t ac i) => Annot m n t' t ac i (SmAnnotM m n t' t ac i) Source # 
Instance details

Defined in HaScalaM.Instances

Methods

init :: SmAnnotM m n t' t ac i -> i Source #

class (WithParamClauses m n p t' t pc c, Ctor c) => Primary m n p t' t pc c where Source #

Methods

mods :: c -> [m] Source #

Instances

Instances details
ParamClauseT m n p t' t pc => Primary m n p t' t pc (SmCtorPrimary m n p t' t pc) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Methods

mods :: SmCtorPrimary m n p t' t pc -> [m] Source #

class (WithParamClauses m n p t' t pc c, Init m n t' t ac i, Stat s, Ctor c) => Secondary m n p t' t pc ac i s c Source #

Instances

Instances details
(ParamClauseT m n p t' t pc, Init m n t' t ac i, Stat s) => Secondary m n p t' t pc ac i (s :: Type) (SmCtorSecondaryS m n p t' t pc ac i s) Source # 
Instance details

Defined in HaScalaM.Instances

class (Name n, Type' t', ArgClauseT m t ac, Tree i) => Init m n t' t ac i where Source #

Methods

tpe :: i -> t' Source #

name' :: i -> n Source #

argClauses :: i -> [ac] Source #

Instances

Instances details
(m ~ SmMod, n ~ SmName, t' ~ SmType', ac ~ SmArgClauseT m t, Name n, Type' t', ArgClauseT m t ac) => Init m n t' t ac (SmInit m n t' t ac) Source # 
Instance details

Defined in HaScalaM.Instances.Base

Methods

tpe :: SmInit m n t' t ac -> t' Source #

name' :: SmInit m n t' t ac -> n Source #

argClauses :: SmInit m n t' t ac -> [ac] Source #

class Tree t => Lit t Source #

Instances

Instances details
Lit SmLit Source # 
Instance details

Defined in HaScalaM.Instances.Base

class (ParamClauseT' m n p' t' b' pc', ParamClauseT m n p t' t pc, Tree g) => ParamClauseGroup m n p p' t' b' t pc pc' g where Source #

Methods

t'paramClause' :: g -> pc' Source #

paramClauses' :: g -> [pc] Source #

Instances

Instances details
(ParamClauseT' m n p' t' b' pc', ParamClauseT m n p t' t pc) => ParamClauseGroup m n p p' t' b' t pc pc' (SmParamClauseGroup m n p p' t' b' t pc pc') Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Methods

t'paramClause' :: SmParamClauseGroup m n p p' t' b' t pc pc' -> pc' Source #

paramClauses' :: SmParamClauseGroup m n p p' t' b' t pc pc' -> [pc] Source #

class (Name n, WithDeclTpeOpt t' p) => Self n t' p Source #

Instances

Instances details
(n ~ SmName, t' ~ SmType', Name n, Type' t') => Self n t' (SmSelf n t') Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

class (Stat s, WithStats s t) => Source s t Source #

Instances

Instances details
Stat s => Source s (SmSource s) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

class (Init m n t' t ac i, Stat s, Self n t' p, Tree e) => Template m n t' t ac i p s e where Source #

Methods

early :: e -> [s] Source #

inits :: e -> [i] Source #

self :: e -> p Source #

stats :: e -> [s] Source #

derives :: e -> [t'] Source #

Instances

Instances details
(Init m n t' t ac i, Stat s, Self n t' p) => Template m n t' t ac i p s (SmTemplate m n t' t ac i p s) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Methods

early :: SmTemplate m n t' t ac i p s -> [s] Source #

inits :: SmTemplate m n t' t ac i p s -> [i] Source #

self :: SmTemplate m n t' t ac i p s -> p Source #

stats :: SmTemplate m n t' t ac i p s -> [s] Source #

derives :: SmTemplate m n t' t ac i p s -> [t'] Source #

class (Primary m n p t' t pc c, Tree w) => WithCtor m n p t' t pc c w where Source #

Methods

ctor :: w -> c Source #

Instances

Instances details
(NameT tn, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Init m n t' t ac i) => WithCtor m n p t' t pc c (SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

ctor :: SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i -> c Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Template m n t' t ac i f s e) => WithCtor m n p t' t pc c (SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

ctor :: SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> c Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Template m n t' t ac i f s e) => WithCtor m n p t' t pc c (SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

ctor :: SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> c Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Template m n t' t ac i f s e) => WithCtor m n p t' t pc c (SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

ctor :: SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> c Source #

class (Template m n t' t ac i p s e, Tree w) => WithTemplate m n t' t ac i p s e w where Source #

Methods

templ :: w -> e Source #

Instances

Instances details
Template m n t' t ac i p s e => WithTemplate m n t' t ac i p s e (SmNewAnonymousT m n t' t ac i p s e) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

templ :: SmNewAnonymousT m n t' t ac i p s e -> e Source #

(NameT tn, Template m n t' t ac i p s e) => WithTemplate m n t' t ac i p s e (SmObjectS m n tn p t' t ac i s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

templ :: SmObjectS m n tn p t' t ac i s e -> e Source #

(NameT tn, Template m n t' t ac i p s e) => WithTemplate m n t' t ac i p s e (SmPkgObjectS m n p tn t' t ac i s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Methods

templ :: SmPkgObjectS m n p tn t' t ac i s e -> e Source #

(ParamClauseGroup m n p p' t' b' t pc pc' g, Template m n t' t ac i f s e) => WithTemplate m n t' t ac i f s e (SmGivenS m n p p' t' b' t pc pc' ac i f s e g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

templ :: SmGivenS m n p p' t' b' t pc pc' ac i f s e g -> e Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Template m n t' t ac i f s e) => WithTemplate m n t' t ac i f s e (SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

templ :: SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> e Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Template m n t' t ac i f s e) => WithTemplate m n t' t ac i f s e (SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

templ :: SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> e Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Template m n t' t ac i f s e) => WithTemplate m n t' t ac i f s e (SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

templ :: SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> e Source #

class (ParamClauseGroup m n p p' t' b' t pc pc' g, WithParamClauses m n p t' t pc w) => WithParamClauseGroup m n p p' t' b' t pc pc' g w where Source #

Methods

paramClauseGroup :: w -> Maybe g Source #

Instances

Instances details
(g ~ SmParamClauseGroup m n p p' t' b' t pc pc', ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroup m n p p' t' b' t pc pc' g (SmGivenAliasS m n p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

paramClauseGroup :: SmGivenAliasS m n p p' t' b' t pc pc' g -> Maybe g Source #

(g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroup m n p p' t' b' t pc pc' g (SmDef'S m n tn p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Decl

Methods

paramClauseGroup :: SmDef'S m n tn p p' t' b' t pc pc' g -> Maybe g Source #

(g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroup m n p p' t' b' t pc pc' g (SmDefS m n tn p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

paramClauseGroup :: SmDefS m n tn p p' t' b' t pc pc' g -> Maybe g Source #

(g ~ SmParamClauseGroup m n p p' t' b' t pc pc', ParamClauseGroup m n p p' t' b' t pc pc' g, Stat s) => WithParamClauseGroup m n p p' t' b' t pc pc' g (SmExtensionGroupS m n p p' t' b' t pc pc' s g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

paramClauseGroup :: SmExtensionGroupS m n p p' t' b' t pc pc' s g -> Maybe g Source #

(g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroup m n p p' t' b' t pc pc' g (SmGiven'S m n tn p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Decl

Methods

paramClauseGroup :: SmGiven'S m n tn p p' t' b' t pc pc' g -> Maybe g Source #

(g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroup m n p p' t' b' t pc pc' g (SmMacroS m n tn p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

paramClauseGroup :: SmMacroS m n tn p p' t' b' t pc pc' g -> Maybe g Source #

(g ~ SmParamClauseGroup m n p p' t' b' t pc pc', ParamClauseGroup m n p p' t' b' t pc pc' g, Template m n t' t ac i f s e) => WithParamClauseGroup m n p p' t' b' t pc pc' g (SmGivenS m n p p' t' b' t pc pc' ac i f s e g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

paramClauseGroup :: SmGivenS m n p p' t' b' t pc pc' ac i f s e g -> Maybe g Source #

class (ParamClauseGroup m n p p' t' b' t pc pc' g, Tree w) => WithParamClauseGroups m n p p' t' b' t pc pc' g w where Source #

Methods

paramClauseGroups :: w -> [g] Source #

Instances

Instances details
(NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroups m n p p' t' b' t pc pc' g (SmDef'S m n tn p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Decl

Methods

paramClauseGroups :: SmDef'S m n tn p p' t' b' t pc pc' g -> [g] Source #

(NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroups m n p p' t' b' t pc pc' g (SmDefS m n tn p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

paramClauseGroups :: SmDefS m n tn p p' t' b' t pc pc' g -> [g] Source #

(NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => WithParamClauseGroups m n p p' t' b' t pc pc' g (SmMacroS m n tn p p' t' b' t pc pc' g) Source # 
Instance details

Defined in HaScalaM.Instances.Stat.Defn

Methods

paramClauseGroups :: SmMacroS m n tn p p' t' b' t pc pc' g -> [g] Source #