module HaScalaM.Types.Stat where
import HaScalaM.Classes
import HaScalaM.Classes.Base
import HaScalaM.Classes.Pat
import HaScalaM.Classes.Ref
import HaScalaM.Classes.Stat
import HaScalaM.Classes.Term
import HaScalaM.Classes.Type
data SmDef'S m n tn p p' t' b' t pc pc' g where
SmDef'S :: ( NameT tn
, ParamClauseGroup m n p p' t' b' t pc pc' g
) => { forall tn m n p p' t' b' t pc pc' g.
SmDef'S m n tn p p' t' b' t pc pc' g -> [m]
modsD'S :: [m]
, forall tn m n p p' t' b' t pc pc' g.
SmDef'S m n tn p p' t' b' t pc pc' g -> tn
nameD'S :: tn
, forall tn m n p p' t' b' t pc pc' g.
SmDef'S m n tn p p' t' b' t pc pc' g -> [g]
paramClauseGroupsD'S :: [g]
, forall tn m n p p' t' b' t pc pc' g.
SmDef'S m n tn p p' t' b' t pc pc' g -> t'
decltpeD'S :: t' } -> SmDef'S m n tn p p' t' b' t pc pc' g
data SmGiven'S m n tn p p' t' b' t pc pc' g where
SmGiven'S :: ( NameT tn
, ParamClauseGroup m n p p' t' b' t pc pc' g
) => { forall tn m n p p' t' b' t pc pc' g.
SmGiven'S m n tn p p' t' b' t pc pc' g -> [m]
modsG'S :: [m]
, forall tn m n p p' t' b' t pc pc' g.
SmGiven'S m n tn p p' t' b' t pc pc' g -> tn
nameG'S :: tn
, forall tn m n p p' t' b' t pc pc' g.
SmGiven'S m n tn p p' t' b' t pc pc' g -> Maybe g
paramClauseGroupOptG'S :: Maybe g
, forall tn m n p p' t' b' t pc pc' g.
SmGiven'S m n tn p p' t' b' t pc pc' g -> t'
decltpeG'S :: t' } -> SmGiven'S m n tn p p' t' b' t pc pc' g
data SmType'S m n t'n p' t' b' pc' where
SmType'S :: ( NameT' t'n
, ParamClauseT' m n p' t' b' pc'
) => { forall t'n m n p' t' b' pc'. SmType'S m n t'n p' t' b' pc' -> [m]
modsT'S :: [m]
, forall t'n m n p' t' b' pc'. SmType'S m n t'n p' t' b' pc' -> t'n
nameT'S :: t'n
, forall t'n m n p' t' b' pc'. SmType'S m n t'n p' t' b' pc' -> pc'
t'paramClauseT'S :: pc'
, forall t'n m n p' t' b' pc'. SmType'S m n t'n p' t' b' pc' -> b'
boundsT'S :: b' } -> SmType'S m n t'n p' t' b' pc'
data SmVal'S m p t' where
SmVal'S :: ( Mod m
, Pat p
, Type' t'
) => { forall m p t'. SmVal'S m p t' -> [m]
modsVal'S :: [m]
, forall m p t'. SmVal'S m p t' -> [p]
patsVal'S :: [p]
, forall m p t'. SmVal'S m p t' -> t'
decltpeVal'S :: t' } -> SmVal'S m p t'
data SmVar'S m p t' where
SmVar'S :: ( Mod m
, Pat p
, Type' t'
) => { forall m p t'. SmVar'S m p t' -> [m]
modsVar'S :: [m]
, forall m p t'. SmVar'S m p t' -> [p]
patsVar'S :: [p]
, forall m p t'. SmVar'S m p t' -> t'
decltpeVar'S :: t' } -> SmVar'S m p t'
data SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e where
SmClassS :: ( 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
) => { forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> [m]
modsCS :: [m]
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> t'n
nameCS :: t'n
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> pc'
t'paramClauseCS :: pc'
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> c
ctorCS :: c
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e -> e
templCS :: e } -> SmClassS m n t'n p p' t' b' t pc pc' c ac i f s e
data SmDefS m n tn p p' t' b' t pc pc' g where
SmDefS :: ( NameT tn
, ParamClauseGroup m n p p' t' b' t pc pc' g
) => { forall tn m n p p' t' b' t pc pc' g.
SmDefS m n tn p p' t' b' t pc pc' g -> [m]
modsDS :: [m]
, forall tn m n p p' t' b' t pc pc' g.
SmDefS m n tn p p' t' b' t pc pc' g -> tn
nameDS :: tn
, forall tn m n p p' t' b' t pc pc' g.
SmDefS m n tn p p' t' b' t pc pc' g -> [g]
paramClauseGroupsDS :: [g]
, forall tn m n p p' t' b' t pc pc' g.
SmDefS m n tn p p' t' b' t pc pc' g -> Maybe t'
decltpeOptDS :: Maybe t'
, forall tn m n p p' t' b' t pc pc' g.
SmDefS m n tn p p' t' b' t pc pc' g -> t
bodyDS :: t } -> SmDefS m n tn p p' t' b' t pc pc' g
data m n t'n p p' t' b' t pc pc' c ac i f s e where
:: ( 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
) => { forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> [m]
modsES :: [m]
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> t'n
nameES :: t'n
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> pc'
t'paramClauseES :: pc'
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> c
ctorES :: c
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e -> e
templES :: e } -> SmEnumS m n t'n p p' t' b' t pc pc' c ac i f s e
data m n tn p p' t' b' t pc pc' c ac i where
:: ( NameT tn
, ParamClauseT' m n p' t' b' pc'
, Primary m n p t' t pc c
, Init m n t' t ac i
) => { forall tn m n p' t' b' pc' p t pc c ac i.
SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i -> [m]
modsECS :: [m]
, forall tn m n p' t' b' pc' p t pc c ac i.
SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i -> tn
nameECS :: tn
, forall tn m n p' t' b' pc' p t pc c ac i.
SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i -> pc'
t'paramClauseECS :: pc'
, forall tn m n p' t' b' pc' p t pc c ac i.
SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i -> c
ctorECS :: c
, forall tn m n p' t' b' pc' p t pc c ac i.
SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i -> [i]
initsECS :: [i] } -> SmEnumCaseS m n tn p p' t' b' t pc pc' c ac i
data SmExtensionGroupS m n p p' t' b' t pc pc' s g where
SmExtensionGroupS :: ( ParamClauseGroup m n p p' t' b' t pc pc' g
, Stat s
) => { forall m n p p' t' b' t pc pc' g s.
SmExtensionGroupS m n p p' t' b' t pc pc' s g -> Maybe g
paramClauseGroupOptEGS :: Maybe g
, forall m n p p' t' b' t pc pc' g s.
SmExtensionGroupS m n p p' t' b' t pc pc' s g -> s
bodyEGS :: s } -> SmExtensionGroupS m n p p' t' b' t pc pc' s g
data SmGivenS m n p p' t' b' t pc pc' ac i f s e g where
SmGivenS :: ( ParamClauseGroup m n p p' t' b' t pc pc' g
, Template m n t' t ac i f s e
) => { forall m n p p' t' b' t pc pc' g ac i f s e.
SmGivenS m n p p' t' b' t pc pc' ac i f s e g -> [m]
modsGS :: [m]
, forall m n p p' t' b' t pc pc' g ac i f s e.
SmGivenS m n p p' t' b' t pc pc' ac i f s e g -> n
nameGS :: n
, forall m n p p' t' b' t pc pc' g ac i f s e.
SmGivenS m n p p' t' b' t pc pc' ac i f s e g -> Maybe g
paramClauseGroupOptGS :: Maybe g
, forall m n p p' t' b' t pc pc' g ac i f s e.
SmGivenS m n p p' t' b' t pc pc' ac i f s e g -> e
templGS :: e } -> SmGivenS m n p p' t' b' t pc pc' ac i f s e g
data SmGivenAliasS m n p p' t' b' t pc pc' g where
SmGivenAliasS :: ParamClauseGroup m n p p' t' b' t pc pc' g => { forall m n p p' t' b' t pc pc' g.
SmGivenAliasS m n p p' t' b' t pc pc' g -> [m]
modsGAS :: [m]
, forall m n p p' t' b' t pc pc' g.
SmGivenAliasS m n p p' t' b' t pc pc' g -> n
nameGAS :: n
, forall m n p p' t' b' t pc pc' g.
SmGivenAliasS m n p p' t' b' t pc pc' g -> Maybe g
paramClauseGroupOptGAS :: Maybe g
, forall m n p p' t' b' t pc pc' g.
SmGivenAliasS m n p p' t' b' t pc pc' g -> t'
decltpeGAS :: t'
, forall m n p p' t' b' t pc pc' g.
SmGivenAliasS m n p p' t' b' t pc pc' g -> t
bodyGAS :: t } -> SmGivenAliasS m n p p' t' b' t pc pc' g
data SmMacroS m n tn p p' t' b' t pc pc' g where
SmMacroS :: ( NameT tn
, ParamClauseGroup m n p p' t' b' t pc pc' g
) => { forall tn m n p p' t' b' t pc pc' g.
SmMacroS m n tn p p' t' b' t pc pc' g -> [m]
modsMS :: [m]
, forall tn m n p p' t' b' t pc pc' g.
SmMacroS m n tn p p' t' b' t pc pc' g -> tn
nameMS :: tn
, forall tn m n p p' t' b' t pc pc' g.
SmMacroS m n tn p p' t' b' t pc pc' g -> [g]
paramClauseGroupsMS :: [g]
, forall tn m n p p' t' b' t pc pc' g.
SmMacroS m n tn p p' t' b' t pc pc' g -> Maybe t'
decltpeOptMS :: Maybe t'
, forall tn m n p p' t' b' t pc pc' g.
SmMacroS m n tn p p' t' b' t pc pc' g -> t
bodyMS :: t } -> SmMacroS m n tn p p' t' b' t pc pc' g
data SmObjectS m n tn t' t ac i f s e where
SmObjectS :: ( NameT tn
, Template m n t' t ac i f s e
) => { forall tn m n t' t ac i f s e.
SmObjectS m n tn t' t ac i f s e -> [m]
modsOS :: [m]
, forall tn m n t' t ac i f s e.
SmObjectS m n tn t' t ac i f s e -> tn
nameOS :: tn
, forall tn m n t' t ac i f s e.
SmObjectS m n tn t' t ac i f s e -> e
templOS :: e } -> SmObjectS m n tn t' t ac i f s e
data SmRepeatedEnumCase m tn where
SmRepeatedEnumCase :: ( Mod m
, NameT tn
) => { forall m tn. SmRepeatedEnumCase m tn -> [m]
modsRECS :: [m]
, forall m tn. SmRepeatedEnumCase m tn -> [tn]
cases :: [tn] } -> SmRepeatedEnumCase m tn
data SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e where
SmTraitS :: ( 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
) => { forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> [m]
modsTS :: [m]
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> t'n
nameTS :: t'n
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> pc'
t'paramClauseTS :: pc'
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> c
ctorTS :: c
, forall t'n m n p' t' b' pc' p t pc c ac i f s e.
SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e -> e
templTS :: e } -> SmTraitS m n t'n p p' t' b' t pc pc' c ac i f s e
data SmTypeS m n t'n p' t' b' pc' where
SmTypeS :: ( NameT' t'n
, ParamClauseT' m n p' t' b' pc'
) => { forall t'n m n p' t' b' pc'. SmTypeS m n t'n p' t' b' pc' -> [m]
modsTpeS :: [m]
, forall t'n m n p' t' b' pc'. SmTypeS m n t'n p' t' b' pc' -> t'n
nameTpeS :: t'n
, forall t'n m n p' t' b' pc'. SmTypeS m n t'n p' t' b' pc' -> pc'
t'paramClauseTpeS :: pc'
, forall t'n m n p' t' b' pc'. SmTypeS m n t'n p' t' b' pc' -> t'
bodyTpeS :: t'
, forall t'n m n p' t' b' pc'. SmTypeS m n t'n p' t' b' pc' -> b'
boundsTpeS :: b' } -> SmTypeS m n t'n p' t' b' pc'
data SmValS m p t' t where
SmValS :: ( Mod m
, Pat p
, Type' t'
, Term t
) => { forall m p t' t. SmValS m p t' t -> [m]
modsValS :: [m]
, forall m p t' t. SmValS m p t' t -> [p]
patsValS :: [p]
, forall m p t' t. SmValS m p t' t -> Maybe t'
decltpeOptValS :: Maybe t'
, forall m p t' t. SmValS m p t' t -> t
rhsValS :: t } -> SmValS m p t' t
data SmVarS m p t' t where
SmVarS :: ( Mod m
, Pat p
, Type' t'
, Term t
) => { forall m p t' t. SmVarS m p t' t -> [m]
modsVarS :: [m]
, forall m p t' t. SmVarS m p t' t -> [p]
patsVarS :: [p]
, forall m p t' t. SmVarS m p t' t -> Maybe t'
decltpeOptVarS :: Maybe t'
, forall m p t' t. SmVarS m p t' t -> t
rhsVarS :: t } -> SmVarS m p t' t
data SmImportExportStatS r i t where
SmImportS :: Importer r i t => { forall r i t. SmImportExportStatS r i t -> [t]
importersIIESS :: [t] } -> SmImportExportStatS r i t
SmExportS :: Importer r i t => { forall r i t. SmImportExportStatS r i t -> [t]
importersIEESS :: [t] } -> SmImportExportStatS r i t
data SmPkgS r s where
SmPkgS :: ( RefT r
, Stat s
) => { forall r s. SmPkgS r s -> r
refPkS :: r
, forall r s. SmPkgS r s -> [s]
statsPkS :: [s] } -> SmPkgS r s
data SmPkgObjectS m n tn t' t ac i f s e where
SmPkgObjectS :: ( NameT tn
, Template m n t' t ac i f s e
) => { forall tn m n t' t ac i f s e.
SmPkgObjectS m n tn t' t ac i f s e -> [m]
modsPkObjS :: [m]
, forall tn m n t' t ac i f s e.
SmPkgObjectS m n tn t' t ac i f s e -> tn
namePkObjS :: tn
, forall tn m n t' t ac i f s e.
SmPkgObjectS m n tn t' t ac i f s e -> e
templPkObjS :: e } -> SmPkgObjectS m n tn t' t ac i f s e