TypeCompose-0.9.14: Type composition classes & instances

Copyright(c) Conal Elliott 2007
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

Data.Zip

Contents

Description

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

Zippings

type ZipTy f = forall a b. f a -> f b -> f (a, b) Source #

Type of zip method

class Zip f where Source #

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.

Methods

zip Source #

Arguments

:: ZipTy f

Generalized zip

Instances
Zip [] Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy [] Source #

Zip IO Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy IO Source #

Zip Endo Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy Endo Source #

Zip Id Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy Id Source #

Monoid u => Zip ((,) u) Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy ((,) u) Source #

Monoid o => Zip (Const o :: Type -> Type) Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy (Const o) Source #

Zip ((->) u :: Type -> Type) Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy ((->) u) Source #

(Zip f, Zip g) => Zip (f :*: g) Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy (f :*: g) Source #

(Arrow j, Monoid_f (Flip j o)) => Zip (Flip j o) Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy (Flip j o) Source #

(Arrow j, Unzip f, Zip g) => Zip (Arrw j f g) Source # 
Instance details

Defined in Data.Zip

Methods

zip :: ZipTy (Arrw j f g) Source #

zipWith :: (Functor f, Zip f) => (a -> b -> c) -> f a -> f b -> f c Source #

Generalized zipWith

zipWith3 :: (Functor f, Zip f) => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #

Generalized zipWith

apZip :: (Applicative h, Zip f) => ZipTy (h :. f) Source #

Handy for Zip instances

ppZip :: (Functor g, Zip g, Zip f) => ZipTy (g :. f) Source #

Handy for Zip instances

arZip :: (Arrow j, Unzip f, Zip g) => ZipTy (Arrw j f g) Source #

Ziping of Arrw values. Warning: definition uses arr, so only use if your arrow has a working arr.

Unzipings

type UnzipTy f = forall a b. f (a, b) -> (f a, f b) Source #

Type of unzip method. Generalizes unzip.

class Unzip f where Source #

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}

Minimal complete definition

Nothing

Methods

unzip Source #

Arguments

:: UnzipTy f

generalized unzip

fsts Source #

Arguments

:: f (a, b) 
-> f a

First part of pair-like value

snds Source #

Arguments

:: f (a, b) 
-> f b

Second part of pair-like value

Instances
Unzip [] Source # 
Instance details

Defined in Data.Zip

Methods

unzip :: UnzipTy [] Source #

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

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

Unzip Endo Source # 
Instance details

Defined in Data.Zip

Methods

unzip :: UnzipTy Endo Source #

fsts :: Endo (a, b) -> Endo a Source #

snds :: Endo (a, b) -> Endo b Source #

Unzip Id Source # 
Instance details

Defined in Data.Zip

Methods

unzip :: UnzipTy Id Source #

fsts :: Id (a, b) -> Id a Source #

snds :: Id (a, b) -> Id b Source #

Unzip ((,) a) Source # 
Instance details

Defined in Data.Zip

Methods

unzip :: UnzipTy ((,) a) Source #

fsts :: (a, (a0, b)) -> (a, a0) Source #

snds :: (a, (a0, b)) -> (a, b) Source #

Unzip (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Zip

Methods

unzip :: UnzipTy (Const a) Source #

fsts :: Const a (a0, b) -> Const a a0 Source #

snds :: Const a (a0, b) -> Const a b Source #

Unzip ((->) a :: Type -> Type) Source # 
Instance details

Defined in Data.Zip

Methods

unzip :: UnzipTy ((->) a) Source #

fsts :: (a -> (a0, b)) -> a -> a0 Source #

snds :: (a -> (a0, b)) -> a -> b Source #

Dual unzipings

class Cozip f where Source #

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 }

Methods

cofsts Source #

Arguments

:: f a 
-> f (a, b)

Zip-like value from first part

cosnds Source #

Arguments

:: f b 
-> f (a, b)

Zip-like value from second part

Instances
Cozip Endo Source # 
Instance details

Defined in Data.Zip

Methods

cofsts :: Endo a -> Endo (a, b) Source #

cosnds :: Endo b -> Endo (a, b) Source #

Cozip (Const e :: Type -> Type) Source # 
Instance details

Defined in Data.Zip

Methods

cofsts :: Const e a -> Const e (a, b) Source #

cosnds :: Const e b -> Const e (a, b) Source #

(Cozip f, Cozip g) => Cozip (f :*: g) Source # 
Instance details

Defined in Data.Zip

Methods

cofsts :: (f :*: g) a -> (f :*: g) (a, b) Source #

cosnds :: (f :*: g) b -> (f :*: g) (a, b) Source #

Arrow j => Cozip (Flip j o) Source # 
Instance details

Defined in Data.Zip

Methods

cofsts :: Flip j o a -> Flip j o (a, b) Source #

cosnds :: Flip j o b -> Flip j o (a, b) Source #

(Functor h, Cozip f) => Cozip (h :. f) Source # 
Instance details

Defined in Data.Zip

Methods

cofsts :: (h :. f) a -> (h :. f) (a, b) Source #

cosnds :: (h :. f) b -> (h :. f) (a, b) Source #

cozip :: (Cozip f, Monoid_f f) => ZipTy f Source #

Ziping of Cozip values. Combines contribution of each.

Misc

pairEdit :: (Functor m, Monoid (m ((c, d) -> (c, d)))) => (m c, m d) -> m ((c, d) -> (c, d)) Source #

Turn a pair of sources into a source of pair-editors. See http://conal.net/blog/posts/pairs-sums-and-reactivity/. 'Functor'\/'Monoid' version. See also pairEditM.

pairEditM :: MonadPlus m => (m c, m d) -> m ((c, d) -> (c, d)) Source #

Turn a pair of sources into a source of pair-editors. See http://conal.net/blog/posts/pairs-sums-and-reactivity/. Monad version. See also pairEdit.