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

Data.Type.Witness.Specific.List.List

Synopsis

Documentation

data ListType w lt where Source #

a witness type for lists of types The w parameter is the witness type of the elements.

Constructors

NilListType :: ListType w '[] 
ConsListType :: w a -> ListType w lt -> ListType w (a ': lt) 

Instances

Instances details
TestEquality w => TestEquality (ListType w :: [k] -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.List.List

Methods

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

Representative w => Representative (ListType w :: [k] -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.List.List

Representative w => Is (ListType w :: [k] -> Type) ('[] :: [k]) Source # 
Instance details

Defined in Data.Type.Witness.Specific.List.List

(Is w a2, Is (ListType w) lt) => Is (ListType w :: [a1] -> Type) (a2 ': lt :: [a1]) Source # 
Instance details

Defined in Data.Type.Witness.Specific.List.List

Methods

representative :: ListType w (a2 ': lt) Source #

(forall (a :: k). Show (w a)) => Show (ListType w lt) Source # 
Instance details

Defined in Data.Type.Witness.Specific.List.List

Methods

showsPrec :: Int -> ListType w lt -> ShowS #

show :: ListType w lt -> String #

showList :: [ListType w lt] -> ShowS #

mapMListType :: Applicative m => (forall t'. wita t' -> m (witb t')) -> ListType wita t -> m (ListType witb t) Source #

joinMListType :: Applicative m => (forall t'. wita t' -> witb t' -> m (witc t')) -> ListType wita t -> ListType witb t -> m (ListType witc t) Source #

mapListType :: (forall t'. wita t' -> witb t') -> ListType wita t -> ListType witb t Source #

joinListType :: (forall t'. wita t' -> witb t' -> witc t') -> ListType wita t -> ListType witb t -> ListType witc t Source #

pairListType :: ListType wita t -> ListType witb t -> ListType (PairType wita witb) t Source #

listTypeToList :: (forall a. w a -> r) -> ListType w t -> [r] Source #

listTypeFor :: Applicative m => ListType w t -> (forall a. w a -> m r) -> m [r] Source #

listTypeFor_ :: Applicative m => ListType w t -> (forall a. w a -> m ()) -> m () Source #

listTypeToFixedList :: (forall a. w a -> r) -> ListType w t -> FixedList (ListLength t) r Source #

listTypeFromFixedList :: FixedList n (Some w) -> (forall t. n ~ ListLength t => ListType w t -> r) -> r Source #