| Safe Haskell | Trustworthy | 
|---|---|
| Language | Haskell2010 | 
Data.Zip
Description
Zipping and unzipping of functors with non-uniform shapes.
Documentation
class Functor f => Semialign f where Source #
Functors supporting a zip and align operations that takes the
 intersection and union of non-uniform shapes.
Minimal definition: either align or alignWith and either zip or zipWith.
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) join zip ≡ fmap (join (,))
Commutativity
align x y ≡ swap <$> align y x zip x y ≡ swap <$> zip y x
Associativity
align x (align y z) ≡ assoc <$> align (align x y) z
    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
alignWith f a b ≡ f <$> align a b zipWith f a b ≡ f <$> zip a b
Functoriality
align (f <$> x) (g <$> y) ≡ bimap f g <$> align x y 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
Alignedness, if f is Foldable
toList x ≡ toListOf (folded . here) (align x y)
         ≡ mapMaybe justHere (toList (align x y))
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" [(,
 but the right hand side is That 0, That 0)][(.That 0, These 0 0)]
Methods
align :: f a -> f b -> f (These a b) Source #
Analogous to zipThese
alignWith :: (These a b -> c) -> f a -> f b -> f c Source #
Analogous to zipWith
zip :: f a -> f b -> f (a, b) Source #
Combines to 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 to structures by taking the intersection of their shapes and combining the elements with the given function.
Instances
class Semialign f => Zip f where Source #
A unit of zip.
fst <$> zip xs (full y) ≡ xs snd <$> zip (full x) ys ≡ ys
Instances
| Zip [] Source # | |
| Defined in Data.Semialign.Internal | |
| Zip Maybe Source # | |
| Defined in Data.Semialign.Internal | |
| Zip ZipList Source # | |
| Defined in Data.Semialign.Internal | |
| Zip Identity Source # | |
| Defined in Data.Semialign.Internal | |
| Zip NonEmpty Source # | |
| Defined in Data.Semialign.Internal | |
| Zip Tree Source # | |
| Defined in Data.Semialign.Internal | |
| Zip (Proxy :: Type -> Type) Source # | |
| Defined in Data.Semialign.Internal | |
| Zip (Tagged b) Source # | |
| Defined in Data.Semialign.Internal | |
| Zip ((->) e :: Type -> Type) Source # | |
| Defined in Data.Semialign.Internal | |
| (Zip f, Zip g) => Zip (Product f g) Source # | |
| Defined in Data.Semialign.Internal | |
| (Zip f, Zip g) => Zip (Compose f g) Source # | |
| Defined in Data.Semialign.Internal | |
class Semialign 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.
Instances
| Unzip [] Source # | |
| Unzip Maybe Source # | |
| Unzip ZipList Source # | |
| Unzip Identity Source # | |
| Unzip NonEmpty Source # | |
| Unzip IntMap Source # | |
| Unzip Tree Source # | |
| Unzip Seq Source # | |
| Unzip Vector Source # | |
| (Eq k, Hashable k) => Unzip (HashMap k) Source # | |
| Ord k => Unzip (Map k) Source # | |
| Unzip (Proxy :: Type -> Type) Source # | |
| Unzip (Tagged b) Source # | |
| (Unzip f, Unzip g) => Unzip (Product f g) Source # | |
| (Unzip f, Unzip g) => Unzip (Compose f g) Source # | |
unzipDefault :: Functor f => f (a, b) -> (f a, f b) Source #
Instances
| Functor f => Functor (Zippy f) Source # | |
| Zip f => Applicative (Zippy f) Source # | |
| Semialign f => Apply (Zippy f) Source # | |
| Eq (f a) => Eq (Zippy f a) Source # | |
| Ord (f a) => Ord (Zippy f a) Source # | |
| Read (f a) => Read (Zippy f a) Source # | |
| Show (f a) => Show (Zippy f a) Source # | |
| (Semialign f, Semigroup a) => Semigroup (Zippy f a) Source # | |
| (Zip f, Monoid a) => Monoid (Zippy f a) Source # | |