| License | BSD-style (see the file LICENSE) |
|---|---|
| Maintainer | sjoerd@w3future.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Trustworthy |
| Language | Haskell98 |
Generics.OneLiner
Contents
Description
- create :: (ADT t, Constraints t c) => for c -> (forall s. c s => [s]) -> [t]
- createA :: (ADT t, Constraints t c, Alternative f) => for c -> (forall s. c s => f s) -> f t
- ctorIndex :: ADT t => t -> Int
- create1 :: (ADT1 t, Constraints1 t c) => for c -> (forall b s. c s => [b] -> [s b]) -> [a] -> [t a]
- createA1 :: (ADT1 t, Constraints1 t c, Alternative f) => for c -> (forall b s. c s => f b -> f (s b)) -> f a -> f (t a)
- ctorIndex1 :: ADT1 t => t a -> Int
- gmap :: (ADT t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t
- gfoldMap :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> m) -> t -> m
- gtraverse :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => s -> f s) -> t -> f t
- gmap1 :: (ADT1 t, Constraints1 t c) => for c -> (forall d e s. c s => (d -> e) -> s d -> s e) -> (a -> b) -> t a -> t b
- gfoldMap1 :: (ADT1 t, Constraints1 t c, Monoid m) => for c -> (forall s b. c s => (b -> m) -> s b -> m) -> (a -> m) -> t a -> m
- gtraverse1 :: (ADT1 t, Constraints1 t c, Applicative f) => for c -> (forall d e s. c s => (d -> f e) -> s d -> f (s e)) -> (a -> f b) -> t a -> f (t b)
- mzipWith :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> s -> m) -> t -> t -> m
- zipWithA :: (ADT t, Constraints t c, Alternative f) => for c -> (forall s. c s => s -> s -> f s) -> t -> t -> f t
- mzipWith1 :: (ADT1 t, Constraints1 t c, Monoid m) => for c -> (forall s b. c s => (b -> b -> m) -> s b -> s b -> m) -> (a -> a -> m) -> t a -> t a -> m
- zipWithA1 :: (ADT1 t, Constraints1 t c, Alternative f) => for c -> (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 :: (ADT t, Constraints t c, Decidable f) => for c -> (forall s. c s => f s) -> f t
- consume1 :: (ADT1 t, Constraints1 t c, Decidable f) => for c -> (forall b s. c s => f b -> f (s b)) -> f a -> f (t a)
- nullaryOp :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s) -> t
- unaryOp :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t
- binaryOp :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s -> s) -> t -> t -> t
- algebra :: (ADTRecord t, Constraints t c, Functor f) => for c -> (forall s. c s => f s -> s) -> f t -> t
- dialgebra :: (ADTRecord t, Constraints t c, Functor f, Applicative g) => for c -> (forall s. c s => f s -> g s) -> f t -> g t
- gcotraverse1 :: (ADTRecord1 t, Constraints1 t c, Functor f) => for c -> (forall d e s. c s => (f d -> e) -> f (s d) -> s e) -> (f a -> b) -> f (t a) -> t b
- class Profunctor p => GenericRecordProfunctor p where
- record :: (ADTRecord t, Constraints t c, GenericRecordProfunctor p) => for c -> (forall s. c s => p s s) -> p t t
- record1 :: (ADTRecord1 t, Constraints1 t c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- class GenericRecordProfunctor p => GenericNonEmptyProfunctor p where
- nonEmpty :: (ADTNonEmpty t, Constraints t c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p t t
- nonEmpty1 :: (ADTNonEmpty1 t, Constraints1 t c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- class GenericNonEmptyProfunctor p => GenericProfunctor p where
- generic :: (ADT t, Constraints t c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p t t
- generic1 :: (ADT1 t, Constraints1 t c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b)
- type ADT t = (Generic t, ADT' (Rep t), Constraints t AnyType)
- type ADTNonEmpty t = (Generic t, ADTNonEmpty' (Rep t), Constraints t AnyType)
- type ADTRecord t = (Generic t, ADTRecord' (Rep t), Constraints t AnyType)
- type Constraints t c = Constraints' (Rep t) c
- type ADT1 t = (Generic1 t, ADT1' (Rep1 t), Constraints1 t AnyType)
- type ADTNonEmpty1 t = (Generic1 t, ADTNonEmpty1' (Rep1 t), Constraints1 t AnyType)
- type ADTRecord1 t = (Generic1 t, ADTRecord1' (Rep1 t), Constraints1 t AnyType)
- type Constraints1 t c = Constraints1' (Rep1 t) c
- data For c = For
- class AnyType a
Producing values
create :: (ADT t, Constraints t c) => for c -> (forall s. c s => [s]) -> [t] Source #
createA :: (ADT t, Constraints t c, Alternative f) => for c -> (forall s. c s => f s) -> f t Source #
create1 :: (ADT1 t, Constraints1 t c) => for c -> (forall b s. c s => [b] -> [s b]) -> [a] -> [t a] Source #
createA1 :: (ADT1 t, Constraints1 t c, Alternative f) => for c -> (forall b s. c s => f b -> f (s b)) -> f a -> f (t a) Source #
ctorIndex1 :: ADT1 t => t a -> Int Source #
Traversing values
gmap :: (ADT t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t Source #
gfoldMap :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> m) -> t -> m Source #
gtraverse :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => s -> f s) -> t -> f t Source #
gmap1 :: (ADT1 t, Constraints1 t c) => for c -> (forall d e s. c s => (d -> e) -> s d -> s e) -> (a -> b) -> t a -> t b Source #
gfoldMap1 :: (ADT1 t, Constraints1 t c, Monoid m) => for c -> (forall s b. c s => (b -> m) -> s b -> m) -> (a -> m) -> t a -> m Source #
gtraverse1 :: (ADT1 t, Constraints1 t c, Applicative f) => for c -> (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(For::ForTraversable)traverse
gtraverse1 is generic1 specialized to Star.
Combining values
mzipWith :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> s -> m) -> t -> t -> m Source #
zipWithA :: (ADT t, Constraints t c, Alternative f) => for c -> (forall s. c s => s -> s -> f s) -> t -> t -> f t Source #
Combine two values by combining each component of the structures with the given function, under an applicative effect.
Returns empty if the constructors don't match.
mzipWith1 :: (ADT1 t, Constraints1 t c, Monoid m) => for c -> (forall s b. c s => (b -> b -> m) -> s b -> s b -> m) -> (a -> a -> m) -> t a -> t a -> m Source #
zipWithA1 :: (ADT1 t, Constraints1 t c, Alternative f) => for c -> (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
consume1 :: (ADT1 t, Constraints1 t c, Decidable f) => for c -> (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 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s) -> t Source #
unaryOp :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t Source #
binaryOp :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s -> s) -> t -> t -> t Source #
algebra :: (ADTRecord t, Constraints t c, Functor f) => for c -> (forall s. c s => f s -> s) -> f t -> t Source #
dialgebra :: (ADTRecord t, Constraints t c, Functor f, Applicative g) => for c -> (forall s. c s => f s -> g s) -> f t -> g t Source #
gcotraverse1 :: (ADTRecord1 t, Constraints1 t c, Functor f) => for c -> (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(For::ForDistributive)cotraverse
gcotraverse1 is record1 specialized to Costar.
Generic programming with profunctors
All the above functions have been implemented using these functions,
using different profunctors.
class Profunctor p => GenericRecordProfunctor p where 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.
Methods
unit :: p (U1 a) (U1 a') Source #
mult :: p (f a) (f' a') -> p (g a) (g' a') -> p ((f :*: g) a) ((f' :*: g') a') Source #
Instances
| GenericRecordProfunctor (->) Source # | |
| Applicative f => GenericRecordProfunctor (Star f) Source # | |
| Functor f => GenericRecordProfunctor (Costar f) Source # | |
| GenericRecordProfunctor (Tagged *) Source # | |
| GenericRecordProfunctor (Ctor *) Source # | |
| Applicative f => GenericRecordProfunctor (Joker * * f) Source # | |
| Divisible f => GenericRecordProfunctor (Clown * * f) Source # | |
| (GenericRecordProfunctor p, GenericRecordProfunctor q) => GenericRecordProfunctor (Product * * p q) Source # | |
| (Applicative f, GenericRecordProfunctor p) => GenericRecordProfunctor (Tannen * * * f p) Source # | |
| (Functor f, Applicative g) => GenericRecordProfunctor (Biff * * * * (->) f g) Source # | |
record :: (ADTRecord t, Constraints t c, GenericRecordProfunctor p) => for c -> (forall s. c s => p s s) -> p t t Source #
record1 :: (ADTRecord1 t, Constraints1 t c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
class GenericRecordProfunctor p => GenericNonEmptyProfunctor p where Source #
A generic function using a GenericNonEmptyProfunctor works on any data
type with at least one constructor.
Minimal complete definition
Instances
| GenericNonEmptyProfunctor (->) Source # | |
| Applicative f => GenericNonEmptyProfunctor (Star f) Source # | |
| GenericNonEmptyProfunctor (Ctor *) Source # | |
| Alternative f => GenericNonEmptyProfunctor (Joker * * f) Source # | |
| Decidable f => GenericNonEmptyProfunctor (Clown * * f) Source # | |
| (GenericNonEmptyProfunctor p, GenericNonEmptyProfunctor q) => GenericNonEmptyProfunctor (Product * * p q) Source # | |
| (Applicative f, GenericNonEmptyProfunctor p) => GenericNonEmptyProfunctor (Tannen * * * f p) Source # | |
nonEmpty :: (ADTNonEmpty t, Constraints t c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p t t Source #
nonEmpty1 :: (ADTNonEmpty1 t, Constraints1 t c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
class GenericNonEmptyProfunctor p => GenericProfunctor p where Source #
A generic function using a GenericProfunctor works on any
algebraic data type, including those with no constructors.
Minimal complete definition
Instances
| GenericProfunctor (->) Source # | |
| Applicative f => GenericProfunctor (Star f) Source # | |
| GenericProfunctor (Ctor *) Source # | |
| Alternative f => GenericProfunctor (Joker * * f) Source # | |
| Decidable f => GenericProfunctor (Clown * * f) Source # | |
| (GenericProfunctor p, GenericProfunctor q) => GenericProfunctor (Product * * p q) Source # | |
| (Applicative f, GenericProfunctor p) => GenericProfunctor (Tannen * * * f p) Source # | |
generic :: (ADT t, Constraints t c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p t t Source #
generic1 :: (ADT1 t, Constraints1 t c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (t a) (t b) Source #
Types
type ADTNonEmpty t = (Generic t, ADTNonEmpty' (Rep t), Constraints t AnyType) Source #
ADTNonEmpty is a constraint type synonym. An instance is an ADT with *at least* one constructor.
type ADTRecord t = (Generic t, ADTRecord' (Rep t), Constraints t AnyType) Source #
type Constraints t c = Constraints' (Rep t) c Source #
Constraints is a constraint type synonym, containing the constraint
requirements for an instance for t of class c.
It requires an instance of class c for each component of t.
type ADTNonEmpty1 t = (Generic1 t, ADTNonEmpty1' (Rep1 t), Constraints1 t AnyType) Source #
type ADTRecord1 t = (Generic1 t, ADTRecord1' (Rep1 t), Constraints1 t AnyType) Source #
type Constraints1 t c = Constraints1' (Rep1 t) c Source #
Tell the compiler which class we want to use in the traversal. Should be used like this:
(For :: For Show)
Where Show can be any class.
Constructors
| For |