subcategories-0.1.0.0: Subcategories induced by class constraints

Safe HaskellNone
LanguageHaskell2010

Control.Subcategory.Zip

Documentation

class CSemialign f => CZip f where Source #

Minimal complete definition

czipWith

Methods

czipWith :: (Dom f a, Dom f b, Dom f c) => (a -> b -> c) -> f a -> f b -> f c Source #

czip :: (Dom f a, Dom f b, Dom f (a, b)) => f a -> f b -> f (a, b) Source #

Instances
CZip [] Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom [] a, Dom [] b, Dom [] c) => (a -> b -> c) -> [a] -> [b] -> [c] Source #

czip :: (Dom [] a, Dom [] b, Dom [] (a, b)) => [a] -> [b] -> [(a, b)] Source #

CZip Maybe Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Maybe a, Dom Maybe b, Dom Maybe c) => (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

czip :: (Dom Maybe a, Dom Maybe b, Dom Maybe (a, b)) => Maybe a -> Maybe b -> Maybe (a, b) Source #

CZip Option Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Option a, Dom Option b, Dom Option c) => (a -> b -> c) -> Option a -> Option b -> Option c Source #

czip :: (Dom Option a, Dom Option b, Dom Option (a, b)) => Option a -> Option b -> Option (a, b) Source #

CZip ZipList Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom ZipList a, Dom ZipList b, Dom ZipList c) => (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

czip :: (Dom ZipList a, Dom ZipList b, Dom ZipList (a, b)) => ZipList a -> ZipList b -> ZipList (a, b) Source #

CZip Identity Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Identity a, Dom Identity b, Dom Identity c) => (a -> b -> c) -> Identity a -> Identity b -> Identity c Source #

czip :: (Dom Identity a, Dom Identity b, Dom Identity (a, b)) => Identity a -> Identity b -> Identity (a, b) Source #

CZip NonEmpty Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom NonEmpty a, Dom NonEmpty b, Dom NonEmpty c) => (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

czip :: (Dom NonEmpty a, Dom NonEmpty b, Dom NonEmpty (a, b)) => NonEmpty a -> NonEmpty b -> NonEmpty (a, b) Source #

CZip IntMap Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom IntMap a, Dom IntMap b, Dom IntMap c) => (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c Source #

czip :: (Dom IntMap a, Dom IntMap b, Dom IntMap (a, b)) => IntMap a -> IntMap b -> IntMap (a, b) Source #

CZip Tree Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Tree a, Dom Tree b, Dom Tree c) => (a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

czip :: (Dom Tree a, Dom Tree b, Dom Tree (a, b)) => Tree a -> Tree b -> Tree (a, b) Source #

CZip Seq Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Seq a, Dom Seq b, Dom Seq c) => (a -> b -> c) -> Seq a -> Seq b -> Seq c Source #

czip :: (Dom Seq a, Dom Seq b, Dom Seq (a, b)) => Seq a -> Seq b -> Seq (a, b) Source #

CZip PrimArray Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom PrimArray a, Dom PrimArray b, Dom PrimArray c) => (a -> b -> c) -> PrimArray a -> PrimArray b -> PrimArray c Source #

czip :: (Dom PrimArray a, Dom PrimArray b, Dom PrimArray (a, b)) => PrimArray a -> PrimArray b -> PrimArray (a, b) Source #

CZip SmallArray Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom SmallArray a, Dom SmallArray b, Dom SmallArray c) => (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c Source #

czip :: (Dom SmallArray a, Dom SmallArray b, Dom SmallArray (a, b)) => SmallArray a -> SmallArray b -> SmallArray (a, b) Source #

CZip Array Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Array a, Dom Array b, Dom Array c) => (a -> b -> c) -> Array a -> Array b -> Array c Source #

czip :: (Dom Array a, Dom Array b, Dom Array (a, b)) => Array a -> Array b -> Array (a, b) Source #

CZip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Vector a, Dom Vector b, Dom Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

czip :: (Dom Vector a, Dom Vector b, Dom Vector (a, b)) => Vector a -> Vector b -> Vector (a, b) Source #

CZip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Vector a, Dom Vector b, Dom Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

czip :: (Dom Vector a, Dom Vector b, Dom Vector (a, b)) => Vector a -> Vector b -> Vector (a, b) Source #

CZip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Vector a, Dom Vector b, Dom Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

czip :: (Dom Vector a, Dom Vector b, Dom Vector (a, b)) => Vector a -> Vector b -> Vector (a, b) Source #

CZip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Vector a, Dom Vector b, Dom Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

czip :: (Dom Vector a, Dom Vector b, Dom Vector (a, b)) => Vector a -> Vector b -> Vector (a, b) Source #

CZip (Proxy :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom Proxy a, Dom Proxy b, Dom Proxy c) => (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

czip :: (Dom Proxy a, Dom Proxy b, Dom Proxy (a, b)) => Proxy a -> Proxy b -> Proxy (a, b) Source #

Ord k => CZip (Map k) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (Map k) a, Dom (Map k) b, Dom (Map k) c) => (a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

czip :: (Dom (Map k) a, Dom (Map k) b, Dom (Map k) (a, b)) => Map k a -> Map k b -> Map k (a, b) Source #

(Eq k, Hashable k) => CZip (HashMap k) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (HashMap k) a, Dom (HashMap k) b, Dom (HashMap k) c) => (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c Source #

czip :: (Dom (HashMap k) a, Dom (HashMap k) b, Dom (HashMap k) (a, b)) => HashMap k a -> HashMap k b -> HashMap k (a, b) Source #

Zip f => CZip (WrapFunctor f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (WrapFunctor f) a, Dom (WrapFunctor f) b, Dom (WrapFunctor f) c) => (a -> b -> c) -> WrapFunctor f a -> WrapFunctor f b -> WrapFunctor f c Source #

czip :: (Dom (WrapFunctor f) a, Dom (WrapFunctor f) b, Dom (WrapFunctor f) (a, b)) => WrapFunctor f a -> WrapFunctor f b -> WrapFunctor f (a, b) Source #

(IsSequence mono, MonoZip mono) => CZip (WrapMono mono :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (WrapMono mono) a, Dom (WrapMono mono) b, Dom (WrapMono mono) c) => (a -> b -> c) -> WrapMono mono a -> WrapMono mono b -> WrapMono mono c Source #

czip :: (Dom (WrapMono mono) a, Dom (WrapMono mono) b, Dom (WrapMono mono) (a, b)) => WrapMono mono a -> WrapMono mono b -> WrapMono mono (a, b) Source #

CZip f => CZip (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (CZippy f) a, Dom (CZippy f) b, Dom (CZippy f) c) => (a -> b -> c) -> CZippy f a -> CZippy f b -> CZippy f c Source #

czip :: (Dom (CZippy f) a, Dom (CZippy f) b, Dom (CZippy f) (a, b)) => CZippy f a -> CZippy f b -> CZippy f (a, b) Source #

CZip ((->) e :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom ((->) e) a, Dom ((->) e) b, Dom ((->) e) c) => (a -> b -> c) -> (e -> a) -> (e -> b) -> e -> c Source #

czip :: (Dom ((->) e) a, Dom ((->) e) b, Dom ((->) e) (a, b)) => (e -> a) -> (e -> b) -> e -> (a, b) Source #

(CZip f, CZip g) => CZip (f :*: g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (f :*: g) a, Dom (f :*: g) b, Dom (f :*: g) c) => (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c Source #

czip :: (Dom (f :*: g) a, Dom (f :*: g) b, Dom (f :*: g) (a, b)) => (f :*: g) a -> (f :*: g) b -> (f :*: g) (a, b) Source #

(CZip f, CZip g) => CZip (Product f g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (Product f g) a, Dom (Product f g) b, Dom (Product f g) c) => (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c Source #

czip :: (Dom (Product f g) a, Dom (Product f g) b, Dom (Product f g) (a, b)) => Product f g a -> Product f g b -> Product f g (a, b) Source #

(CZip f, CZip g) => CZip (f :.: g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (f :.: g) a, Dom (f :.: g) b, Dom (f :.: g) c) => (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c Source #

czip :: (Dom (f :.: g) a, Dom (f :.: g) b, Dom (f :.: g) (a, b)) => (f :.: g) a -> (f :.: g) b -> (f :.: g) (a, b) Source #

(CZip f, CZip g) => CZip (Compose f g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (Compose f g) a, Dom (Compose f g) b, Dom (Compose f g) c) => (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c Source #

czip :: (Dom (Compose f g) a, Dom (Compose f g) b, Dom (Compose f g) (a, b)) => Compose f g a -> Compose f g b -> Compose f g (a, b) Source #

class CZip f => CUnzip f where Source #

Minimal complete definition

cunzipWith

Methods

cunzip :: (Dom f (a, b), Dom f a, Dom f b) => f (a, b) -> (f a, f b) Source #

cunzipWith :: (Dom f c, Dom f a, Dom f b) => (c -> (a, b)) -> f c -> (f a, f b) Source #

Instances
CUnzip [] Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom [] (a, b), Dom [] a, Dom [] b) => [(a, b)] -> ([a], [b]) Source #

cunzipWith :: (Dom [] c, Dom [] a, Dom [] b) => (c -> (a, b)) -> [c] -> ([a], [b]) Source #

CUnzip Maybe Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Maybe (a, b), Dom Maybe a, Dom Maybe b) => Maybe (a, b) -> (Maybe a, Maybe b) Source #

cunzipWith :: (Dom Maybe c, Dom Maybe a, Dom Maybe b) => (c -> (a, b)) -> Maybe c -> (Maybe a, Maybe b) Source #

CUnzip Option Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Option (a, b), Dom Option a, Dom Option b) => Option (a, b) -> (Option a, Option b) Source #

cunzipWith :: (Dom Option c, Dom Option a, Dom Option b) => (c -> (a, b)) -> Option c -> (Option a, Option b) Source #

CUnzip ZipList Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom ZipList (a, b), Dom ZipList a, Dom ZipList b) => ZipList (a, b) -> (ZipList a, ZipList b) Source #

cunzipWith :: (Dom ZipList c, Dom ZipList a, Dom ZipList b) => (c -> (a, b)) -> ZipList c -> (ZipList a, ZipList b) Source #

CUnzip Identity Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Identity (a, b), Dom Identity a, Dom Identity b) => Identity (a, b) -> (Identity a, Identity b) Source #

cunzipWith :: (Dom Identity c, Dom Identity a, Dom Identity b) => (c -> (a, b)) -> Identity c -> (Identity a, Identity b) Source #

CUnzip NonEmpty Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom NonEmpty (a, b), Dom NonEmpty a, Dom NonEmpty b) => NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) Source #

cunzipWith :: (Dom NonEmpty c, Dom NonEmpty a, Dom NonEmpty b) => (c -> (a, b)) -> NonEmpty c -> (NonEmpty a, NonEmpty b) Source #

CUnzip IntMap Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom IntMap (a, b), Dom IntMap a, Dom IntMap b) => IntMap (a, b) -> (IntMap a, IntMap b) Source #

cunzipWith :: (Dom IntMap c, Dom IntMap a, Dom IntMap b) => (c -> (a, b)) -> IntMap c -> (IntMap a, IntMap b) Source #

CUnzip Tree Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Tree (a, b), Dom Tree a, Dom Tree b) => Tree (a, b) -> (Tree a, Tree b) Source #

cunzipWith :: (Dom Tree c, Dom Tree a, Dom Tree b) => (c -> (a, b)) -> Tree c -> (Tree a, Tree b) Source #

CUnzip Seq Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Seq (a, b), Dom Seq a, Dom Seq b) => Seq (a, b) -> (Seq a, Seq b) Source #

cunzipWith :: (Dom Seq c, Dom Seq a, Dom Seq b) => (c -> (a, b)) -> Seq c -> (Seq a, Seq b) Source #

CUnzip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Vector (a, b), Dom Vector a, Dom Vector b) => Vector (a, b) -> (Vector a, Vector b) Source #

cunzipWith :: (Dom Vector c, Dom Vector a, Dom Vector b) => (c -> (a, b)) -> Vector c -> (Vector a, Vector b) Source #

CUnzip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Vector (a, b), Dom Vector a, Dom Vector b) => Vector (a, b) -> (Vector a, Vector b) Source #

cunzipWith :: (Dom Vector c, Dom Vector a, Dom Vector b) => (c -> (a, b)) -> Vector c -> (Vector a, Vector b) Source #

CUnzip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Vector (a, b), Dom Vector a, Dom Vector b) => Vector (a, b) -> (Vector a, Vector b) Source #

cunzipWith :: (Dom Vector c, Dom Vector a, Dom Vector b) => (c -> (a, b)) -> Vector c -> (Vector a, Vector b) Source #

CUnzip Vector Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Vector (a, b), Dom Vector a, Dom Vector b) => Vector (a, b) -> (Vector a, Vector b) Source #

cunzipWith :: (Dom Vector c, Dom Vector a, Dom Vector b) => (c -> (a, b)) -> Vector c -> (Vector a, Vector b) Source #

CUnzip (Proxy :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom Proxy (a, b), Dom Proxy a, Dom Proxy b) => Proxy (a, b) -> (Proxy a, Proxy b) Source #

cunzipWith :: (Dom Proxy c, Dom Proxy a, Dom Proxy b) => (c -> (a, b)) -> Proxy c -> (Proxy a, Proxy b) Source #

Ord k => CUnzip (Map k) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (Map k) (a, b), Dom (Map k) a, Dom (Map k) b) => Map k (a, b) -> (Map k a, Map k b) Source #

cunzipWith :: (Dom (Map k) c, Dom (Map k) a, Dom (Map k) b) => (c -> (a, b)) -> Map k c -> (Map k a, Map k b) Source #

(Eq k, Hashable k) => CUnzip (HashMap k) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (HashMap k) (a, b), Dom (HashMap k) a, Dom (HashMap k) b) => HashMap k (a, b) -> (HashMap k a, HashMap k b) Source #

cunzipWith :: (Dom (HashMap k) c, Dom (HashMap k) a, Dom (HashMap k) b) => (c -> (a, b)) -> HashMap k c -> (HashMap k a, HashMap k b) Source #

Unzip f => CUnzip (WrapFunctor f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (WrapFunctor f) (a, b), Dom (WrapFunctor f) a, Dom (WrapFunctor f) b) => WrapFunctor f (a, b) -> (WrapFunctor f a, WrapFunctor f b) Source #

cunzipWith :: (Dom (WrapFunctor f) c, Dom (WrapFunctor f) a, Dom (WrapFunctor f) b) => (c -> (a, b)) -> WrapFunctor f c -> (WrapFunctor f a, WrapFunctor f b) Source #

(IsSequence mono, MonoZip mono) => CUnzip (WrapMono mono :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (WrapMono mono) (a, b), Dom (WrapMono mono) a, Dom (WrapMono mono) b) => WrapMono mono (a, b) -> (WrapMono mono a, WrapMono mono b) Source #

cunzipWith :: (Dom (WrapMono mono) c, Dom (WrapMono mono) a, Dom (WrapMono mono) b) => (c -> (a, b)) -> WrapMono mono c -> (WrapMono mono a, WrapMono mono b) Source #

(CUnzip f, CUnzip g) => CUnzip (f :*: g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (f :*: g) (a, b), Dom (f :*: g) a, Dom (f :*: g) b) => (f :*: g) (a, b) -> ((f :*: g) a, (f :*: g) b) Source #

cunzipWith :: (Dom (f :*: g) c, Dom (f :*: g) a, Dom (f :*: g) b) => (c -> (a, b)) -> (f :*: g) c -> ((f :*: g) a, (f :*: g) b) Source #

(CUnzip f, CUnzip g) => CUnzip (Product f g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (Product f g) (a, b), Dom (Product f g) a, Dom (Product f g) b) => Product f g (a, b) -> (Product f g a, Product f g b) Source #

cunzipWith :: (Dom (Product f g) c, Dom (Product f g) a, Dom (Product f g) b) => (c -> (a, b)) -> Product f g c -> (Product f g a, Product f g b) Source #

(CUnzip f, CUnzip g) => CUnzip (f :.: g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (f :.: g) (a, b), Dom (f :.: g) a, Dom (f :.: g) b) => (f :.: g) (a, b) -> ((f :.: g) a, (f :.: g) b) Source #

cunzipWith :: (Dom (f :.: g) c, Dom (f :.: g) a, Dom (f :.: g) b) => (c -> (a, b)) -> (f :.: g) c -> ((f :.: g) a, (f :.: g) b) Source #

(CUnzip f, CUnzip g) => CUnzip (Compose f g) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cunzip :: (Dom (Compose f g) (a, b), Dom (Compose f g) a, Dom (Compose f g) b) => Compose f g (a, b) -> (Compose f g a, Compose f g b) Source #

cunzipWith :: (Dom (Compose f g) c, Dom (Compose f g) a, Dom (Compose f g) b) => (c -> (a, b)) -> Compose f g c -> (Compose f g a, Compose f g b) Source #

cunzipDefault :: (CFunctor f, Dom f (a, b), Dom f a, Dom f b) => f (a, b) -> (f a, f b) Source #

newtype CZippy f a Source #

Constructors

CZippy 

Fields

Instances
Functor f => Functor (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

fmap :: (a -> b) -> CZippy f a -> CZippy f b #

(<$) :: a -> CZippy f b -> CZippy f a #

Semialign f => Semialign (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

align :: CZippy f a -> CZippy f b -> CZippy f (These a b) #

alignWith :: (These a b -> c) -> CZippy f a -> CZippy f b -> CZippy f c #

Zip f => Zip (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

zip :: CZippy f a -> CZippy f b -> CZippy f (a, b) #

zipWith :: (a -> b -> c) -> CZippy f a -> CZippy f b -> CZippy f c #

Repeat f => Repeat (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

repeat :: a -> CZippy f a #

CFunctor f => CFunctor (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

cmap :: (Dom (CZippy f) a, Dom (CZippy f) b) => (a -> b) -> CZippy f a -> CZippy f b Source #

(<$:) :: (Dom (CZippy f) a, Dom (CZippy f) b) => a -> CZippy f b -> CZippy f a Source #

Constrained (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Associated Types

type Dom (CZippy f) a :: Constraint Source #

CSemialign f => CSemialign (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

calignWith :: (Dom (CZippy f) a, Dom (CZippy f) b, Dom (CZippy f) c) => (These a b -> c) -> CZippy f a -> CZippy f b -> CZippy f c Source #

calign :: (Dom (CZippy f) a, Dom (CZippy f) b, Dom (CZippy f) (These a b)) => CZippy f a -> CZippy f b -> CZippy f (These a b) Source #

CRepeat f => CRepeat (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom (CZippy f) a => a -> CZippy f a Source #

CZip f => CZip (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

czipWith :: (Dom (CZippy f) a, Dom (CZippy f) b, Dom (CZippy f) c) => (a -> b -> c) -> CZippy f a -> CZippy f b -> CZippy f c Source #

czip :: (Dom (CZippy f) a, Dom (CZippy f) b, Dom (CZippy f) (a, b)) => CZippy f a -> CZippy f b -> CZippy f (a, b) Source #

Eq (f a) => Eq (CZippy f a) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

(==) :: CZippy f a -> CZippy f a -> Bool #

(/=) :: CZippy f a -> CZippy f a -> Bool #

Ord (f a) => Ord (CZippy f a) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

compare :: CZippy f a -> CZippy f a -> Ordering #

(<) :: CZippy f a -> CZippy f a -> Bool #

(<=) :: CZippy f a -> CZippy f a -> Bool #

(>) :: CZippy f a -> CZippy f a -> Bool #

(>=) :: CZippy f a -> CZippy f a -> Bool #

max :: CZippy f a -> CZippy f a -> CZippy f a #

min :: CZippy f a -> CZippy f a -> CZippy f a #

Read (f a) => Read (CZippy f a) Source # 
Instance details

Defined in Control.Subcategory.Zip

Show (f a) => Show (CZippy f a) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

showsPrec :: Int -> CZippy f a -> ShowS #

show :: CZippy f a -> String #

showList :: [CZippy f a] -> ShowS #

(CZip f, Dom f a, Semigroup a) => Semigroup (CZippy f a) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

(<>) :: CZippy f a -> CZippy f a -> CZippy f a #

sconcat :: NonEmpty (CZippy f a) -> CZippy f a #

stimes :: Integral b => b -> CZippy f a -> CZippy f a #

(CRepeat f, Dom f a, Monoid a) => Monoid (CZippy f a) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

mempty :: CZippy f a #

mappend :: CZippy f a -> CZippy f a -> CZippy f a #

mconcat :: [CZippy f a] -> CZippy f a #

type Dom (CZippy f) a Source # 
Instance details

Defined in Control.Subcategory.Zip

type Dom (CZippy f) a = Dom f a

class CZip f => CRepeat f where Source #

Methods

crepeat :: Dom f a => a -> f a Source #

Instances
CRepeat [] Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom [] a => a -> [a] Source #

CRepeat Maybe Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom Maybe a => a -> Maybe a Source #

CRepeat Option Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom Option a => a -> Option a Source #

CRepeat ZipList Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom ZipList a => a -> ZipList a Source #

CRepeat Identity Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom Identity a => a -> Identity a Source #

CRepeat NonEmpty Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom NonEmpty a => a -> NonEmpty a Source #

CRepeat Tree Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom Tree a => a -> Tree a Source #

Repeat f => CRepeat (WrapFunctor f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom (WrapFunctor f) a => a -> WrapFunctor f a Source #

CRepeat f => CRepeat (CZippy f) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom (CZippy f) a => a -> CZippy f a Source #

CRepeat ((->) e :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Zip

Methods

crepeat :: Dom ((->) e) a => a -> e -> a Source #