product-profunctors-0.10.0.0: product-profunctors

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Product.Adaptor

Description

Adaptors generalize traversals in two ways:

  • they may focus on values of different types;
  • the type of transformation is an abstract product profunctor p a b, rather than a function type a -> f b.
(a -> f b)         -> (a, a) -> f (b, b)   -- Traversal
(p a1 b1, p a2 b2) -> p (a1, a2) (b1, b2)  -- Adaptor

This module provides a generic implementation of adaptors and a type synonym for convenience.

Example

{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics

data Foo a b c = Foo { fooA :: a, fooB :: b, fooC :: c } deriving Generic

pFoo :: ProductProfunctor p => Adaptor p (Foo (p a a') (p b b') (p c c'))
pFoo = genericAdaptor

is equivalent to

pFoo :: ProductProfunctor p =>
        Foo (p a a') (p b b') (p c c') -> p (Foo a b c) (Foo a' b' c')
pFoo (Foo a b c) = Foo
  ***$ lmap fooA a
  **** lmap fooB b
  **** lmap fooC c

To use the type synonym Adaptor in versions of GHC older than 8.0.1, Foo must be an instance of Unzippable. You may simply declare a default instance:

instance Unzippable Foo

Synopsis

Documentation

genericAdaptor :: GAdaptable p a b c => a -> p b c Source #

Generic adaptor.

genericAdaptor :: ProductProfunctor p =>
                  Adaptor p (Foo (p a a') (p b b') (p c c'))
genericAdaptor :: ProductProfunctor p =>
                  Foo (p a a') (p b b') (p c c') -> p (Foo a b c) (Foo a' b' c')

type Adaptor p a = a -> p (Unzip Fst a) (Unzip Snd a) Source #

A type synonym to shorten the signature of an adaptor.

Adaptor p (Foo (p a a') (p b b') (p c c'))
~
Foo (p a a') (p b b') (p c c') -> p (Foo a b c) (Foo a' b' c')

class Unzippable (a :: k) Source #

A type like

T = Foo (p a a') (p b b') (p c c')

can be unzipped to

Unzip 'Fst T = Foo a  b  c
Unzip 'Snd T = Foo a' b' c'

This defines the type family Unzip with versions of GHC older than 8.0.1. For 8.0.1 and newer versions, Unzip is an independent type family and Unzippable is just an empty class for backwards compatibility.