License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
All functions without postfix are for instances of Generic
, and functions
with postfix 1
are for instances of Generic1
(with kind * -> *
) which
get an extra argument to specify how to deal with the parameter.
Functions with postfix 01
are also for Generic1
but they get yet another
argument that, like the Generic
functions, allows handling of constant leaves.
The function createA_
does not require any such instance, but must be given
a constructor explicitly.
- create :: forall c t. (ADT t, Constraints t c) => (forall s. c s => [s]) -> [t]
- createA :: forall c t f. (ADT t, Constraints t c, Alternative f) => (forall s. c s => f s) -> f t
- ctorIndex :: forall t. ADT t => t -> Int
- create1 :: forall c t a. (ADT1 t, Constraints1 t c) => (forall b s. c s => [b] -> [s b]) -> [a] -> [t a]
- createA1 :: forall c t f a. (ADT1 t, Constraints1 t c, Alternative f) => (forall b s. c s => f b -> f (s b)) -> f a -> f (t a)
- ctorIndex1 :: forall t a. ADT1 t => t a -> Int
- createA_ :: forall c t f. (FunConstraints c t, Applicative f) => (forall s. c s => f s) -> t -> f (FunResult t)
- gmap :: forall c t. (ADT t, Constraints t c) => (forall s. c s => s -> s) -> t -> t
- gfoldMap :: forall c t m. (ADT t, Constraints t c, Monoid m) => (forall s. c s => s -> m) -> t -> m
- gtraverse :: forall c t f. (ADT t, Constraints t c, Applicative f) => (forall s. c s => s -> f s) -> t -> f t
- gmap1 :: forall c t a b. (ADT1 t, Constraints1 t c) => (forall d e s. c s => (d -> e) -> s d -> s e) -> (a -> b) -> t a -> t b
- gfoldMap1 :: forall c t m a. (ADT1 t, Constraints1 t c, Monoid m) => (forall s b. c s => (b -> m) -> s b -> m) -> (a -> m) -> t a -> m
- gtraverse1 :: forall c t f a b. (ADT1 t, Constraints1 t c, Applicative f) => (forall d e s. c s => (d -> f e) -> s d -> f (s e)) -> (a -> f b) -> t a -> f (t b)
- mzipWith :: forall c t m. (ADT t, Constraints t c, Monoid m) => (forall s. c s => s -> s -> m) -> t -> t -> m
- mzipWith' :: forall c t m. (ADT t, Constraints t c, Monoid m) => m -> (forall s. c s => s -> s -> m) -> t -> t -> m
- zipWithA :: forall c t f. (ADT t, Constraints t c, Alternative f) => (forall s. c s => s -> s -> f s) -> t -> t -> f t
- mzipWith1 :: forall c t m a. (ADT1 t, Constraints1 t c, Monoid m) => (forall s b. c s => (b -> b -> m) -> s b -> s b -> m) -> (a -> a -> m) -> t a -> t a -> m
- mzipWith1' :: forall c t m a. (ADT1 t, Constraints1 t c, Monoid m) => m -> (forall s b. c s => (b -> b -> m) -> s b -> s b -> m) -> (a -> a -> m) -> t a -> t a -> m
- zipWithA1 :: forall c t f a b. (ADT1 t, Constraints1 t c, Alternative f) => (forall d e s. c s => (d -> d -> f e) -> s d -> s d -> f (s e)) -> (a -> a -> f b) -> t a -> t a -> f (t b)
- consume :: forall c t f. (ADT t, Constraints t c, Decidable f) => (forall s. c s => f s) -> f t
- consume1 :: forall c t f a. (ADT1 t, Constraints1 t c, Decidable f) => (forall b s. c s => f b -> f (s b)) -> f a -> f (t a)
- nullaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s) -> t
- unaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s -> s) -> t -> t
- binaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s -> s -> s) -> t -> t -> t
- createA' :: forall c t f. (ADTRecord t, Constraints t c, Applicative f) => (forall s. c s => f s) -> f t
- algebra :: forall c t f. (ADTRecord t, Constraints t c, Functor f) => (forall s. c s => f s -> s) -> f t -> t
- dialgebra :: forall c t f g. (ADTRecord t, Constraints t c, Functor f, Applicative g) => (forall s. c s => f s -> g s) -> f t -> g t
- createA1' :: forall c t f a. (ADTRecord1 t, Constraints1 t c, Applicative f) => (forall b s. c s => f b -> f (s b)) -> f a -> f (t a)
- gcotraverse1 :: forall c t f a b. (ADTRecord1 t, Constraints1 t c, Functor f) => (forall d e s. c s => (f d -> e) -> f (s d) -> s e) -> (f a -> b) -> f (t a) -> t b
- record :: forall c p t. (ADTRecord t, Constraints t c, GenericRecordProfunctor p) => (forall s. c s => p s s) -> p t t
- nonEmpty :: forall c p t. (ADTNonEmpty t, Constraints t c, GenericNonEmptyProfunctor p) => (forall s. c s => p s s) -> p t t
- generic :: forall c p t. (ADT t, Constraints t c, GenericProfunctor p) => (forall s. c s => p s s) -> p t t
- record1 :: forall c p t a b. (ADTRecord1 t, Constraints1 t c, GenericRecordProfunctor p) => (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- nonEmpty1 :: forall c p t a b. (ADTNonEmpty1 t, Constraints1 t c, GenericNonEmptyProfunctor p) => (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- generic1 :: forall c p t a b. (ADT1 t, Constraints1 t c, GenericProfunctor p) => (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- record01 :: forall c0 c1 p t a b. (ADTRecord1 t, Constraints01 t c0 c1, GenericRecordProfunctor p) => (forall s. c0 s => p s s) -> (forall d e s. c1 s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- nonEmpty01 :: forall c0 c1 p t a b. (ADTNonEmpty1 t, Constraints01 t c0 c1, GenericNonEmptyProfunctor p) => (forall s. c0 s => p s s) -> (forall d e s. c1 s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- generic01 :: forall c0 c1 p t a b. (ADT1 t, Constraints01 t c0 c1, GenericProfunctor p) => (forall s. c0 s => p s s) -> (forall d e s. c1 s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- class (Profunctor p, GenericUnitProfunctor p, GenericProductProfunctor p) => GenericRecordProfunctor p
- class (GenericRecordProfunctor p, GenericSumProfunctor p) => GenericNonEmptyProfunctor p
- class (GenericNonEmptyProfunctor p, GenericEmptyProfunctor p) => GenericProfunctor p
- class Profunctor p => GenericUnitProfunctor p where
- class Profunctor p => GenericProductProfunctor p where
- class Profunctor p => GenericSumProfunctor p where
- class Profunctor p => GenericEmptyProfunctor p where
- type ADT t = (ADT t t, Constraints t AnyType)
- type ADTNonEmpty t = (ADTNonEmpty t t, Constraints t AnyType)
- type ADTRecord t = (ADTRecord t t, Constraints t AnyType)
- type Constraints t c = Constraints t t (D c)
- type ADT1 t = (ADT1 t t, Constraints1 t AnyType)
- type ADTNonEmpty1 t = (ADTNonEmpty1 t t, Constraints1 t AnyType)
- type ADTRecord1 t = (ADTRecord1 t t, Constraints1 t AnyType)
- type Constraints1 t c = Constraints1 t t (D c)
- type Constraints01 t c0 c1 = Constraints01 t t (D c0) (D c1)
- class FunConstraints c t
- type family FunResult t where ...
- class AnyType (a :: k)
Producing values
create :: forall c t. (ADT t, Constraints t c) => (forall s. c s => [s]) -> [t] Source #
createA :: forall c t f. (ADT t, Constraints t c, Alternative f) => (forall s. c s => f s) -> f t Source #
create1 :: forall c t a. (ADT1 t, Constraints1 t c) => (forall b s. c s => [b] -> [s b]) -> [a] -> [t a] Source #
createA1 :: forall c t f a. (ADT1 t, Constraints1 t c, Alternative f) => (forall b s. c s => f b -> f (s b)) -> f a -> f (t a) Source #
ctorIndex1 :: forall t a. ADT1 t => t a -> Int Source #
createA_ :: forall c t f. (FunConstraints c t, Applicative f) => (forall s. c s => f s) -> t -> f (FunResult t) Source #
Traversing values
gmap :: forall c t. (ADT t, Constraints t c) => (forall s. c s => s -> s) -> t -> t Source #
gfoldMap :: forall c t m. (ADT t, Constraints t c, Monoid m) => (forall s. c s => s -> m) -> t -> m Source #
gtraverse :: forall c t f. (ADT t, Constraints t c, Applicative f) => (forall s. c s => s -> f s) -> t -> f t Source #
gmap1 :: forall c t a b. (ADT1 t, Constraints1 t c) => (forall d e s. c s => (d -> e) -> s d -> s e) -> (a -> b) -> t a -> t b Source #
gfoldMap1 :: forall c t m a. (ADT1 t, Constraints1 t c, Monoid m) => (forall s b. c s => (b -> m) -> s b -> m) -> (a -> m) -> t a -> m Source #
gtraverse1 :: forall c t f a b. (ADT1 t, Constraints1 t c, Applicative f) => (forall d e s. c s => (d -> f e) -> s d -> f (s e)) -> (a -> f b) -> t a -> f (t b) Source #
traverse =gtraverse1
@Traversable
traverse
gtraverse1
is generic1
specialized to Star
.
Combining values
mzipWith :: forall c t m. (ADT t, Constraints t c, Monoid m) => (forall s. c s => s -> s -> m) -> t -> t -> m Source #
mzipWith' :: forall c t m. (ADT t, Constraints t c, Monoid m) => m -> (forall s. c s => s -> s -> m) -> t -> t -> m Source #
zipWithA :: forall c t f. (ADT t, Constraints t c, Alternative f) => (forall s. c s => s -> s -> f s) -> t -> t -> f t Source #
mzipWith1 :: forall c t m a. (ADT1 t, Constraints1 t c, Monoid m) => (forall s b. c s => (b -> b -> m) -> s b -> s b -> m) -> (a -> a -> m) -> t a -> t a -> m Source #
mzipWith1' :: forall c t m a. (ADT1 t, Constraints1 t c, Monoid m) => m -> (forall s b. c s => (b -> b -> m) -> s b -> s b -> m) -> (a -> a -> m) -> t a -> t a -> m Source #
Variant of mzipWith1
where you can choose the value which is returned
when the constructors don't match.
zipWithA1 :: forall c t f a b. (ADT1 t, Constraints1 t c, Alternative f) => (forall d e s. c s => (d -> d -> f e) -> s d -> s d -> f (s e)) -> (a -> a -> f b) -> t a -> t a -> f (t b) Source #
Consuming values
consume :: forall c t f. (ADT t, Constraints t c, Decidable f) => (forall s. c s => f s) -> f t Source #
consume1 :: forall c t f a. (ADT1 t, Constraints1 t c, Decidable f) => (forall b s. c s => f b -> f (s b)) -> f a -> f (t a) Source #
Functions for records
These functions only work for single constructor data types.
nullaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s) -> t Source #
unaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s -> s) -> t -> t Source #
binaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s -> s -> s) -> t -> t -> t Source #
createA' :: forall c t f. (ADTRecord t, Constraints t c, Applicative f) => (forall s. c s => f s) -> f t Source #
algebra :: forall c t f. (ADTRecord t, Constraints t c, Functor f) => (forall s. c s => f s -> s) -> f t -> t Source #
dialgebra :: forall c t f g. (ADTRecord t, Constraints t c, Functor f, Applicative g) => (forall s. c s => f s -> g s) -> f t -> g t Source #
createA1' :: forall c t f a. (ADTRecord1 t, Constraints1 t c, Applicative f) => (forall b s. c s => f b -> f (s b)) -> f a -> f (t a) Source #
gcotraverse1 :: forall c t f a b. (ADTRecord1 t, Constraints1 t c, Functor f) => (forall d e s. c s => (f d -> e) -> f (s d) -> s e) -> (f a -> b) -> f (t a) -> t b Source #
cotraverse =gcotraverse1
@Distributive
cotraverse
gcotraverse1
is record1
specialized to Costar
.
Generic programming with profunctors
All the above functions have been implemented using these functions,
using different profunctor
s.
record :: forall c p t. (ADTRecord t, Constraints t c, GenericRecordProfunctor p) => (forall s. c s => p s s) -> p t t Source #
nonEmpty :: forall c p t. (ADTNonEmpty t, Constraints t c, GenericNonEmptyProfunctor p) => (forall s. c s => p s s) -> p t t Source #
generic :: forall c p t. (ADT t, Constraints t c, GenericProfunctor p) => (forall s. c s => p s s) -> p t t Source #
record1 :: forall c p t a b. (ADTRecord1 t, Constraints1 t c, GenericRecordProfunctor p) => (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
nonEmpty1 :: forall c p t a b. (ADTNonEmpty1 t, Constraints1 t c, GenericNonEmptyProfunctor p) => (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
generic1 :: forall c p t a b. (ADT1 t, Constraints1 t c, GenericProfunctor p) => (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
record01 :: forall c0 c1 p t a b. (ADTRecord1 t, Constraints01 t c0 c1, GenericRecordProfunctor p) => (forall s. c0 s => p s s) -> (forall d e s. c1 s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
nonEmpty01 :: forall c0 c1 p t a b. (ADTNonEmpty1 t, Constraints01 t c0 c1, GenericNonEmptyProfunctor p) => (forall s. c0 s => p s s) -> (forall d e s. c1 s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
generic01 :: forall c0 c1 p t a b. (ADT1 t, Constraints01 t c0 c1, GenericProfunctor p) => (forall s. c0 s => p s s) -> (forall d e s. c1 s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
Classes
class (Profunctor p, GenericUnitProfunctor p, GenericProductProfunctor p) => GenericRecordProfunctor p Source #
A generic function using a GenericRecordProfunctor
works on any data type
with exactly one constructor, a.k.a. records,
with multiple fields (mult
) or no fields (unit
).
GenericRecordProfunctor
is similar to ProductProfuctor
from the
product-profunctor package, but using types from GHC.Generics.
class (GenericRecordProfunctor p, GenericSumProfunctor p) => GenericNonEmptyProfunctor p Source #
A generic function using a GenericNonEmptyProfunctor
works on any data
type with at least one constructor.
class (GenericNonEmptyProfunctor p, GenericEmptyProfunctor p) => GenericProfunctor p Source #
A generic function using a GenericProfunctor
works on any
algebraic data type, including those with no constructors and constants.
class Profunctor p => GenericUnitProfunctor p where Source #
Applicative f => GenericUnitProfunctor (Star f) Source # | |
Functor f => GenericUnitProfunctor (Costar f) Source # | |
GenericUnitProfunctor (Tagged *) Source # | |
Applicative f => GenericUnitProfunctor (Zip f) Source # | |
GenericUnitProfunctor (Ctor *) Source # | |
GenericUnitProfunctor ((->) LiftedRep LiftedRep) Source # | |
Applicative f => GenericUnitProfunctor (Joker * * f) Source # | |
Divisible f => GenericUnitProfunctor (Clown * * f) Source # | |
(GenericUnitProfunctor p, GenericUnitProfunctor q) => GenericUnitProfunctor (Product * * p q) Source # | |
(Applicative f, GenericUnitProfunctor p) => GenericUnitProfunctor (Tannen * * * f p) Source # | |
(Functor f, Applicative g, Profunctor p, GenericUnitProfunctor p) => GenericUnitProfunctor (Biff * * * * p f g) Source # | |
class Profunctor p => GenericProductProfunctor p where Source #
Applicative f => GenericProductProfunctor (Star f) Source # | |
Functor f => GenericProductProfunctor (Costar f) Source # | |
GenericProductProfunctor (Tagged *) Source # | |
Applicative f => GenericProductProfunctor (Zip f) Source # | |
GenericProductProfunctor (Ctor *) Source # | |
GenericProductProfunctor ((->) LiftedRep LiftedRep) Source # | |
Applicative f => GenericProductProfunctor (Joker * * f) Source # | |
Divisible f => GenericProductProfunctor (Clown * * f) Source # | |
(GenericProductProfunctor p, GenericProductProfunctor q) => GenericProductProfunctor (Product * * p q) Source # | |
(Applicative f, GenericProductProfunctor p) => GenericProductProfunctor (Tannen * * * f p) Source # | |
(Functor f, Applicative g, Profunctor p, GenericProductProfunctor p) => GenericProductProfunctor (Biff * * * * p f g) Source # | |
class Profunctor p => GenericSumProfunctor p where Source #
Applicative f => GenericSumProfunctor (Star f) Source # | |
Alternative f => GenericSumProfunctor (Zip f) Source # | |
GenericSumProfunctor (Ctor *) Source # | |
GenericSumProfunctor ((->) LiftedRep LiftedRep) Source # | |
Alternative f => GenericSumProfunctor (Joker * * f) Source # | |
Decidable f => GenericSumProfunctor (Clown * * f) Source # | |
(GenericSumProfunctor p, GenericSumProfunctor q) => GenericSumProfunctor (Product * * p q) Source # | |
(Applicative f, GenericSumProfunctor p) => GenericSumProfunctor (Tannen * * * f p) Source # | |
class Profunctor p => GenericEmptyProfunctor p where Source #
Applicative f => GenericEmptyProfunctor (Star f) Source # | |
Alternative f => GenericEmptyProfunctor (Zip f) Source # | |
GenericEmptyProfunctor (Ctor *) Source # | |
GenericEmptyProfunctor ((->) LiftedRep LiftedRep) Source # | |
Alternative f => GenericEmptyProfunctor (Joker * * f) Source # | |
Decidable f => GenericEmptyProfunctor (Clown * * f) Source # | |
(GenericEmptyProfunctor p, GenericEmptyProfunctor q) => GenericEmptyProfunctor (Product * * p q) Source # | |
(Applicative f, GenericEmptyProfunctor p) => GenericEmptyProfunctor (Tannen * * * f p) Source # | |
Types
type ADTNonEmpty t = (ADTNonEmpty t t, Constraints t AnyType) Source #
type Constraints t c = Constraints t t (D c) Source #
type ADTNonEmpty1 t = (ADTNonEmpty1 t t, Constraints1 t AnyType) Source #
type ADTRecord1 t = (ADTRecord1 t t, Constraints1 t AnyType) Source #
type Constraints1 t c = Constraints1 t t (D c) Source #
type Constraints01 t c0 c1 = Constraints01 t t (D c0) (D c1) Source #
class FunConstraints c t Source #
Automatically apply a lifted function to a polymorphic argument as many times as possible.
A constraint `FunConstraint c t` is equivalent to the conjunction of
constraints `c s` for every argument type of t
.
If r
is not a function type:
c a :- FunConstraints c (a -> r) (c a, c b) :- FunConstraints c (a -> b -> r) (c a, c b, c d) :- FunConstraints c (a -> b -> d -> r)
(~) * (FunResult r) r => FunConstraints c r Source # | |
(c a, FunConstraints c b) => FunConstraints c (a -> b) Source # | |