one-liner-2.0: Constraint-based generics
LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Generics.OneLiner

Description

All functions without postfix are for instances of Generic, and functions with postfix 1 are for instances of Generic1 (with kind Type -> Type) 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.

Synopsis

Producing values

create :: forall c t. (ADT t, Constraints t c) => (forall s. c s => [s]) -> [t] Source #

Create a value (one for each constructor), given how to construct the components.

minBound = head $ create @Bounded [minBound]
maxBound = last $ create @Bounded [maxBound]

create is createA specialized to lists.

createA :: forall c t f. (ADT t, Constraints t c, Alternative f) => (forall s. c s => f s) -> f t Source #

Create a value (one for each constructor), given how to construct the components, under an applicative effect.

Here's how to implement get from the binary package, first encoding the constructor in a byte:

get = getWord8 >>= \ix -> getCompose (createA @Binary (Compose [get])) !! fromEnum ix

createA is generic specialized to Joker.

ctorIndex :: forall t. ADT t => t -> Int Source #

Get the index in the lists returned by create and createA of the constructor of the given value.

For example, this is the implementation of put that generates the binary data that the above implentation of get expects:

put t = putWord8 (toEnum (ctorIndex t)) <> gfoldMap @Binary put t

create1 :: forall c t a. (ADT1 t, Constraints1 t c) => (forall b s. c s => [b] -> [s b]) -> [a] -> [t a] Source #

create1 is createA1 specialized to lists.

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 #

createA1 is generic1 specialized to Joker.

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 #

Create a value, given a constructor (or a function) and how to construct its components, under an applicative effect.

For example, this is the implementation of arbitrary for a type with a single constructor (e.g., quadruples (,,,)).

arbitrary = createA_ @Arbitrary arbitrary (,,,)

Traversing values

gmap :: forall c t. (ADT t, Constraints t c) => (forall s. c s => s -> s) -> t -> t Source #

Map over a structure, updating each component.

gmap is generic specialized to (->).

gfoldMap :: forall c t m. (ADT t, Constraints t c, Monoid m) => (forall s. c s => s -> m) -> t -> m Source #

Map each component of a structure to a monoid, and combine the results.

If you have a class Size, which measures the size of a structure, then this could be the default implementation:

size = succ . getSum . gfoldMap @Size (Sum . size)

gfoldMap is gtraverse specialized to Const.

gtraverse :: forall c t f. (ADT t, Constraints t c, Applicative f) => (forall s. c s => s -> f s) -> t -> f t Source #

Map each component of a structure to an action, evaluate these actions from left to right, and collect the results.

gtraverse is generic specialized to Star.

glmap :: forall c t. (ADT t, Constraints t c) => (forall s. c s => s %1 -> s) -> t %1 -> t Source #

Map over a structure linearly, updating each component.

glmap is generic specialized to the linear arrow.

glfoldMap :: forall c t m. (ADT t, Constraints t c, Monoid m) => (forall s. c s => s %1 -> m) -> t %1 -> m Source #

Map each component of a structure to a linear monoid, and combine the results.

For example. this could be the default implementation of Consumable:

consume = glfoldMap @Consumable consume

glfoldMap is gltraverse specialized to Const.

gltraverse :: forall c t f. (ADT t, Constraints t c, Applicative f) => (forall s. c s => s %1 -> f s) -> t %1 -> f t Source #

Map each component of a structure to an action linearly, evaluate these actions from left to right, and collect the results.

For example. this could be the default implementations of Dupable and Movable:

dupV = gltraverse @Dupable dupV
move = gltraverse @Movable move

gltraverse is generic specialized to linear Kleisli.

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 #

fmap = gmap1 @Functor fmap

gmap1 is generic1 specialized to (->).

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 #

foldMap = gfoldMap1 @Foldable foldMap

gfoldMap1 is gtraverse1 specialized to Const.

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.

glmap1 :: forall c t a b. (ADT1 t, Constraints1 t c) => (forall d e s. c s => (d %1 -> e) -> s d %1 -> s e) -> (a %1 -> b) -> t a %1 -> t b Source #

fmap = gmap1 @Functor fmap

glmap1 is generic1 specialized to the linear arrow.

gltraverse1 :: forall c t f a b. (ADT1 t, Constraints1 t c, Applicative f) => (forall d e s. c s => (d %1 -> f e) -> s d %1 -> f (s e)) -> (a %1 -> f b) -> t a %1 -> f (t b) Source #

traverse = gltraverse1 @Traversable traverse

gltraverse1 is generic1 specialized to linear Kleisli.

gltraverse01 :: forall c t f a b. (ADT1 t, Constraints01 t Movable c, Applicative f) => (forall d e s. c s => (d %1 -> f e) -> s d %1 -> f (s e)) -> (a %1 -> f b) -> t a %1 -> f (t b) Source #

gltraverse01 is generic01 specialized to linear Kleisli, requiring Movable for constants.

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 #

Combine two values by combining each component of the structures to a monoid, and combine the results. Returns mempty if the constructors don't match.

compare s t = compare (ctorIndex s) (ctorIndex t) <> mzipWith @Ord compare s t

mzipWith is zipWithA specialized to Compose Maybe (Const m)

mzipWith' :: forall c t m. (ADT t, Constraints t c, Monoid m) => m -> (forall s. c s => s -> s -> m) -> t -> t -> m Source #

Variant of mzipWith where you can choose the value which is returned when the constructors don't match.

compare s t = mzipWith` @Ord (compare (ctorIndex s) (ctorIndex t)) compare s t

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 #

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.

zipWithA is generic specialized to Zip

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 #

liftCompare = mzipWith1 @Ord1 liftCompare

mzipWith1 is zipWithA1 specialized to Compose Maybe (Const 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 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 #

zipWithA1 is generic1 specialized to Zip

Consuming values

consume :: forall c t f. (ADT t, Constraints t c, Decidable f) => (forall s. c s => f s) -> f t Source #

Generate ways to consume values of type t. This is the contravariant version of createA.

consume is generic specialized to Clown.

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 #

consume1 is generic1 specialized to Clown.

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 #

Implement a nullary operator by calling the operator for each component.

mempty = nullaryOp @Monoid mempty
fromInteger i = nullaryOp @Num (fromInteger i)

nullaryOp is record specialized to Tagged.

unaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s -> s) -> t -> t Source #

Implement a unary operator by calling the operator on the components. This is here for consistency, it is the same as record.

negate = unaryOp @Num negate

binaryOp :: forall c t. (ADTRecord t, Constraints t c) => (forall s. c s => s -> s -> s) -> t -> t -> t Source #

Implement a binary operator by calling the operator on the components.

mappend = binaryOp @Monoid mappend
(+) = binaryOp @Num (+)

binaryOp is algebra specialized to pairs.

createA' :: forall c t f. (ADTRecord t, Constraints t c, Applicative f) => (forall s. c s => f s) -> f t Source #

Create a value of a record type (with exactly one constructor), given how to construct the components, under an applicative effect.

Here's how to implement get from the binary package:

get = createA` (For :: For Binary) get

createA` is record specialized to Joker.

algebra :: forall c t f. (ADTRecord t, Constraints t c, Functor f) => (forall s. c s => f s -> s) -> f t -> t Source #

Create an F-algebra, given an F-algebra for each of the components.

binaryOp f l r = algebra @c (\(Pair a b) -> f a b) (Pair l r)

algebra is record specialized to Costar.

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 #

dialgebra is record specialized to Biff (->).

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 #

createA1` is record1 specialized to Joker.

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 profunctors.

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, Generic1Profunctor 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.

Instances

Instances details
(Profunctor p, GenericUnitProfunctor p, GenericProductProfunctor p) => GenericRecordProfunctor p Source # 
Instance details

Defined in Generics.OneLiner.Classes

class (GenericRecordProfunctor p, GenericSumProfunctor p) => GenericNonEmptyProfunctor p Source #

A generic function using a GenericNonEmptyProfunctor works on any data type with at least one constructor.

Instances

Instances details
(GenericRecordProfunctor p, GenericSumProfunctor p) => GenericNonEmptyProfunctor p Source # 
Instance details

Defined in Generics.OneLiner.Classes

class (GenericNonEmptyProfunctor p, GenericEmptyProfunctor p) => GenericProfunctor p Source #

A generic function using a GenericProfunctor works on any algebraic data type of kind Type, including those with no constructors and constants.

Instances

Instances details
(GenericNonEmptyProfunctor p, GenericEmptyProfunctor p) => GenericProfunctor p Source # 
Instance details

Defined in Generics.OneLiner.Classes

class (GenericProfunctor p, GenericConstantProfunctor p) => Generic1Profunctor p Source #

A generic function using a Generic1Profunctor works on any algebraic data type of kind Type -> Type, including those with no constructors and constants.

Instances

Instances details
(GenericProfunctor p, GenericConstantProfunctor p) => Generic1Profunctor p Source # 
Instance details

Defined in Generics.OneLiner.Classes

class Profunctor p => GenericUnitProfunctor p where Source #

Methods

unit :: p (U1 a) (U1 a') Source #

Instances

Instances details
Applicative f => GenericUnitProfunctor (Kleisli f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Kleisli f (U1 a) (U1 a') Source #

Applicative f => GenericUnitProfunctor (Zip f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Zip f (U1 a) (U1 a') Source #

GenericUnitProfunctor (Ctor :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Internal

Methods

unit :: Ctor (U1 a) (U1 a') Source #

GenericUnitProfunctor (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Tagged (U1 a) (U1 a') Source #

Functor f => GenericUnitProfunctor (Costar f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Costar f (U1 a) (U1 a') Source #

Applicative f => GenericUnitProfunctor (Star f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Star f (U1 a) (U1 a') Source #

GenericUnitProfunctor (->) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: U1 a -> U1 a' Source #

Divisible f => GenericUnitProfunctor (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Clown f (U1 a) (U1 a') Source #

Applicative f => GenericUnitProfunctor (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Joker f (U1 a) (U1 a') Source #

GenericUnitProfunctor (FUN 'One :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: FUN 'One (U1 a) (U1 a') Source #

(GenericUnitProfunctor p, GenericUnitProfunctor q) => GenericUnitProfunctor (Product p q) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Product p q (U1 a) (U1 a') Source #

(Applicative f, GenericUnitProfunctor p) => GenericUnitProfunctor (Tannen f p) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Tannen f p (U1 a) (U1 a') Source #

(Functor f, Applicative g, Profunctor p, GenericUnitProfunctor p) => GenericUnitProfunctor (Biff p f g) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

unit :: Biff p f g (U1 a) (U1 a') Source #

class Profunctor p => GenericProductProfunctor p where Source #

Methods

mult :: p (f a) (f' a') -> p (g a) (g' a') -> p ((f :*: g) a) ((f' :*: g') a') Source #

Instances

Instances details
Applicative f => GenericProductProfunctor (Kleisli f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Kleisli f (f0 a) (f' a') -> Kleisli f (g a) (g' a') -> Kleisli f ((f0 :*: g) a) ((f' :*: g') a') Source #

Applicative f => GenericProductProfunctor (Zip f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Zip f (f0 a) (f' a') -> Zip f (g a) (g' a') -> Zip f ((f0 :*: g) a) ((f' :*: g') a') Source #

GenericProductProfunctor (Ctor :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Internal

Methods

mult :: Ctor (f a) (f' a') -> Ctor (g a) (g' a') -> Ctor ((f :*: g) a) ((f' :*: g') a') Source #

GenericProductProfunctor (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Tagged (f a) (f' a') -> Tagged (g a) (g' a') -> Tagged ((f :*: g) a) ((f' :*: g') a') Source #

Functor f => GenericProductProfunctor (Costar f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Costar f (f0 a) (f' a') -> Costar f (g a) (g' a') -> Costar f ((f0 :*: g) a) ((f' :*: g') a') Source #

Applicative f => GenericProductProfunctor (Star f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Star f (f0 a) (f' a') -> Star f (g a) (g' a') -> Star f ((f0 :*: g) a) ((f' :*: g') a') Source #

GenericProductProfunctor (->) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: (f a -> f' a') -> (g a -> g' a') -> (f :*: g) a -> (f' :*: g') a' Source #

Divisible f => GenericProductProfunctor (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Clown f (f0 a) (f' a') -> Clown f (g a) (g' a') -> Clown f ((f0 :*: g) a) ((f' :*: g') a') Source #

Applicative f => GenericProductProfunctor (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Joker f (f0 a) (f' a') -> Joker f (g a) (g' a') -> Joker f ((f0 :*: g) a) ((f' :*: g') a') Source #

GenericProductProfunctor (FUN 'One :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: FUN 'One (f a) (f' a') -> FUN 'One (g a) (g' a') -> FUN 'One ((f :*: g) a) ((f' :*: g') a') Source #

(GenericProductProfunctor p, GenericProductProfunctor q) => GenericProductProfunctor (Product p q) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Product p q (f a) (f' a') -> Product p q (g a) (g' a') -> Product p q ((f :*: g) a) ((f' :*: g') a') Source #

(Applicative f, GenericProductProfunctor p) => GenericProductProfunctor (Tannen f p) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Tannen f p (f0 a) (f' a') -> Tannen f p (g a) (g' a') -> Tannen f p ((f0 :*: g) a) ((f' :*: g') a') Source #

(Functor f, Applicative g, Profunctor p, GenericProductProfunctor p) => GenericProductProfunctor (Biff p f g) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

mult :: Biff p f g (f0 a) (f' a') -> Biff p f g (g0 a) (g' a') -> Biff p f g ((f0 :*: g0) a) ((f' :*: g') a') Source #

class Profunctor p => GenericSumProfunctor p where Source #

Methods

plus :: p (f a) (f' a') -> p (g a) (g' a') -> p ((f :+: g) a) ((f' :+: g') a') Source #

Instances

Instances details
Applicative f => GenericSumProfunctor (Kleisli f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: Kleisli f (f0 a) (f' a') -> Kleisli f (g a) (g' a') -> Kleisli f ((f0 :+: g) a) ((f' :+: g') a') Source #

Alternative f => GenericSumProfunctor (Zip f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: Zip f (f0 a) (f' a') -> Zip f (g a) (g' a') -> Zip f ((f0 :+: g) a) ((f' :+: g') a') Source #

GenericSumProfunctor (Ctor :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Internal

Methods

plus :: Ctor (f a) (f' a') -> Ctor (g a) (g' a') -> Ctor ((f :+: g) a) ((f' :+: g') a') Source #

Applicative f => GenericSumProfunctor (Star f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: Star f (f0 a) (f' a') -> Star f (g a) (g' a') -> Star f ((f0 :+: g) a) ((f' :+: g') a') Source #

GenericSumProfunctor (->) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: (f a -> f' a') -> (g a -> g' a') -> (f :+: g) a -> (f' :+: g') a' Source #

Decidable f => GenericSumProfunctor (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: Clown f (f0 a) (f' a') -> Clown f (g a) (g' a') -> Clown f ((f0 :+: g) a) ((f' :+: g') a') Source #

Alternative f => GenericSumProfunctor (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: Joker f (f0 a) (f' a') -> Joker f (g a) (g' a') -> Joker f ((f0 :+: g) a) ((f' :+: g') a') Source #

GenericSumProfunctor (FUN 'One :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: FUN 'One (f a) (f' a') -> FUN 'One (g a) (g' a') -> FUN 'One ((f :+: g) a) ((f' :+: g') a') Source #

(GenericSumProfunctor p, GenericSumProfunctor q) => GenericSumProfunctor (Product p q) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: Product p q (f a) (f' a') -> Product p q (g a) (g' a') -> Product p q ((f :+: g) a) ((f' :+: g') a') Source #

(Applicative f, GenericSumProfunctor p) => GenericSumProfunctor (Tannen f p) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

plus :: Tannen f p (f0 a) (f' a') -> Tannen f p (g a) (g' a') -> Tannen f p ((f0 :+: g) a) ((f' :+: g') a') Source #

class Profunctor p => GenericEmptyProfunctor p where Source #

Methods

zero :: p (V1 a) (V1 a') Source #

Instances

Instances details
Applicative f => GenericEmptyProfunctor (Kleisli f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: Kleisli f (V1 a) (V1 a') Source #

Functor f => GenericEmptyProfunctor (Zip f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: Zip f (V1 a) (V1 a') Source #

GenericEmptyProfunctor (Ctor :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Internal

Methods

zero :: Ctor (V1 a) (V1 a') Source #

Functor f => GenericEmptyProfunctor (Star f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: Star f (V1 a) (V1 a') Source #

GenericEmptyProfunctor (->) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: V1 a -> V1 a' Source #

Decidable f => GenericEmptyProfunctor (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: Clown f (V1 a) (V1 a') Source #

Alternative f => GenericEmptyProfunctor (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: Joker f (V1 a) (V1 a') Source #

GenericEmptyProfunctor (FUN 'One :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: FUN 'One (V1 a) (V1 a') Source #

(GenericEmptyProfunctor p, GenericEmptyProfunctor q) => GenericEmptyProfunctor (Product p q) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: Product p q (V1 a) (V1 a') Source #

(Applicative f, GenericEmptyProfunctor p) => GenericEmptyProfunctor (Tannen f p) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

zero :: Tannen f p (V1 a) (V1 a') Source #

class Profunctor p => GenericConstantProfunctor p where Source #

Methods

identity :: p c c Source #

Instances

Instances details
Applicative f => GenericConstantProfunctor (Kleisli f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: Kleisli f c c Source #

Alternative f => GenericConstantProfunctor (Zip f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: Zip f c c Source #

GenericConstantProfunctor (Ctor :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Internal

Methods

identity :: Ctor c c Source #

Applicative f => GenericConstantProfunctor (Star f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: Star f c c Source #

GenericConstantProfunctor (->) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: c -> c Source #

Decidable f => GenericConstantProfunctor (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: Clown f c c Source #

Alternative f => GenericConstantProfunctor (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: Joker f c c Source #

GenericConstantProfunctor (FUN 'One :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: FUN 'One c c Source #

(GenericConstantProfunctor p, GenericConstantProfunctor q) => GenericConstantProfunctor (Product p q) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: Product p q c c Source #

(Applicative f, GenericConstantProfunctor p) => GenericConstantProfunctor (Tannen f p) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

identity :: Tannen f p c c Source #

Types

type ADT t = (ADT t t, Constraints t AnyType) Source #

type Constraints t c = Constraints t t (D c) Source #

type ADT1 t = (ADT1 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)

Minimal complete definition

autoApply

Instances

Instances details
FunResult r ~ r => FunConstraints c r Source # 
Instance details

Defined in Generics.OneLiner.Internal

Methods

autoApply :: Applicative f => (forall s. c s => f s) -> f r -> f (FunResult r) Source #

(c a, FunConstraints c b) => FunConstraints c (a -> b) Source # 
Instance details

Defined in Generics.OneLiner.Internal

Methods

autoApply :: Applicative f => (forall s. c s => f s) -> f (a -> b) -> f (FunResult (a -> b)) Source #

type family FunResult t where ... Source #

The result type of a curried function.

If r is not a function type (i.e., does not unify with `_ -> _`):

FunResult (a -> r) ~ r
FunResult (a -> b -> r) ~ r
FunResult (a -> b -> c -> r) ~ r

Equations

FunResult (a -> b) = FunResult b 
FunResult r = r 

class AnyType (a :: k) Source #

Any type is instance of AnyType, you can use it with @AnyType if you don't actually need a class constraint.

Instances

Instances details
AnyType (a :: k) Source # 
Instance details

Defined in Generics.OneLiner.Internal.Unary