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

HaScalaM.Types.Tilde

Documentation

data SmCaseCT p t where Source #

Constructors

SmCaseC 

Fields

Instances

Instances details
(Pat p, Term t) => CaseTree p t (SmCaseCT p t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

pat :: SmCaseCT p t -> p Source #

(Pat p, Term t) => Case p t (SmCaseCT p t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

(Pat p, Term t) => Tree (SmCaseCT p t :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Term

(Pat p, Term t) => WithBody t (SmCaseCT p t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

body :: SmCaseCT p t -> t Source #

(Pat p, Term t) => WithCondOpt t (SmCaseCT p t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

cond' :: SmCaseCT p t -> Maybe t Source #

(p ~ SmPat, t ~ SmTerm) => Show (SmCaseCT p t) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmCaseCT p t -> ShowS #

show :: SmCaseCT p t -> String #

showList :: [SmCaseCT p t] -> ShowS #

data SmType'CaseCT t' where Source #

Constructors

SmType'CaseT'C 

Fields

Instances

Instances details
Type' t' => CaseTree t' t' (SmType'CaseCT t') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

pat :: SmType'CaseCT t' -> t' Source #

Type' t' => Tree (SmType'CaseCT t' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Type

Type' t' => WithBody t' (SmType'CaseCT t') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

body :: SmType'CaseCT t' -> t' Source #

Type' t' => Type'Case t' (SmType'CaseCT t') Source # 
Instance details

Defined in HaScalaM.Instances.Type

t' ~ SmType' => Show (SmType'CaseCT t') Source # 
Instance details

Defined in HaScalaM.Instances.Show

data SmCtorPrimary m n p t' t pc where Source #

Constructors

SmCtorPrimary 

Fields

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 #

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

Defined in HaScalaM.Instances.Tilde

Methods

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

ParamClauseT m n p t' t pc => Ctor (SmCtorPrimary m n p t' t pc :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

ParamClauseT m n p t' t pc => Tree (SmCtorPrimary m n p t' t pc :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

(m ~ SmMod, n ~ SmName, t' ~ SmType', t ~ SmTerm, p ~ SmParamT m n t' t, pc ~ SmParamClauseT m n p t' t) => Show (SmCtorPrimary m n p t' t pc) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmCtorPrimary m n p t' t pc -> ShowS #

show :: SmCtorPrimary m n p t' t pc -> String #

showList :: [SmCtorPrimary m n p t' t pc] -> ShowS #

data SmEnumerator where Source #

Constructors

ECaseGenerator :: (p ~ SmPat, b ~ SmTerm, Pat p, Term b) => SmCaseGeneratorE p b -> SmEnumerator 
EGenerator :: (p ~ SmPat, b ~ SmTerm, Pat p, Term b) => SmGeneratorE p b -> SmEnumerator 
EGuard :: (b ~ SmTerm, Term b) => SmGuardE b -> SmEnumerator 
EVal :: (p ~ SmPat, b ~ SmTerm, Pat p, Term b) => SmValE p b -> SmEnumerator 

Instances

Instances details
Show SmEnumerator Source # 
Instance details

Defined in HaScalaM.Instances.Show

Tree SmEnumerator Source # 
Instance details

Defined in HaScalaM.Instances.Enums

Enumerator SmEnumerator Source # 
Instance details

Defined in HaScalaM.Instances.Enums

data SmImportee where Source #

Constructors

SmGivenI 

Fields

SmGivenAllI :: SmImportee 
SmNameI 

Fields

SmRenameI 

Fields

SmUnimportI 

Fields

SmWildcardI :: SmImportee 

Instances

Instances details
Show SmImportee Source # 
Instance details

Defined in HaScalaM.Instances.Show

Tree SmImportee Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Importee SmImportee Source # 
Instance details

Defined in HaScalaM.Instances.Stat

data SmImporter r i where Source #

Constructors

SmImporter 

Fields

Instances

Instances details
(r ~ SmRef, i ~ SmImportee, RefT r, Importee i) => Importer r i (SmImporter r i) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Methods

ref :: SmImporter r i -> r Source #

importees :: SmImporter r i -> [i] Source #

(RefT r, Importee i) => Tree (SmImporter r i :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Show (SmImporter r i) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmImporter r i -> ShowS #

show :: SmImporter r i -> String #

showList :: [SmImporter r i] -> ShowS #

data SmInit m n t' t ac where Source #

Constructors

SmInit 

Fields

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 #

(Name n, Type' t', ArgClauseT m t ac) => Tree (SmInit m n t' t ac :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Base

(n ~ SmName, t' ~ SmType', ac ~ SmArgClauseT m t) => Show (SmInit m n t' t ac) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmInit m n t' t ac -> ShowS #

show :: SmInit m n t' t ac -> String #

showList :: [SmInit m n t' t ac] -> ShowS #

data SmMod where Source #

Constructors

MAnnot :: (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) => SmAnnotM m n t' t ac i -> SmMod 
MMod :: SmModM -> SmMod 
MAccess :: (r ~ SmRef_, Ref r) => SmAccessM r -> SmMod 

Instances

Instances details
(i ~ SmInit m n t' t ac, r ~ SmRef_) => Show SmMod Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmMod -> ShowS #

show :: SmMod -> String #

showList :: [SmMod] -> ShowS #

ArgsType SmMod Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Mod SmMod Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

ParamsType SmMod Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Tree SmMod Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Variant SmMod Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

data SmName where Source #

Instances

Instances details
Show SmName Source # 
Instance details

Defined in HaScalaM.Instances.Show

Name SmName Source # 
Instance details

Defined in HaScalaM.Instances.Ref

Methods

value :: SmName -> String Source #

Tree SmName Source # 
Instance details

Defined in HaScalaM.Instances.Ref

data SmNameT where Source #

Constructors

SmNameT 

Fields

Instances

Instances details
Show SmNameT Source # 
Instance details

Defined in HaScalaM.Instances.Show

Name SmNameT Source # 
Instance details

Defined in HaScalaM.Instances.Ref

Methods

value :: SmNameT -> String Source #

NameT SmNameT Source # 
Instance details

Defined in HaScalaM.Instances.Ref

Tree SmNameT Source # 
Instance details

Defined in HaScalaM.Instances.Ref

Stat s => Member SmNameT (SmPkgS SmRef s) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Methods

name :: SmPkgS SmRef s -> SmNameT Source #

Stat s => MemberT SmNameT (SmPkgS SmRef s) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

data SmNameT' where Source #

Constructors

SmNameT' 

Fields

Instances

Instances details
Show SmNameT' Source # 
Instance details

Defined in HaScalaM.Instances.Show

Name SmNameT' Source # 
Instance details

Defined in HaScalaM.Instances.Ref

NameT' SmNameT' Source # 
Instance details

Defined in HaScalaM.Instances.Ref

Tree SmNameT' Source # 
Instance details

Defined in HaScalaM.Instances.Ref

data SmParamClauseGroup m n p p' t' b' t pc pc' where Source #

Constructors

SmParamClauseGroup 

Fields

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 #

(ParamClauseT' m n p' t' b' pc', ParamClauseT m n p t' t pc) => Tree (SmParamClauseGroup m n p p' t' b' t pc pc' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Show (SmParamClauseGroup m n p p' t' b' t pc pc') Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmParamClauseGroup m n p p' t' b' t pc pc' -> ShowS #

show :: SmParamClauseGroup m n p p' t' b' t pc pc' -> String #

showList :: [SmParamClauseGroup m n p p' t' b' t pc pc'] -> ShowS #

data SmPatP where Source #

Constructors

SmAlternativeP 

Fields

SmBindP 

Fields

SmGivenP 

Fields

SmInterpolateP 

Fields

SmNameP 

Fields

SmRepeatedP 

Fields

SmSelectP 

Fields

SmSeqWildcardP :: SmPatP 
SmTypedP 

Fields

SmWildcardP :: SmPatP 
SmXmlP 

Fields

Instances

Instances details
Tree SmPatP Source # 
Instance details

Defined in HaScalaM.Instances.Pat

data SmPat where Source #

Constructors

PExtract :: (t ~ SmTerm, p ~ SmPat, ac ~ SmArgClauseP p, Term t, Pat p, ArgClauseP p ac) => SmExtractP t p ac -> SmPat 
PExtractInfix :: (tn ~ SmNameT, p ~ SmPat, ac ~ SmArgClauseP p, NameT tn, Pat p, ArgClauseP p ac) => SmExtractInfixP tn p ac -> SmPat 
PLit :: SmLit -> SmPat 
PMacro :: (t ~ SmTerm, Term t) => SmMacroP t -> SmPat 
PPat :: SmPatP -> SmPat 
PTuple :: (p ~ SmPat, Pat p) => SmTupleP p -> SmPat 
PVar :: (tn ~ SmNameT, NameT tn) => SmVarP tn -> SmPat 

Instances

Instances details
Show SmPat Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmPat -> ShowS #

show :: SmPat -> String #

showList :: [SmPat] -> ShowS #

Tree SmPat Source # 
Instance details

Defined in HaScalaM.Instances.Pat

Pat SmPat Source # 
Instance details

Defined in HaScalaM.Instances.Pat

data SmArgClauseP p where Source #

Constructors

SmArgClauseP 

Fields

Instances

Instances details
Pat p => ArgClause p (SmArgClauseP p) Source # 
Instance details

Defined in HaScalaM.Instances.Pat

Pat p => SyntaxValuesClauses p (SmArgClauseP p) Source # 
Instance details

Defined in HaScalaM.Instances.Pat

Methods

values :: SmArgClauseP p -> [p] Source #

Pat p => Tree (SmArgClauseP p :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Pat

Pat p => ArgClauseP p (SmArgClauseP p) Source # 
Instance details

Defined in HaScalaM.Instances.Pat

Pat p => WithPats p (SmArgClauseP p) Source # 
Instance details

Defined in HaScalaM.Instances.Pat

Methods

pats :: SmArgClauseP p -> [p] Source #

Show (SmArgClauseP p) Source # 
Instance details

Defined in HaScalaM.Instances.Show

data SmRef_ where Source #

Constructors

RImportee :: SmImportee -> SmRef_ 
RInit :: (m ~ SmMod, n ~ SmName, t' ~ SmType', t ~ SmTerm, ac ~ SmArgClauseT m t, Name n, Type' t', ArgClauseT m t ac) => SmInit m n t' t ac -> SmRef_ 
RName :: SmName -> SmRef_ 
R_TRef :: SmRef -> SmRef_ 
R_T'Ref :: SmRef' -> SmRef_ 

Instances

Instances details
Show SmRef_ Source # 
Instance details

Defined in HaScalaM.Instances.Show

Ref SmRef_ Source # 
Instance details

Defined in HaScalaM.Instances.Ref

Tree SmRef_ Source # 
Instance details

Defined in HaScalaM.Instances.Ref

data SmRef where Source #

Constructors

RTAnonymous :: SmAnonymousRT -> SmRef 
RTName :: SmNameT -> SmRef 
RTRef :: (n ~ SmNameT, t ~ SmTerm) => SmRefT n t -> SmRef 
RTSelect :: (tn ~ SmNameT, t ~ SmTerm, Name tn, Term t) => SmSelectRT tn t -> SmRef 

Instances

Instances details
Show SmRef Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmRef -> ShowS #

show :: SmRef -> String #

showList :: [SmRef] -> ShowS #

Tree SmRef Source # 
Instance details

Defined in HaScalaM.Instances.Ref

RefT SmRef Source # 
Instance details

Defined in HaScalaM.Instances.Ref

Stat s => Member SmNameT (SmPkgS SmRef s) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Methods

name :: SmPkgS SmRef s -> SmNameT Source #

Stat s => Tree (SmPkgS SmRef s :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Stat s => WithExprs s (SmPkgS SmRef s) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Methods

exprs :: SmPkgS SmRef s -> [s] Source #

Stat s => WithStats s (SmPkgS SmRef s) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Methods

stats :: SmPkgS SmRef s -> [s] Source #

Stat s => MemberT SmNameT (SmPkgS SmRef s) Source # 
Instance details

Defined in HaScalaM.Instances.Stat

data SmRef' where Source #

Constructors

RT'Name :: SmNameT' -> SmRef' 
RT'Ref :: (t'n ~ SmNameT', t' ~ SmType', r ~ SmRef) => SmRefT' t'n t' r -> SmRef' 

Instances

Instances details
Show SmRef' Source # 
Instance details

Defined in HaScalaM.Instances.Show

Tree SmRef' Source # 
Instance details

Defined in HaScalaM.Instances.Ref

RefT' SmRef' Source # 
Instance details

Defined in HaScalaM.Instances.Ref

data SmSelf n t' where Source #

Constructors

SmSelf 

Fields

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

(Name n, Type' t') => Member n (SmSelf n t') Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Methods

name :: SmSelf n t' -> n Source #

(Name n, Type' t') => Tree (SmSelf n t' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

(Name n, Type' t') => WithDeclTpeOpt t' (SmSelf n t') Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

Methods

decltpe' :: SmSelf n t' -> Maybe t' Source #

(n ~ SmName, t' ~ SmType') => Show (SmSelf n t') Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmSelf n t' -> ShowS #

show :: SmSelf n t' -> String #

showList :: [SmSelf n t'] -> ShowS #

data SmStat where Source #

Constructors

S'' :: String -> SmStat 
SCtorSecondary :: (m ~ SmMod, n ~ SmName, p ~ SmParamT m n t' t, t' ~ SmType', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, s ~ SmStat, ParamClauseT m n p t' t pc, Init m n t' t ac i, Stat s) => SmCtorSecondaryS m n p t' t pc ac i s -> SmStat 
SDef' :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => SmDef'S m n tn p p' t' b' t pc pc' g -> SmStat 
SGiven' :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => SmGiven'S m n tn p p' t' b' t pc pc' g -> SmStat 
SType' :: (m ~ SmMod, n ~ SmName, t'n ~ SmNameT', p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', pc' ~ SmParamClauseT' m n p' t' b', NameT' t'n, ParamClauseT' m n p' t' b' pc') => SmType'S m n t'n p' t' b' pc' -> SmStat 
SVal' :: (m ~ SmMod, p ~ SmPat, t' ~ SmType', Mod m, Pat p, Type' t') => SmVal'S m p t' -> SmStat 
SVar' :: (m ~ SmMod, p ~ SmPat, t' ~ SmType', Mod m, Pat p, Type' t') => SmVar'S m p t' -> SmStat 
SClass :: (m ~ SmMod, n ~ SmName, t'n ~ SmNameT', p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', c ~ SmCtorPrimary m n p t' t pc, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, f ~ SmSelf n t', s ~ SmStat, e ~ SmTemplate m n t' t ac i f s, 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) => SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> SmStat 
SDef :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => SmDefS m n tn p p' t' b' t pc pc' g -> SmStat 
SEnum :: (m ~ SmMod, n ~ SmName, t'n ~ SmNameT', p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', c ~ SmCtorPrimary m n p t' t pc, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, f ~ SmSelf n t', s ~ SmStat, e ~ SmTemplate m n t' t ac i f s, 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) => SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> SmStat 
SEnumCase :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', c ~ SmCtorPrimary m n p t' t pc, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, NameT tn, ParamClauseT' m n p' t' b' pc', Primary m n p t' t pc c, Init m n t' t ac i) => SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i -> SmStat 
SExtensionGroup :: (m ~ SmMod, n ~ SmName, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', s ~ SmStat, g ~ SmParamClauseGroup m n p p' t' b' t pc pc', ParamClauseGroup m n p p' t' b' t pc pc' g, Stat s) => SmExtensionGroupS m n p p' t' b' t pc pc' s g -> SmStat 
SGiven :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', g ~ SmParamClauseGroup m n p p' t' b' t pc pc', ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, f ~ SmSelf n t', s ~ SmStat, e ~ SmTemplate m n t' t ac i f s, ParamClauseGroup m n p p' t' b' t pc pc' g, Template 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 -> SmStat 
SImpExp :: (r ~ SmRef, i ~ SmImportee, t ~ SmImporter r i, Importer r i t) => SmImportExportStatS r i t -> SmStat 
SGivenAlias :: (m ~ SmMod, n ~ SmName, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', g ~ SmParamClauseGroup m n p p' t' b' t pc pc', ParamClauseGroup m n p p' t' b' t pc pc' g) => SmGivenAliasS m n p p' t' b' t pc pc' g -> SmStat 
SMacro :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', g ~ SmParamClauseGroup m n p p' t' b' t pc pc', NameT tn, ParamClauseGroup m n p p' t' b' t pc pc' g) => SmMacroS m n tn p p' t' b' t pc pc' g -> SmStat 
SObject :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, t' ~ SmType', t ~ SmTerm, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, f ~ SmSelf n t', s ~ SmStat, e ~ SmTemplate m n t' t ac i f s, NameT tn, Template m n t' t ac i f s e) => SmObjectS m n tn t' t ac i f s e -> SmStat 
SPkg :: (r ~ SmRef, s ~ SmStat, RefT r, Stat s) => SmPkgS r s -> SmStat 
SPkgObject :: (m ~ SmMod, n ~ SmName, tn ~ SmNameT, p ~ SmParamT m n t' t, t' ~ SmType', t ~ SmTerm, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, f ~ SmSelf n t', s ~ SmStat, e ~ SmTemplate m n t' t ac i f s, NameT tn, Template m n t' t ac i f s e) => SmPkgObjectS m n tn t' t ac i f s e -> SmStat 
SRepeatedEnumCase :: (m ~ SmMod, tn ~ SmNameT, Mod m, NameT tn) => SmRepeatedEnumCase m tn -> SmStat 
STerm :: SmTerm -> SmStat 
STrait :: (m ~ SmMod, n ~ SmName, t'n ~ SmNameT', p ~ SmParamT m n t' t, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, pc' ~ SmParamClauseT' m n p' t' b', c ~ SmCtorPrimary m n p t' t pc, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, f ~ SmSelf n t', s ~ SmStat, e ~ SmTemplate m n t' t ac i f s, 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) => SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> SmStat 
SType :: (m ~ SmMod, n ~ SmName, t'n ~ SmNameT', p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', pc' ~ SmParamClauseT' m n p' t' b', NameT' t'n, ParamClauseT' m n p' t' b' pc') => SmTypeS m n t'n p' t' b' pc' -> SmStat 
SVal :: (m ~ SmMod, p ~ SmPat, t' ~ SmType', t ~ SmTerm, Mod m, Pat p, Type' t', Term t) => SmValS m p t' t -> SmStat 
SVar :: (m ~ SmMod, p ~ SmPat, t' ~ SmType', t ~ SmTerm, Mod m, Pat p, Type' t', Term t) => SmVarS m p t' t -> SmStat 

Instances

Instances details
Show SmStat Source # 
Instance details

Defined in HaScalaM.Instances.Show

Stat SmStat Source # 
Instance details

Defined in HaScalaM.Instances.Stat

Tree SmStat Source # 
Instance details

Defined in HaScalaM.Instances.Stat

data SmSource s where Source #

Constructors

SmSource 

Fields

Instances

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

Defined in HaScalaM.Instances.Tilde

Stat s => Tree (SmSource s :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Tilde

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

Defined in HaScalaM.Instances.Tilde

Methods

exprs :: SmSource s -> [s] Source #

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

Defined in HaScalaM.Instances.Tilde

Methods

stats :: SmSource s -> [s] Source #

Show (SmSource s) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmSource s -> ShowS #

show :: SmSource s -> String #

showList :: [SmSource s] -> ShowS #

data SmTemplate m n t' t ac i p s where Source #

Constructors

SmTemplate 

Fields

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 #

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

Defined in HaScalaM.Instances.Tilde

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

Defined in HaScalaM.Instances.Tilde

Methods

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

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

Defined in HaScalaM.Instances.Tilde

Methods

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

Show (SmTemplate m n t' t ac i p s) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmTemplate m n t' t ac i p s -> ShowS #

show :: SmTemplate m n t' t ac i p s -> String #

showList :: [SmTemplate m n t' t ac i p s] -> ShowS #

data SmTermT where Source #

Constructors

SmAnnotateT 

Fields

SmAnonymousFunctionT 

Fields

SmAscribeT 

Fields

SmEndMarkerT 

Fields

SmEtaT 

Fields

SmInterpolateT 

Fields

SmNewT 

Fields

SmPlaceholder :: SmTermT 
SmQuotedMacroExprT 

Fields

SmQuotedMacroType'T 

Fields

SmRepeatedT 

Fields

SmReturnT 

Fields

SmSplicedMacroExprT 

Fields

SmSplicedMacroPatT 

Fields

SmThrowT 

Fields

SmTryWithHandlerT 

Fields

SmXmlT 

Fields

data SmTerm where Source #

Constructors

T'' :: String -> SmTerm 
TApply :: (m ~ SmMod, t ~ SmTerm, ac ~ SmArgClauseT m t, ArgClauseT m t ac) => SmApplyT m t ac -> SmTerm 
TApplyInfix :: (m ~ SmMod, tn ~ SmNameT, t' ~ SmType', t ~ SmTerm, ac' ~ SmArgClauseT' t', ac ~ SmArgClauseT m t, NameT tn, ArgClauseT' t' ac', ArgClauseT m t ac) => SmApplyInfixT m tn t t' ac' ac -> SmTerm 
TApplyType' :: (t ~ SmTerm, t' ~ SmType', ac' ~ SmArgClauseT' t', Term t, ArgClauseT' t' ac') => SmApplyType'T t t' ac' -> SmTerm 
TAssign :: (t ~ SmTerm, Term t) => SmAssignT t -> SmTerm 
TBlock :: (s ~ SmStat, Stat s) => SmBlockT s -> SmTerm 
TContextFunction :: (m ~ SmMod, n ~ SmName, p ~ SmParamT m n t' t, t' ~ SmType', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, ParamClauseT m n p t' t pc) => SmContextFunctionT m n p t' t pc -> SmTerm 
TDo :: (t ~ SmTerm, Term t) => SmDoT t -> SmTerm 
TFor :: (e ~ SmEnumerator, t ~ SmTerm, Enumerator e, Term t) => SmForT e t -> SmTerm 
TForYield :: (e ~ SmEnumerator, t ~ SmTerm, Enumerator e, Term t) => SmForYieldT e t -> SmTerm 
TFunction :: (m ~ SmMod, n ~ SmName, p ~ SmParamT m n t' t, t' ~ SmType', t ~ SmTerm, pc ~ SmParamClauseT m n p t' t, ParamClauseT m n p t' t pc) => SmFunctionT m n p t' t pc -> SmTerm 
TIf :: (m ~ SmMod, t ~ SmTerm, Mod m, Term t) => SmIfT m t -> SmTerm 
TLit :: SmLit -> SmTerm 
TMatch :: (p ~ SmPat, t ~ SmTerm, ct ~ SmCaseCT p t, Case p t ct) => SmMatchT p t ct -> SmTerm 
TNewAnonymous :: (m ~ SmMod, n ~ SmName, t' ~ SmType', t ~ SmTerm, ac ~ SmArgClauseT m t, i ~ SmInit m n t' t ac, p ~ SmSelf n t', s ~ SmStat, e ~ SmTemplate m n t' t ac i p s, Template m n t' t ac i p s e) => SmNewAnonymousT m n t' t ac i p s e -> SmTerm 
TPartialFunction :: (p ~ SmPat, t ~ SmTerm, ct ~ SmCaseCT p t, Case p t ct) => SmPartialFunctionT p t ct -> SmTerm 
TPolyFunction :: (m ~ SmMod, n ~ SmName, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', pc' ~ SmParamClauseT' m n p' t' b', t ~ SmTerm, ParamClauseT' m n p' t' b' pc', Term t) => SmPolyFunctionT m n p' t' b' pc' t -> SmTerm 
TRef :: SmRef -> SmTerm 
TTerm :: SmTermT -> SmTerm 
TTry :: (p ~ SmPat, t ~ SmTerm, ct ~ SmCaseCT p t, Case p t ct) => SmTryT p t ct -> SmTerm 
TTuple :: (t ~ SmTerm, Term t) => SmTupleT t -> SmTerm 
TWhile :: (t ~ SmTerm, Term t) => SmWhileT t -> SmTerm 

Instances

Instances details
Show SmTerm Source # 
Instance details

Defined in HaScalaM.Instances.Show

Tree SmTerm Source # 
Instance details

Defined in HaScalaM.Instances.Term

Term SmTerm Source # 
Instance details

Defined in HaScalaM.Instances.Term

data SmArgClauseT m t where Source #

Constructors

SmArgClauseT 

Fields

Instances

Instances details
(m ~ SmMod, t ~ SmTerm, ArgsType m, Term t) => ArgClauseT m t (SmArgClauseT m t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

mod :: SmArgClauseT m t -> Maybe m Source #

(t ~ SmTerm, ArgsType m, Term t) => ArgClause t (SmArgClauseT m t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

(t ~ SmTerm, ArgsType m, Term t) => SyntaxValuesClauses t (SmArgClauseT m t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

values :: SmArgClauseT m t -> [t] Source #

(ArgsType m, Term t) => Tree (SmArgClauseT m t :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Term

(m ~ SmMod, t ~ SmTerm) => Show (SmArgClauseT m t) Source # 
Instance details

Defined in HaScalaM.Instances.Show

data SmParamT m n t' t where Source #

Constructors

SmParamT 

Fields

Instances

Instances details
(Mod m, Name n, Type' t', Term t) => Param m n (SmParamT m n t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

mods' :: SmParamT m n t' t -> [m] Source #

(Mod m, Name n, Type' t', Term t) => ParamT m n (SmParamT m n t' t) t' t Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

defaultOpt :: SmParamT m n t' t -> Maybe t Source #

(Mod m, Name n, Type' t', Term t) => Member n (SmParamT m n t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

name :: SmParamT m n t' t -> n Source #

(Mod m, Name n, Type' t', Term t) => Tree (SmParamT m n t' t :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Term

(Mod m, Name n, Type' t', Term t) => WithDeclTpeOpt t' (SmParamT m n t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

decltpe' :: SmParamT m n t' t -> Maybe t' Source #

(m ~ SmMod, n ~ SmName, t' ~ SmType', t ~ SmTerm) => Show (SmParamT m n t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmParamT m n t' t -> ShowS #

show :: SmParamT m n t' t -> String #

showList :: [SmParamT m n t' t] -> ShowS #

data SmParamClauseT m n p t' t where Source #

Constructors

SmParamClauseT 

Fields

Instances

Instances details
(p ~ SmParamT m n t' t, ParamsType m, ParamT m n p t' t) => ParamClauseT m n p t' t (SmParamClauseT m n p t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

mod' :: SmParamClauseT m n p t' t -> Maybe m Source #

(p ~ SmParamT m n t' t, ParamsType m, ParamT m n p t' t) => ParamClause m n p (SmParamClauseT m n p t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

(p ~ SmParamT m n t' t, ParamsType m, ParamT m n p t' t) => SyntaxValuesClauses p (SmParamClauseT m n p t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Term

Methods

values :: SmParamClauseT m n p t' t -> [p] Source #

(p ~ SmParamT m n t' t, ParamsType m, ParamT m n p t' t) => Tree (SmParamClauseT m n p t' t :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Term

(m ~ SmMod, t' ~ SmType', n ~ SmName, t ~ SmTerm, p ~ SmParamT m n t' t) => Show (SmParamClauseT m n p t' t) Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmParamClauseT m n p t' t -> ShowS #

show :: SmParamClauseT m n p t' t -> String #

showList :: [SmParamClauseT m n p t' t] -> ShowS #

data SmType'T' where Source #

Constructors

SmAndT' 

Fields

SmAnnotateT' 

Fields

SmAnonymousLambdaT' 

Fields

SmAnonymousNameT' :: SmType'T' 
SmAnonymousParamT' 

Fields

SmBlockT' 

Fields

SmByNameT' 

Fields

SmImplicitFunctionT' 

Fields

SmMethodT' 

Fields

SmOrT' 

Fields

SmRepeatedT' 

Fields

SmPatWildcardT' :: SmType'T' 
SmWithT' 

Fields

SmWildcardT' 

Fields

data SmType' where Source #

Constructors

T'Apply :: (n ~ SmName, t' ~ SmType', ac' ~ SmArgClauseT' t', ArgClauseT' t' ac') => SmApplyT' t' ac' -> SmType' 
T'ApplyInfix :: (t'n ~ SmNameT', t' ~ SmType', NameT' t'n, Type' t') => SmApplyInfixT' t'n t' -> SmType' 
T'ContextFunction :: (t' ~ SmType', Type' t') => SmContextFunctionT' t' -> SmType' 
T'Existential :: (t' ~ SmType', s ~ SmStat, Type' t', Stat s) => SmExistentialT' t' s -> SmType' 
T'Function :: (t' ~ SmType', Type' t') => SmFunctionT' t' -> SmType' 
T'Lambda :: (m ~ SmMod, n ~ SmName, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', pc' ~ SmParamClauseT' m n p' t' b', ParamClauseT' m n p' t' b' pc') => SmLambdaT' m n p' t' b' pc' -> SmType' 
T'Lit :: SmLit -> SmType' 
T'Macro :: (t ~ SmTerm, Term t) => SmMacroT' t -> SmType' 
T'Match :: (t' ~ SmType', ct ~ SmType'CaseCT t', Type'Case t' ct) => SmMatchT' t' ct -> SmType' 
T'PolyFunction :: (m ~ SmMod, n ~ SmName, p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', pc' ~ SmParamClauseT' m n p' t' b', ParamClauseT' m n p' t' b' pc') => SmPolyFunctionT' m n p' t' b' pc' -> SmType' 
T'Ref :: SmRef' -> SmType' 
T'Refine :: (t' ~ SmType', s ~ SmStat, Type' t', Stat s) => SmRefineT' t' s -> SmType' 
T'Tuple :: (t' ~ SmType', Type' t') => SmTupleT' t' -> SmType' 
T'Type' :: SmType'T' -> SmType' 
T'Var :: (t'n ~ SmNameT', NameT' t'n) => SmVarT' t'n -> SmType' 

Instances

Instances details
Show SmType' Source # 
Instance details

Defined in HaScalaM.Instances.Show

Tree SmType' Source # 
Instance details

Defined in HaScalaM.Instances.Type

Type' SmType' Source # 
Instance details

Defined in HaScalaM.Instances.Type

data SmArgClauseT' t' where Source #

Constructors

SmArgClauseT' 

Fields

Instances

Instances details
Type' t' => ArgClause t' (SmArgClauseT' t') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Type' t' => SyntaxValuesClauses t' (SmArgClauseT' t') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

values :: SmArgClauseT' t' -> [t'] Source #

Type' t' => Tree (SmArgClauseT' t' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Type

Type' t' => ArgClauseT' t' (SmArgClauseT' t') Source # 
Instance details

Defined in HaScalaM.Instances.Type

t' ~ SmType' => Show (SmArgClauseT' t') Source # 
Instance details

Defined in HaScalaM.Instances.Show

data SmBounds' t' where Source #

Constructors

SmBounds' 

Fields

Instances

Instances details
Type' t' => Tree (SmBounds' t' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Type

Type' t' => Bounds' t' (SmBounds' t') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

lo :: SmBounds' t' -> Maybe t' Source #

hi :: SmBounds' t' -> Maybe t' Source #

t' ~ SmType' => Show (SmBounds' t') Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmBounds' t' -> ShowS #

show :: SmBounds' t' -> String #

showList :: [SmBounds' t'] -> ShowS #

data SmType'Def m n t'n p' t' b' pc' where Source #

Constructors

T'DType' :: SmType'S m n t'n p' t' b' pc' -> SmType'Def m n t'n p' t' b' pc' 
T'DType :: SmTypeS m n t'n p' t' b' pc' -> SmType'Def m n t'n p' t' b' pc' 

Instances

Instances details
(NameT' t'n, ParamClauseT' m n p' t' b' pc') => Type'Def m n t'n p' t' b' pc' (SmType'Def m n t'n p' t' b' pc') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

bounds' :: SmType'Def m n t'n p' t' b' pc' -> b' Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc') => WithT'ParamClause m n p' t' b' pc' (SmType'Def m n t'n p' t' b' pc') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

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

(NameT' t'n, ParamClauseT' m n p' t' b' pc') => Member t'n (SmType'Def m n t'n p' t' b' pc') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

name :: SmType'Def m n t'n p' t' b' pc' -> t'n Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc') => Tree (SmType'Def m n t'n p' t' b' pc' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Type

(NameT' t'n, ParamClauseT' m n p' t' b' pc') => WithMods m (SmType'Def m n t'n p' t' b' pc') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

mods :: SmType'Def m n t'n p' t' b' pc' -> [m] Source #

(NameT' t'n, ParamClauseT' m n p' t' b' pc') => MemberT' t'n (SmType'Def m n t'n p' t' b' pc') Source # 
Instance details

Defined in HaScalaM.Instances.Type

(m ~ SmMod, n ~ SmName, t'n ~ SmNameT', p' ~ SmParamT' m n t' b', t' ~ SmType', b' ~ SmBounds' t', pc' ~ SmParamClauseT' m n p' t' b') => Show (SmType'Def m n t'n p' t' b' pc') Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmType'Def m n t'n p' t' b' pc' -> ShowS #

show :: SmType'Def m n t'n p' t' b' pc' -> String #

showList :: [SmType'Def m n t'n p' t' b' pc'] -> ShowS #

data SmParamT' m n t' b' where Source #

Constructors

SmParamT' 

Fields

Instances

Instances details
(p' ~ SmParamT' m n t' b', pc' ~ SmParamClauseT' m n p' t' b', Mod m, Name n, Bounds' t' b', ParamT' m n p' t' b' pc', ParamClauseT' m n p' t' b' pc') => WithT'ParamClause m n p' t' b' pc' (SmParamT' m n t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

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

(Mod m, Name n, Bounds' t' b') => Param m n (SmParamT' m n t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

mods' :: SmParamT' m n t' b' -> [m] Source #

(p' ~ SmParamT' m n t' b', pc' ~ SmParamClauseT' m n p' t' b', Mod m, Name n, Bounds' t' b') => ParamT' m n (SmParamT' m n t' b') t' b' pc' Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

tbounds' :: SmParamT' m n t' b' -> b' Source #

vbounds' :: SmParamT' m n t' b' -> [t'] Source #

cbounds' :: SmParamT' m n t' b' -> [t'] Source #

(Mod m, Name n, Bounds' t' b') => Member n (SmParamT' m n t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

name :: SmParamT' m n t' b' -> n Source #

(Mod m, Name n, Bounds' t' b') => Tree (SmParamT' m n t' b' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Type

(m ~ SmMod, n ~ SmName, t' ~ SmType', b' ~ SmBounds' t', p' ~ SmParamT' m n t' b', pc' ~ SmParamClauseT' m n p' t' b') => Show (SmParamT' m n t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmParamT' m n t' b' -> ShowS #

show :: SmParamT' m n t' b' -> String #

showList :: [SmParamT' m n t' b'] -> ShowS #

data SmParamClauseT' m n p' t' b' where Source #

Constructors

SmParamClauseT' 

Fields

Instances

Instances details
(p' ~ SmParamT' m n t' b', Mod m, Name n, Bounds' t' b') => ParamClauseT' m n p' t' b' (SmParamClauseT' m n p' t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Type

(p' ~ SmParamT' m n t' b', Mod m, Name n, Bounds' t' b') => ParamClause m n p' (SmParamClauseT' m n p' t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Type

(p' ~ SmParamT' m n t' b', Mod m, Name n, Bounds' t' b') => SyntaxValuesClauses p' (SmParamClauseT' m n p' t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Type

Methods

values :: SmParamClauseT' m n p' t' b' -> [p'] Source #

(Mod m, Name n, Bounds' t' b') => Tree (SmParamClauseT' m n p' t' b' :: Type) Source # 
Instance details

Defined in HaScalaM.Instances.Type

(m ~ SmMod, n ~ SmName, t' ~ SmType', b' ~ SmBounds' t', p' ~ SmParamT' m n t' b') => Show (SmParamClauseT' m n p' t' b') Source # 
Instance details

Defined in HaScalaM.Instances.Show

Methods

showsPrec :: Int -> SmParamClauseT' m n p' t' b' -> ShowS #

show :: SmParamClauseT' m n p' t' b' -> String #

showList :: [SmParamClauseT' m n p' t' b'] -> ShowS #