subcategories-0.2.0.1: Subcategories induced by class constraints
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Subcategory.Semialign

Documentation

class CFunctor f => CSemialign f where Source #

Minimal complete definition

calignWith

Methods

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

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

Instances

Instances details
CSemialign ZipList Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Identity Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign IntMap Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Seq Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Tree Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Array Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign PrimArray Source # 
Instance details

Defined in Control.Subcategory.Semialign

CSemialign SmallArray Source # 
Instance details

Defined in Control.Subcategory.Semialign

CSemialign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign NonEmpty Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign Maybe Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign [] Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

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

Defined in Control.Subcategory.Semialign

Methods

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

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

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

Defined in Control.Subcategory.Semialign

Methods

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

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

Semialign f => CSemialign (WrapFunctor f) Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

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

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign (WrapMono IntSet :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Semialign

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

Defined in Control.Subcategory.Semialign

Methods

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

calign :: (Dom (WrapMono mono) a, Dom (WrapMono mono) b, Dom (WrapMono mono) (These a b)) => WrapMono mono a -> WrapMono mono b -> WrapMono mono (These a b) 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 #

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

Defined in Control.Subcategory.Semialign

Methods

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

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

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

Defined in Control.Subcategory.Semialign

Methods

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

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

CSemialign ((->) s) Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

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

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

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

Defined in Control.Subcategory.Semialign

Methods

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

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

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

Defined in Control.Subcategory.Semialign

Methods

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

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

class CSemialign f => CAlign f where Source #

Methods

cnil :: Dom f a => f a Source #

Instances

Instances details
CAlign ZipList Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom ZipList a => ZipList a Source #

CAlign IntMap Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom IntMap a => IntMap a Source #

CAlign Seq Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Seq a => Seq a Source #

CAlign Array Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Array a => Array a Source #

CAlign PrimArray Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom PrimArray a => PrimArray a Source #

CAlign SmallArray Source # 
Instance details

Defined in Control.Subcategory.Semialign

CAlign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Vector a => Vector a Source #

CAlign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Vector a => Vector a Source #

CAlign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Vector a => Vector a Source #

CAlign Vector Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Vector a => Vector a Source #

CAlign Maybe Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Maybe a => Maybe a Source #

CAlign [] Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom [] a => [a] Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom Proxy a => Proxy a Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (Map k) a => Map k a Source #

Align f => CAlign (WrapFunctor f) Source # 
Instance details

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (WrapFunctor f) a => WrapFunctor f a Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (HashMap k) a => HashMap k a Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (WrapMono mono) a => WrapMono mono a Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (Product f g) a => Product f g a Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (f :*: g) a => (f :*: g) a Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (Compose f g) a => Compose f g a Source #

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

Defined in Control.Subcategory.Semialign

Methods

cnil :: Dom (f :.: g) a => (f :.: g) a Source #

csalign :: (CSemialign f, Dom f a, Semigroup a) => f a -> f a -> f a Source #

cpadZip :: (CSemialign f, Dom f a, Dom f b, Dom f (Maybe a, Maybe b)) => f a -> f b -> f (Maybe a, Maybe b) Source #

cpadZipWith :: (CSemialign f, Dom f a, Dom f b, Dom f c) => (Maybe a -> Maybe b -> c) -> f a -> f b -> f c Source #