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

Data.Type.Witness.Specific.Empty

Documentation

newtype EmptyType t Source #

Constructors

MkEmptyType Void 

Instances

Instances details
WitnessConstraint (c :: k -> Constraint) (EmptyType :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Methods

witnessConstraint :: forall (t :: k0). EmptyType t -> Dict (c t) Source #

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

Defined in Data.Type.Witness.Specific.Empty

Methods

testEquality :: forall (a :: k0) (b :: k0). EmptyType a -> EmptyType b -> Maybe (a :~: b) #

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 #

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

Defined in Data.Type.Witness.Specific.Empty

Associated Types

type WitnessTypeList EmptyType :: [k] Source #

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

Defined in Data.Type.Witness.Specific.Empty

Methods

testCompare :: forall (a :: k0) (b :: k0). EmptyType a -> EmptyType b -> WOrdering a b Source #

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

Defined in Data.Type.Witness.Specific.Empty

Countable (EmptyType t) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Empty (EmptyType t) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Methods

never :: EmptyType t -> a #

Finite (EmptyType t) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Methods

allValues :: [EmptyType t] #

assemble :: forall b f. Applicative f => (EmptyType t -> f b) -> f (EmptyType t -> b) #

Searchable (EmptyType t) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Methods

search :: (EmptyType t -> Maybe b) -> Maybe b #

Eq (EmptyType t) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Methods

(==) :: EmptyType t -> EmptyType t -> Bool #

(/=) :: EmptyType t -> EmptyType t -> Bool #

type WitnessTypeList (EmptyType :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

type WitnessTypeList (EmptyType :: k -> Type) = '[] :: [k]