Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
class FiniteWitness (w :: k -> Type) where Source #
assembleAllFor :: forall (m :: Type -> Type) (f :: k -> Type). Applicative m => (forall (t :: k). w t -> m (f t)) -> m (AllFor f w) Source #
Instances
FiniteWitness (EmptyType :: k -> Type) Source # | |
Defined in Data.Type.Witness.Specific.Empty assembleAllFor :: Applicative m => (forall (t :: k0). EmptyType t -> m (f t)) -> m (AllFor f EmptyType) Source # | |
FiniteWitness ((:~:) t :: k -> Type) Source # | |
Defined in Data.Type.Witness.General.Finite assembleAllFor :: Applicative m => (forall (t0 :: k0). (t :~: t0) -> m (f t0)) -> m (AllFor f ((:~:) t)) Source # | |
(FiniteWitness p, FiniteWitness q) => FiniteWitness (EitherType p q :: k -> Type) Source # | |
Defined in Data.Type.Witness.Specific.Either assembleAllFor :: Applicative m => (forall (t :: k0). EitherType p q t -> m (f t)) -> m (AllFor f (EitherType p q)) Source # |
allWitnesses :: FiniteWitness w => [Some w] Source #
allForCodomain :: FiniteWitness w => AllFor f w -> [Some f] Source #
assembleAllOf :: (FiniteWitness w, Applicative m) => (forall t. w t -> m t) -> m (AllOf w) Source #
Orphan instances
(FiniteWitness w, AllConstraint Show w, WitnessConstraint Show w) => Show (AllOf w) Source # | |
(TestEquality w, FiniteWitness w) => Countable (Some w) Source # | |
(TestEquality w, FiniteWitness w) => Finite (Some w) Source # | |
(TestEquality w, FiniteWitness w) => Searchable (Some w) Source # | |