Safe Haskell | None |
---|
These
-based zipping and unzipping of functors with non-uniform
shapes, plus traversal of (bi)foldable (bi)functors through said
functors.
- class Functor f => Align f where
- malign :: (Align f, Monoid a) => f a -> f a -> f a
- padZip :: Align f => f a -> f b -> f (Maybe a, Maybe b)
- padZipWith :: Align f => (Maybe a -> Maybe b -> c) -> f a -> f b -> f c
- lpadZip :: [a] -> [b] -> [(Maybe a, b)]
- lpadZipWith :: (Maybe a -> b -> c) -> [a] -> [b] -> [c]
- rpadZip :: [a] -> [b] -> [(a, Maybe b)]
- rpadZipWith :: (a -> Maybe b -> c) -> [a] -> [b] -> [c]
- alignVectorWith :: (Vector v a, Vector v b, Vector v c) => (These a b -> c) -> v a -> v b -> v c
- class Align f => Unalign f where
- class (Functor t, Foldable t) => Crosswalk t where
- class (Bifunctor t, Bifoldable t) => Bicrosswalk t where
- bicrosswalk :: Align f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- bisequenceL :: Align f => t (f a) (f b) -> f (t a b)
Documentation
class Functor f => Align f whereSource
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: nil
and either align
or alignWith
.
Laws:
(`align` nil) = fmap This (nil `align`) = fmap That join align = fmap (join These) align (f <$> x) (g <$> y) = bimap f g <$> align x y alignWith f a b = f <$> align a b
Specialized aligns
malign :: (Align f, Monoid a) => f a -> f a -> f aSource
Align two structures and combine with mappend
.
padZipWith :: Align f => (Maybe a -> Maybe b -> c) -> f a -> f b -> f cSource
lpadZipWith :: (Maybe a -> b -> c) -> [a] -> [b] -> [c]Source
Left-padded zipWith
.
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 cSource
Unalign
class Align f => Unalign f whereSource
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)
Crosswalk
class (Functor t, Foldable t) => Crosswalk t whereSource
Foldable functors supporting traversal through an alignable functor.
Minimal definition: crosswalk
or sequenceL
.
Laws:
crosswalk (const nil) = const nil crosswalk f = sequenceL . fmap f
Bicrosswalk
class (Bifunctor t, Bifoldable t) => Bicrosswalk t whereSource
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
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