TypeCompose-0.9.1: Type composition classes & instances

PortabilityGHC
Stabilityexperimental
Maintainerconal@conal.net
Safe HaskellSafe-Infered

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 whereSource

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

zipSource

Arguments

:: ZipTy f

Generalized zip

Instances

Zip [] 
Zip IO 
Zip Endo 
Zip Id 
Zip ((->) u) 
Monoid u => Zip ((,) u) 
Monoid o => Zip (Const o) 
(Zip f, Zip g) => Zip (:*: f g) 
(Arrow ~>, Monoid_f (Flip ~> o)) => Zip (Flip ~> o) 
(Arrow ~>, Unzip f, Zip g) => Zip (Arrw ~> f g) 

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

Generalized zipWith

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

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 ~>, Unzip f, Zip g) => ZipTy (Arrw ~> 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 whereSource

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}

Methods

unzipSource

Arguments

:: UnzipTy f

generalized unzip

fstsSource

Arguments

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

First part of pair-like value

sndsSource

Arguments

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

Second part of pair-like value

Instances

Unzip [] 
Unzip Endo 
Unzip Id 
Unzip ((->) a) 
Unzip ((,) a) 
Unzip (Const a) 

Dual unzipings

class Cozip f whereSource

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

cofstsSource

Arguments

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

Zip-like value from first part

cosndsSource

Arguments

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

Zip-like value from second part

Instances

Cozip Endo 
Cozip (Const e) 
(Cozip f, Cozip g) => Cozip (:*: f g) 
Arrow ~> => Cozip (Flip ~> o) 
(Functor h, Cozip f) => Cozip (:. h f) 

cozip :: (Cozip f, Monoid_f f) => ZipTy fSource

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.