Copyright | (c) Conal Elliott 2007 |
---|---|
License | BSD3 |
Maintainer | conal@conal.net |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell98 |
Zip-related type constructor classes.
This module is similar to Control.Functor.Zip
in the
category-extras
package, but it does not require a Functor
superclass.
This module defines generalized zip
and unzip
, so if you use it,
you'll have to
import Prelude hiding (zip,zipWith,zipWith3,unzip)
Temporarily, there is also Data.Pair, which contains the same functionality with different naming. I'm unsure which I prefer.
Synopsis
- type ZipTy f = forall a b. f a -> f b -> f (a, b)
- class Zip f where
- zipWith :: (Functor f, Zip f) => (a -> b -> c) -> f a -> f b -> f c
- zipWith3 :: (Functor f, Zip f) => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- apZip :: (Applicative h, Zip f) => ZipTy (h :. f)
- ppZip :: (Functor g, Zip g, Zip f) => ZipTy (g :. f)
- arZip :: (Arrow j, Unzip f, Zip g) => ZipTy (Arrw j f g)
- type UnzipTy f = forall a b. f (a, b) -> (f a, f b)
- class Unzip f where
- class Cozip f where
- cozip :: (Cozip f, Monoid_f f) => ZipTy f
- pairEdit :: (Functor m, Monoid (m ((c, d) -> (c, d)))) => (m c, m d) -> m ((c, d) -> (c, d))
- pairEditM :: MonadPlus m => (m c, m d) -> m ((c, d) -> (c, d))
Zippings
Type constructor class for zip
-like things.
Here are some standard instance templates you can fill in. They're not
defined in the general forms below, because they would lead to a lot of
overlap.
instance Applicative f => Zip f where zip = liftA2 (,) instance (Applicative h, Zip f) => Zip (h :. f) where zip = apZip instance (Functor g, Zip g, Zip f) => Zip (g :. f) where zip = ppZip instance (Arrow (~>), Unzip f, Zip g) => Zip (Arrw (~>) f g) where zip = arZip instance (Monoid_f h, Cozip h) => Zip h where zip = cozip
Also, if you have a type constructor that's a Functor
and a Zip
,
here is a way to define '(*)' for Applicative
:
(<*>) = zipWith ($)
Minimum definitions for instances.
Instances
Zip [] Source # | |
Zip IO Source # | |
Zip Endo Source # | |
Zip Id Source # | |
Monoid u => Zip ((,) u) Source # | |
Monoid o => Zip (Const o :: Type -> Type) Source # | |
Zip ((->) u :: Type -> Type) Source # | |
(Zip f, Zip g) => Zip (f :*: g) Source # | |
(Arrow j, Monoid_f (Flip j o)) => Zip (Flip j o) Source # | |
(Arrow j, Unzip f, Zip g) => Zip (Arrw j f g) Source # | |
zipWith3 :: (Functor f, Zip f) => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #
Generalized zipWith
Unzipings
Unzippable. Minimal instance definition: either (a) unzip
or (b)
both of fsts
and snds
. A standard template to substitute any
Functor
f.
But watch out for effects!
instance Functor f => Unzip f where {fsts = fmap fst; snds = fmap snd}
Nothing
:: UnzipTy f | generalized unzip |
:: f (a, b) | |
-> f a | First part of pair-like value |
:: f (a, b) | |
-> f b | Second part of pair-like value |
Dual unzipings
Dual to Unzip
.
Especially handy for contravariant functors (Cofunctor
) . Use this
template (filling in f
) :
instance Cofunctor f => Cozip f where { cofsts = cofmap fst ; cosnds = cofmap snd }
:: f a | |
-> f (a, b) | Zip-like value from first part |
:: f b | |
-> f (a, b) | Zip-like value from second part |
cozip :: (Cozip f, Monoid_f f) => ZipTy f Source #
Ziping of Cozip
values. Combines contribution of each.