Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Coformat.Variables
Documentation
data KnownVariateType Source #
Constructors
Categorical | |
Integral |
class Variate a where Source #
Associated Types
type VariateResult a :: Type -> Type Source #
type VariateType a :: KnownVariateType Source #
Instances
Variate Bool Source # | |
Defined in Language.Coformat.Variables Associated Types type VariateResult Bool :: Type -> Type Source # type VariateType Bool :: KnownVariateType Source # | |
Variate Int Source # | |
Defined in Language.Coformat.Variables Associated Types type VariateResult Int :: Type -> Type Source # type VariateType Int :: KnownVariateType Source # | |
Variate Natural Source # | |
Defined in Language.Coformat.Variables Associated Types type VariateResult Natural :: Type -> Type Source # type VariateType Natural :: KnownVariateType Source # | |
Variate EnumVar Source # | |
Defined in Language.Coformat.Variables Associated Types type VariateResult EnumVar :: Type -> Type Source # type VariateType EnumVar :: KnownVariateType Source # |
data Variable varTy where Source #
Constructors
MkDV :: (Variate a, VariateType a ~ varTy, Foldable (VariateResult a)) => a -> Variable varTy |
data IxedVariable varTy Source #
Constructors
IxedVariable | |
Fields
|
type CategoricalVariate a = (Variate a, VariateType a ~ Categorical) Source #
searchSpace :: Show a => Integral a => a -> [a] Source #
type IntegralVariate a = (Variate a, VariateType a ~ Integral) Source #
type IntegralVariable = Variable Integral Source #
data SomeIxedVariable :: Type where Source #
Constructors
SomeIxedVariable :: IxedVariable varTy -> SomeIxedVariable |
asSome :: [IxedVariable varTy] -> [SomeIxedVariable] Source #