semialign-1.3: Align and Zip type-classes from the common Semialign ancestor.
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Zip

Description

Zipping and unzipping of functors with non-uniform shapes.

Synopsis

Documentation

class Functor f => Semialign f where Source #

Functors supporting an align operation that takes the union of non-uniform shapes.

Minimal definition: either align or alignWith.

Laws

The laws of align and zip resemble lattice laws. There is a plenty of laws, but they are simply satisfied.

And an addition property if f is Foldable, which tries to enforce align-feel: neither values are duplicated nor lost.

Note: join f x = f x x

Idempotency

join align ≡ fmap (join These)

Commutativity

align x y ≡ swap <$> align y x

Associativity

align x (align y z) ≡ assoc <$> align (align x y) z

With

alignWith f a b ≡ f <$> align a b

Functoriality

align (f <$> x) (g <$> y) ≡ bimap f g <$> align x y

Alignedness, if f is Foldable

toList x ≡ toListOf (folded . here) (align x y)
         ≡ mapMaybe justHere (toList (align x y))

And an addition property if f is Foldable, which tries to enforce align-feel: neither values are duplicated nor lost.

toList x = toListOf (folded . here) (align x y)
         = mapMaybe justHere (toList (align x y))

Minimal complete definition

(align | alignWith)

Methods

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

Analogous to zip, combines two structures by taking the union of their shapes and using These to hold the elements.

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

Analogous to zipWith, combines two structures by taking the union of their shapes and combining the elements with the given function.

Instances

Instances details
Semialign ZipList Source #

zipWith = liftA2 .

Instance details

Defined in Data.Semialign.Internal

Methods

align :: ZipList a -> ZipList b -> ZipList (These a b) Source #

alignWith :: (These a b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

Semialign Identity Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Identity a -> Identity b -> Identity (These a b) Source #

alignWith :: (These a b -> c) -> Identity a -> Identity b -> Identity c Source #

Semialign IntMap Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: IntMap a -> IntMap b -> IntMap (These a b) Source #

alignWith :: (These a b -> c) -> IntMap a -> IntMap b -> IntMap c Source #

Semialign Seq Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Seq a -> Seq b -> Seq (These a b) Source #

alignWith :: (These a b -> c) -> Seq a -> Seq b -> Seq c Source #

Semialign Tree Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Tree a -> Tree b -> Tree (These a b) Source #

alignWith :: (These a b -> c) -> Tree a -> Tree b -> Tree c Source #

Semialign Vector Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Vector a -> Vector b -> Vector (These a b) Source #

alignWith :: (These a b -> c) -> Vector a -> Vector b -> Vector c Source #

Semialign NonEmpty Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: NonEmpty a -> NonEmpty b -> NonEmpty (These a b) Source #

alignWith :: (These a b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

Semialign Maybe Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Maybe a -> Maybe b -> Maybe (These a b) Source #

alignWith :: (These a b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

Semialign [] Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: [a] -> [b] -> [These a b] Source #

alignWith :: (These a b -> c) -> [a] -> [b] -> [c] Source #

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

Defined in Data.Semialign.Internal

Methods

align :: Proxy a -> Proxy b -> Proxy (These a b) Source #

alignWith :: (These a b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

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

Defined in Data.Semialign.Internal

Methods

align :: Map k a -> Map k b -> Map k (These a b) Source #

alignWith :: (These a b -> c) -> Map k a -> Map k b -> Map k c Source #

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

Defined in Data.Semialign.Internal

Methods

align :: HashMap k a -> HashMap k b -> HashMap k (These a b) Source #

alignWith :: (These a b -> c) -> HashMap k a -> HashMap k b -> HashMap k c Source #

Monad m => Semialign (Stream m) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Stream m a -> Stream m b -> Stream m (These a b) Source #

alignWith :: (These a b -> c) -> Stream m a -> Stream m b -> Stream m c Source #

Semialign (Tagged b) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Tagged b a -> Tagged b b0 -> Tagged b (These a b0) Source #

alignWith :: (These a b0 -> c) -> Tagged b a -> Tagged b b0 -> Tagged b c Source #

Monad m => Semialign (Bundle m v) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: Bundle m v a -> Bundle m v b -> Bundle m v (These a b) Source #

alignWith :: (These a b -> c) -> Bundle m v a -> Bundle m v b -> Bundle m v c Source #

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

Defined in Data.Semialign.Internal

Methods

align :: Product f g a -> Product f g b -> Product f g (These a b) Source #

alignWith :: (These a b -> c) -> Product f g a -> Product f g b -> Product f g c Source #

Semialign ((->) e) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

align :: (e -> a) -> (e -> b) -> e -> These a b Source #

alignWith :: (These a b -> c) -> (e -> a) -> (e -> b) -> e -> c Source #

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

Defined in Data.Semialign.Internal

Methods

align :: Compose f g a -> Compose f g b -> Compose f g (These a b) Source #

alignWith :: (These a b -> c) -> Compose f g a -> Compose f g b -> Compose f g c Source #

class Semialign f => Zip f where Source #

Functors supporting a zip operation that takes the intersection of non-uniform shapes.

Minimal definition: either zip or zipWith.

Idempotency

join zip   ≡ fmap (join (,))

Commutativity

zip x y ≡ swap <$> zip y x

Associativity

zip x (zip y z) ≡ assoc <$> zip (zip x y) z

Absorption

fst    <$> zip xs (align xs ys) ≡ xs
toThis <$> align xs (zip xs ys) ≡ This <$> xs
  where
    toThis (This a)    = This a
    toThis (These a _) = This a
    toThis (That b)    = That b

With

zipWith f a b ≡ f <$> zip a b

Functoriality

zip (f <$> x) (g <$> y) ≡ bimap f g <$> zip x y

Zippyness

fmap fst (zip x x) ≡ x
fmap snd (zip x x) ≡ x
zip (fmap fst x) (fmap snd x) ≡ x

Distributivity

                   align (zip xs ys) zs ≡ undistrThesePair <$> zip (align xs zs) (align ys zs)
distrPairThese <$> zip (align xs ys) zs ≡                      align (zip xs zs) (zip ys zs)
                   zip (align xs ys) zs ≡ undistrPairThese <$> align (zip xs zs) (zip ys zs)

Note, the following doesn't hold:

distrThesePair <$> align (zip xs ys) zs ≢ zip (align xs zs) (align ys zs)

when xs = [] and ys = zs = [0], then the left hand side is "only" [(That 0, That 0)], but the right hand side is [(That 0, These 0 0)].

Minimal complete definition

(zip | zipWith)

Methods

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

Combines two structures by taking the intersection of their shapes and using pair to hold the elements.

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

Combines two structures by taking the intersection of their shapes and combining the elements with the given function.

Instances

Instances details
Zip ZipList Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: ZipList a -> ZipList b -> ZipList (a, b) Source #

zipWith :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

Zip Identity Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Identity a -> Identity b -> Identity (a, b) Source #

zipWith :: (a -> b -> c) -> Identity a -> Identity b -> Identity c Source #

Zip IntMap Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: IntMap a -> IntMap b -> IntMap (a, b) Source #

zipWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c Source #

Zip Seq Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Seq a -> Seq b -> Seq (a, b) Source #

zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c Source #

Zip Tree Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Tree a -> Tree b -> Tree (a, b) Source #

zipWith :: (a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

Zip Vector Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Vector a -> Vector b -> Vector (a, b) Source #

zipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

Zip NonEmpty Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) Source #

zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

Zip Maybe Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Maybe a -> Maybe b -> Maybe (a, b) Source #

zipWith :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

Zip [] Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: [a] -> [b] -> [(a, b)] Source #

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

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

Defined in Data.Semialign.Internal

Methods

zip :: Proxy a -> Proxy b -> Proxy (a, b) Source #

zipWith :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

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

Defined in Data.Semialign.Internal

Methods

zip :: Map k a -> Map k b -> Map k (a, b) Source #

zipWith :: (a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

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

Defined in Data.Semialign.Internal

Methods

zip :: HashMap k a -> HashMap k b -> HashMap k (a, b) Source #

zipWith :: (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c Source #

Monad m => Zip (Stream m) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Stream m a -> Stream m b -> Stream m (a, b) Source #

zipWith :: (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c Source #

Zip (Tagged b) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Tagged b a -> Tagged b b0 -> Tagged b (a, b0) Source #

zipWith :: (a -> b0 -> c) -> Tagged b a -> Tagged b b0 -> Tagged b c Source #

Monad m => Zip (Bundle m v) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: Bundle m v a -> Bundle m v b -> Bundle m v (a, b) Source #

zipWith :: (a -> b -> c) -> Bundle m v a -> Bundle m v b -> Bundle m v c Source #

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

Defined in Data.Semialign.Internal

Methods

zip :: Product f g a -> Product f g b -> Product f g (a, b) Source #

zipWith :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c Source #

Zip ((->) e) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

zip :: (e -> a) -> (e -> b) -> e -> (a, b) Source #

zipWith :: (a -> b -> c) -> (e -> a) -> (e -> b) -> e -> c Source #

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

Defined in Data.Semialign.Internal

Methods

zip :: Compose f g a -> Compose f g b -> Compose f g (a, b) Source #

zipWith :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c Source #

class Zip f => Repeat f where Source #

Zippable functors supporting left and right units

Unit

fst <$> zip xs (repeat y) ≡ xs
snd <$> zip (repeat x) ys ≡ ys

Methods

repeat :: a -> f a Source #

A repeat structure.

Instances

Instances details
Repeat ZipList Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> ZipList a Source #

Repeat Identity Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> Identity a Source #

Repeat Tree Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> Tree a Source #

Repeat NonEmpty Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> NonEmpty a Source #

Repeat Maybe Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> Maybe a Source #

Repeat [] Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> [a] Source #

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

Defined in Data.Semialign.Internal

Methods

repeat :: a -> Proxy a Source #

Repeat (Tagged b) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> Tagged b a Source #

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

Defined in Data.Semialign.Internal

Methods

repeat :: a -> Product f g a Source #

Repeat ((->) e) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat :: a -> e -> a Source #

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

Defined in Data.Semialign.Internal

Methods

repeat :: a -> Compose f g a Source #

class Zip f => Unzip f where Source #

Right inverse of zip.

This class is definable for every Functor. See unzipDefault.

Laws

uncurry zip (unzip xs) ≡ xs
unzip (zip xs xs) ≡ (xs, xs)

Note:

unzip (zip xs ys) ≢ (xs, _) or (_, ys)

For sequence-like types this holds, but for Map-like it doesn't.

Minimal complete definition

unzipWith | unzip

Methods

unzipWith :: (c -> (a, b)) -> f c -> (f a, f b) Source #

unzip :: f (a, b) -> (f a, f b) Source #

Instances

Instances details
Unzip ZipList Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> ZipList c -> (ZipList a, ZipList b) Source #

unzip :: ZipList (a, b) -> (ZipList a, ZipList b) Source #

Unzip Identity Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Identity c -> (Identity a, Identity b) Source #

unzip :: Identity (a, b) -> (Identity a, Identity b) Source #

Unzip IntMap Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> IntMap c -> (IntMap a, IntMap b) Source #

unzip :: IntMap (a, b) -> (IntMap a, IntMap b) Source #

Unzip Seq Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Seq c -> (Seq a, Seq b) Source #

unzip :: Seq (a, b) -> (Seq a, Seq b) Source #

Unzip Tree Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Tree c -> (Tree a, Tree b) Source #

unzip :: Tree (a, b) -> (Tree a, Tree b) Source #

Unzip Vector Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Vector c -> (Vector a, Vector b) Source #

unzip :: Vector (a, b) -> (Vector a, Vector b) Source #

Unzip NonEmpty Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> NonEmpty c -> (NonEmpty a, NonEmpty b) Source #

unzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) Source #

Unzip Maybe Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Maybe c -> (Maybe a, Maybe b) Source #

unzip :: Maybe (a, b) -> (Maybe a, Maybe b) Source #

Unzip [] Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> [c] -> ([a], [b]) Source #

unzip :: [(a, b)] -> ([a], [b]) Source #

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

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Proxy c -> (Proxy a, Proxy b) Source #

unzip :: Proxy (a, b) -> (Proxy a, Proxy b) Source #

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

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Map k c -> (Map k a, Map k b) Source #

unzip :: Map k (a, b) -> (Map k a, Map k b) Source #

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

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> HashMap k c -> (HashMap k a, HashMap k b) Source #

unzip :: HashMap k (a, b) -> (HashMap k a, HashMap k b) Source #

Unzip (Tagged b) Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b0)) -> Tagged b c -> (Tagged b a, Tagged b b0) Source #

unzip :: Tagged b (a, b0) -> (Tagged b a, Tagged b b0) Source #

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

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Product f g c -> (Product f g a, Product f g b) Source #

unzip :: Product f g (a, b) -> (Product f g a, Product f g b) Source #

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

Defined in Data.Semialign.Internal

Methods

unzipWith :: (c -> (a, b)) -> Compose f g c -> (Compose f g a, Compose f g b) Source #

unzip :: Compose f g (a, b) -> (Compose f g a, Compose f g b) Source #

unzipDefault :: Functor f => f (a, b) -> (f a, f b) Source #

newtype Zippy f a Source #

Constructors

Zippy 

Fields

Instances

Instances details
Repeat f => Applicative (Zippy f) Source # 
Instance details

Defined in Data.Zip

Methods

pure :: a -> Zippy f a #

(<*>) :: Zippy f (a -> b) -> Zippy f a -> Zippy f b #

liftA2 :: (a -> b -> c) -> Zippy f a -> Zippy f b -> Zippy f c #

(*>) :: Zippy f a -> Zippy f b -> Zippy f b #

(<*) :: Zippy f a -> Zippy f b -> Zippy f a #

Functor f => Functor (Zippy f) Source # 
Instance details

Defined in Data.Zip

Methods

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

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

Zip f => Apply (Zippy f) Source # 
Instance details

Defined in Data.Zip

Methods

(<.>) :: Zippy f (a -> b) -> Zippy f a -> Zippy f b #

(.>) :: Zippy f a -> Zippy f b -> Zippy f b #

(<.) :: Zippy f a -> Zippy f b -> Zippy f a #

liftF2 :: (a -> b -> c) -> Zippy f a -> Zippy f b -> Zippy f c #

(Repeat f, Monoid a) => Monoid (Zippy f a) Source # 
Instance details

Defined in Data.Zip

Methods

mempty :: Zippy f a #

mappend :: Zippy f a -> Zippy f a -> Zippy f a #

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

(Zip f, Semigroup a) => Semigroup (Zippy f a) Source # 
Instance details

Defined in Data.Zip

Methods

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

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

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

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

Defined in Data.Zip

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

Defined in Data.Zip

Methods

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

show :: Zippy f a -> String #

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

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

Defined in Data.Zip

Methods

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

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

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

Defined in Data.Zip

Methods

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

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

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

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

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

max :: Zippy f a -> Zippy f a -> Zippy f a #

min :: Zippy f a -> Zippy f a -> Zippy f a #