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

Generics.OneLiner.Classes

Description

 
Synopsis

Documentation

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

dimapForget :: Profunctor p => (a %1 -> b) -> (c %1 -> d) -> p b c -> p a d Source #

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 => 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 #

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 #

newtype Zip f a b Source #

Constructors

Zip 

Fields

Instances

Instances details
Functor f => Profunctor (Zip f) Source # 
Instance details

Defined in Generics.OneLiner.Classes

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Zip f a b -> Zip f s t #

lmap :: (s %1 -> a) -> Zip f a t -> Zip f s t #

rmap :: (b %1 -> t) -> Zip f s b -> Zip f s t #

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

Defined in Generics.OneLiner.Classes

Methods

identity :: Zip f c c Source #

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

Defined in Generics.OneLiner.Classes

Methods

zero :: Zip f (V1 a) (V1 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 #

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 #

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

Defined in Generics.OneLiner.Classes

Methods

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

e1 :: (f a %m -> b) -> (g a %m -> b) -> (f :+: g) a %m -> b Source #

fst1 :: (f :*: g) a -> f a Source #

snd1 :: (f :*: g) a -> g a Source #

Orphan instances

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

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Tagged a b -> Tagged s t #

lmap :: (s %1 -> a) -> Tagged a t -> Tagged s t #

rmap :: (b %1 -> t) -> Tagged s b -> Tagged s t #

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

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Costar f a b -> Costar f s t #

lmap :: (s %1 -> a) -> Costar f a t -> Costar f s t #

rmap :: (b %1 -> t) -> Costar f s b -> Costar f s t #

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

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Star f a b -> Star f s t #

lmap :: (s %1 -> a) -> Star f a t -> Star f s t #

rmap :: (b %1 -> t) -> Star f s b -> Star f s t #

Contravariant f => Profunctor (Clown f :: Type -> Type -> Type) Source # 
Instance details

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Clown f a b -> Clown f s t #

lmap :: (s %1 -> a) -> Clown f a t -> Clown f s t #

rmap :: (b %1 -> t) -> Clown f s b -> Clown f s t #

Functor f => Profunctor (Joker f :: Type -> Type -> Type) Source # 
Instance details

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Joker f a b -> Joker f s t #

lmap :: (s %1 -> a) -> Joker f a t -> Joker f s t #

rmap :: (b %1 -> t) -> Joker f s b -> Joker f s t #

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

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> FUN 'One a b -> FUN 'One s t #

lmap :: (s %1 -> a) -> FUN 'One a t -> FUN 'One s t #

rmap :: (b %1 -> t) -> FUN 'One s b -> FUN 'One s t #

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

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Product p q a b -> Product p q s t #

lmap :: (s %1 -> a) -> Product p q a t -> Product p q s t #

rmap :: (b %1 -> t) -> Product p q s b -> Product p q s t #

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

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Tannen f p a b -> Tannen f p s t #

lmap :: (s %1 -> a) -> Tannen f p a t -> Tannen f p s t #

rmap :: (b %1 -> t) -> Tannen f p s b -> Tannen f p s t #

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

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Biff p f g a b -> Biff p f g s t #

lmap :: (s %1 -> a) -> Biff p f g a t -> Biff p f g s t #

rmap :: (b %1 -> t) -> Biff p f g s b -> Biff p f g s t #