these-0.8.1: An either-or-both data type & a generalized 'zip with padding' typeclass

Safe HaskellNone
LanguageHaskell2010

Data.Align

Contents

Description

These-based zipping and unzipping of functors with non-uniform shapes, plus traversal of (bi)foldable (bi)functors through said functors.

Synopsis

Documentation

class Functor f => Semialign f where Source #

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

If your functor is actually a functor from Kleisli Maybe to Hask (so it supports maybeMap :: (a -> Maybe b) -> f a -> f b), then an Align instance is making your functor lax monoidal w.r.t. the cartesian monoidal structure on Kleisli Maybe, because These is the cartesian product in that category (a -> Maybe (These b c) ~ (a -> Maybe b, a -> Maybe c)). This insight is due to rwbarton.

Minimal definition: either align or alignWith.

Laws:

join align = fmap (join These)
align (f <$> x) (g <$> y) = bimap f g <$> align x y
alignWith f a b = f <$> align a b
align x (align y z) = fmap assoc (align (align x y) z)

Note: join f x = f x x

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.Align

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.Align

Methods

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

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

Semialign ZipList Source # 
Instance details

Defined in Data.Align

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.Align

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.Align

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.Align

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 #

Since: 0.8.1

Instance details

Defined in Data.Align

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.Align

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.Align

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.Align

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.Align

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 #

Since: 0.8.1

Instance details

Defined in Data.Align

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.Align

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 #

Since: 0.8.1

Instance details

Defined in Data.Align

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.Align

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 #

Since: 0.8.1

Instance details

Defined in Data.Align

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.Align

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 #

Since: 0.8.1

Instance details

Defined in Data.Align

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.Align

Methods

nil :: [a] Source #

Align Maybe Source # 
Instance details

Defined in Data.Align

Methods

nil :: Maybe a Source #

Align ZipList Source # 
Instance details

Defined in Data.Align

Methods

nil :: ZipList a Source #

Align IntMap Source # 
Instance details

Defined in Data.Align

Methods

nil :: IntMap a Source #

Align Seq Source # 
Instance details

Defined in Data.Align

Methods

nil :: Seq a Source #

Align Vector Source # 
Instance details

Defined in Data.Align

Methods

nil :: Vector a Source #

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

Defined in Data.Align

Methods

nil :: HashMap k a Source #

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

Defined in Data.Align

Methods

nil :: Map k a Source #

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

Since: 0.8.1

Instance details

Defined in Data.Align

Methods

nil :: Proxy a Source #

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

Defined in Data.Align

Methods

nil :: Stream m a Source #

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

Defined in Data.Align

Methods

nil :: Bundle m v a Source #

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

Defined in Data.Align

Methods

nil :: Product f g a Source #

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

Since: 0.8.1

Instance details

Defined in Data.Align

Methods

nil :: Compose f g a Source #

Specialized aligns

malign :: (Align f, Monoid a) => f a -> f a -> f a Source #

Align two structures and combine with mappend.

See salign. malign will be deprecated after Semigroup becomes a super class of Monoid

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

Align two structures and combine with <>.

Since: 0.7.3

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

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

padZipWith :: Align 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 #

Unalign

class Align f => Unalign f where Source #

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

Minimal definition: nothing; a default definition is provided, but it may not have the desired definition for all functors. See the source for more information.

Laws:

unalign nil                 = (nil,           nil)
unalign (This        <$> x) = (Just    <$> x, Nothing <$  x)
unalign (That        <$> y) = (Nothing <$  y, Just    <$> y)
unalign (join These  <$> x) = (Just    <$> x, Just    <$> x)
unalign ((x `These`) <$> y) = (Just x  <$  y, Just    <$> y)
unalign ((`These` y) <$> x) = (Just    <$> x, Just y  <$  x)

Minimal complete definition

Nothing

Methods

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

Instances
Unalign [] Source # 
Instance details

Defined in Data.Align

Methods

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

Unalign Maybe Source # 
Instance details

Defined in Data.Align

Methods

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

Unalign ZipList Source # 
Instance details

Defined in Data.Align

Methods

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

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

Defined in Data.Align

Methods

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

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

Defined in Data.Align

Methods

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

Crosswalk

class (Functor t, Foldable t) => Crosswalk t where Source #

Foldable functors supporting traversal through an alignable functor.

Minimal definition: crosswalk or sequenceL.

Laws:

crosswalk (const nil) = const nil
crosswalk f = sequenceL . fmap f

Minimal complete definition

crosswalk | sequenceL

Methods

crosswalk :: Align f => (a -> f b) -> t a -> f (t b) Source #

sequenceL :: Align f => t (f a) -> f (t a) Source #

Instances
Crosswalk [] Source # 
Instance details

Defined in Data.Align

Methods

crosswalk :: Align f => (a -> f b) -> [a] -> f [b] Source #

sequenceL :: Align f => [f a] -> f [a] Source #

Crosswalk Maybe Source # 
Instance details

Defined in Data.Align

Methods

crosswalk :: Align f => (a -> f b) -> Maybe a -> f (Maybe b) Source #

sequenceL :: Align f => Maybe (f a) -> f (Maybe a) Source #

Crosswalk Identity Source # 
Instance details

Defined in Data.Align

Methods

crosswalk :: Align f => (a -> f b) -> Identity a -> f (Identity b) Source #

sequenceL :: Align f => Identity (f a) -> f (Identity a) Source #

Crosswalk Seq Source # 
Instance details

Defined in Data.Align

Methods

crosswalk :: Align f => (a -> f b) -> Seq a -> f (Seq b) Source #

sequenceL :: Align f => Seq (f a) -> f (Seq a) Source #

Crosswalk Vector Source # 
Instance details

Defined in Data.Align

Methods

crosswalk :: Align f => (a -> f b) -> Vector a -> f (Vector b) Source #

sequenceL :: Align f => Vector (f a) -> f (Vector a) Source #

Crosswalk ((,) a) Source #

Since: 0.7.5

Instance details

Defined in Data.Align

Methods

crosswalk :: Align f => (a0 -> f b) -> (a, a0) -> f (a, b) Source #

sequenceL :: Align f => (a, f a0) -> f (a, a0) Source #

Crosswalk (These a) Source # 
Instance details

Defined in Data.Align

Methods

crosswalk :: Align f => (a0 -> f b) -> These a a0 -> f (These a b) Source #

sequenceL :: Align f => These a (f a0) -> f (These a a0) Source #

(Crosswalk f, Crosswalk g) => Crosswalk (Compose f g) Source #

Since: 0.7.5

Instance details

Defined in Data.Align

Methods

crosswalk :: Align f0 => (a -> f0 b) -> Compose f g a -> f0 (Compose f g b) Source #

sequenceL :: Align f0 => Compose f g (f0 a) -> f0 (Compose f g a) Source #

Bicrosswalk

class (Bifunctor t, Bifoldable t) => Bicrosswalk t where Source #

Bifoldable bifunctors supporting traversal through an alignable functor.

Minimal definition: bicrosswalk or bisequenceL.

Laws:

bicrosswalk (const empty) (const empty) = const empty
bicrosswalk f g = bisequenceL . bimap f g

Minimal complete definition

bicrosswalk | bisequenceL

Methods

bicrosswalk :: Align f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) Source #

bisequenceL :: Align f => t (f a) (f b) -> f (t a b) Source #

Instances
Bicrosswalk Either Source # 
Instance details

Defined in Data.Align

Methods

bicrosswalk :: Align f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) Source #

bisequenceL :: Align f => Either (f a) (f b) -> f (Either a b) Source #

Bicrosswalk These Source # 
Instance details

Defined in Data.Align

Methods

bicrosswalk :: Align f => (a -> f c) -> (b -> f d) -> These a b -> f (These c d) Source #

bisequenceL :: Align f => These (f a) (f b) -> f (These a b) Source #