witness-0.6.2: values that witness types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Type.Witness.General.Finite

Documentation

class FiniteWitness (w :: k -> Type) where Source #

Methods

assembleAllFor :: forall (m :: Type -> Type) (f :: k -> Type). Applicative m => (forall (t :: k). w t -> m (f t)) -> m (AllFor f w) Source #

Instances

Instances details
FiniteWitness (EmptyType :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Methods

assembleAllFor :: Applicative m => (forall (t :: k0). EmptyType t -> m (f t)) -> m (AllFor f EmptyType) Source #

FiniteWitness ((:~:) t :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.General.Finite

Methods

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 # 
Instance details

Defined in Data.Type.Witness.Specific.Either

Methods

assembleAllFor :: Applicative m => (forall (t :: k0). EitherType p q t -> m (f t)) -> m (AllFor f (EitherType p q)) 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 # 
Instance details

Methods

showsPrec :: Int -> AllOf w -> ShowS #

show :: AllOf w -> String #

showList :: [AllOf w] -> ShowS #

(TestEquality w, FiniteWitness w) => Countable (Some w) Source # 
Instance details

Methods

countPrevious :: Some w -> Maybe (Some w) #

countMaybeNext :: Maybe (Some w) -> Maybe (Some w) #

(TestEquality w, FiniteWitness w) => Finite (Some w) Source # 
Instance details

Methods

allValues :: [Some w] #

assemble :: forall b f. Applicative f => (Some w -> f b) -> f (Some w -> b) #

(TestEquality w, FiniteWitness w) => Searchable (Some w) Source # 
Instance details

Methods

search :: (Some w -> Maybe b) -> Maybe b #