semialign-1.1: Align and Zip type-classes from the common Semialign ancestor.

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Align

Contents

Description

These-based aligning and unaligning of functors with non-uniform shapes.

For a traversals traversal of (bi)foldable (bi)functors through said functors see Data.Crosswalk.

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
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 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 Option Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

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

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

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 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 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 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 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 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 #

(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 #

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 #

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 #

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 ((->) e :: Type -> Type) 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 (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 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 => Align f where Source #

A unit of align.

Laws

(`align` nil) ≡ fmap This
(nil `align`) ≡ fmap That

Methods

nil :: f a Source #

An empty structure. aligning with nil will produce a structure with the same shape and elements as the other input, modulo This or That.

Instances
Align [] Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

nil :: [a] Source #

Align Maybe Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

nil :: Maybe a Source #

Align Option Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

nil :: Option a Source #

Align ZipList Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

nil :: ZipList a Source #

Align IntMap Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

nil :: IntMap a Source #

Align Seq Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

nil :: Seq a Source #

Align Vector Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

nil :: Vector a Source #

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

Defined in Data.Semialign.Internal

Methods

nil :: HashMap k a Source #

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

Defined in Data.Semialign.Internal

Methods

nil :: Map k a Source #

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

Defined in Data.Semialign.Internal

Methods

nil :: Proxy a Source #

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

Defined in Data.Semialign.Internal

Methods

nil :: Stream m a Source #

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

Defined in Data.Semialign.Internal

Methods

nil :: Bundle m v a Source #

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

Defined in Data.Semialign.Internal

Methods

nil :: Product f g a Source #

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

Defined in Data.Semialign.Internal

Methods

nil :: Compose f g a Source #

class Semialign f => Unalign f where Source #

Alignable functors supporting an "inverse" to align: splitting a union shape into its component parts.

Laws

uncurry align (unalign xs) ≡ xs
unalign (align xs ys) ≡ (xs, ys)

Compatibility note

In version 1 unalign was changed to return (f a, f b) pair, instead of (f (Just a), f (Just b)). Old behaviour can be achieved with if ever needed.

>>> unzipWith (unalign . Just) [This 'a', That 'b', These 'c' 'd']
([Just 'a',Nothing,Just 'c'],[Nothing,Just 'b',Just 'd'])

Minimal complete definition

unalignWith | unalign

Methods

unalign :: f (These a b) -> (f a, f b) Source #

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

Instances
Unalign Maybe Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unalign :: Maybe (These a b) -> (Maybe a, Maybe b) Source #

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

Unalign Option Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unalign :: Option (These a b) -> (Option a, Option b) Source #

unalignWith :: (c -> These a b) -> Option c -> (Option a, Option b) Source #

Unalign IntMap Source # 
Instance details

Defined in Data.Semialign.Internal

Methods

unalign :: IntMap (These a b) -> (IntMap a, IntMap b) Source #

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

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

Defined in Data.Semialign.Internal

Methods

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

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

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

Defined in Data.Semialign.Internal

Methods

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

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

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

Defined in Data.Semialign.Internal

Methods

unalign :: Proxy (These a b) -> (Proxy a, Proxy b) Source #

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

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

Defined in Data.Semialign.Internal

Methods

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

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

Specialized aligns

salign :: (Semialign f, Semigroup a) => f a -> f a -> f a Source #

Align two structures and combine with <>.

padZip :: Semialign f => f a -> f b -> f (Maybe a, Maybe b) Source #

Align two structures as in zip, but filling in blanks with Nothing.

padZipWith :: Semialign f => (Maybe a -> Maybe b -> c) -> f a -> f b -> f c Source #

Align two structures as in zipWith, but filling in blanks with Nothing.

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

Left-padded zip.

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

Left-padded zipWith.

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

Right-padded zip.

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

Right-padded zipWith.

alignVectorWith :: (Vector v a, Vector v b, Vector v c) => (These a b -> c) -> v a -> v b -> v c Source #