witness-0.4: values that witness types

Safe HaskellSafe
LanguageHaskell98

Data.Witness.List

Synopsis

Documentation

data ListType w lt where Source #

a witness type for HList-style lists. 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

TestEquality * w => TestEquality * (ListType w) Source # 

Methods

testEquality :: f a -> f b -> Maybe ((ListType w :~: a) b) #

Representative * w => Representative * (ListType w) Source # 

Methods

getRepWitness :: rep a -> Dict (Is (ListType w) rep a) Source #

Eq1 * w => Eq1 * (ListType w) Source # 

Methods

equals1 :: p a -> p a -> Bool Source #

Representative * w => Is * (ListType w) () Source # 

Methods

representative :: () a Source #

(Is * w a, Is * (ListType w) lt) => Is * (ListType w) (a, lt) Source # 

Methods

representative :: (a, lt) a Source #

Eq1 * w => Eq (ListType w a) Source # 

Methods

(==) :: ListType w a -> ListType w a -> Bool #

(/=) :: ListType w a -> ListType w a -> Bool #

listFill :: ListType w t -> (forall a. w a -> a) -> t Source #

listMap :: ListType w t -> (forall a. w a -> a -> a) -> t -> t Source #

listLift2 :: ListType w t -> (forall a. w a -> a -> a -> a) -> t -> t -> t Source #

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

listTypeMap :: (forall a. w1 a -> w2 a) -> ListType w1 t -> ListType w2 t Source #

data AppendList w la lb Source #

Constructors

MkAppendList 

Fields

appendList :: ListType w la -> ListType w lb -> AppendList w la lb Source #

data AddItemList w a l Source #

Constructors

MkAddItemList 

Fields

addListItem :: w a -> ListType w l -> AddItemList w a l Source #

data MergeItemList w a l Source #

Constructors

MkMergeItemList 

Fields

data MergeList w la lb Source #

Constructors

MkMergeList 

Fields

mergeList :: TestEquality w => ListType w la -> ListType w lb -> MergeList w la lb Source #

type MapWitness cc w1 w2 = forall r v1. w1 v1 -> (forall v2. w2 v2 -> cc v1 v2 -> r) -> r Source #

sameMapWitness :: (forall v. w v -> cc v v) -> MapWitness cc w w Source #

data MapList cc w2 l Source #

Constructors

MkMapList 

Fields

mapList :: Tensor cc => MapWitness cc w1 w2 -> ListType w1 l -> MapList cc w2 l Source #

data RemoveFromList w a l Source #

Constructors

MkRemoveFromList 

Fields

data RemoveManyFromList wit lx l Source #

Constructors

MkRemoveManyFromList 

Fields

newtype EitherWitness w1 w2 a Source #

Constructors

MkEitherWitness (Either (w1 a) (w2 a)) 

Instances

(TestEquality k w1, TestEquality k w2) => TestEquality k (EitherWitness k w1 w2) Source # 

Methods

testEquality :: f a -> f b -> Maybe ((EitherWitness k w1 w2 :~: a) b) #

data PartitionList wit1 wit2 l Source #

Constructors

MkPartitionList 

Fields