one-liner-0.7: Constraint-based generics

LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Generics.OneLiner.Internal

Description

 

Synopsis

Documentation

type family Constraints' (t :: * -> *) (c :: * -> Constraint) :: Constraint Source #

Instances

type Constraints' V1 c Source # 
type Constraints' V1 c = ()
type Constraints' U1 c Source # 
type Constraints' U1 c = ()
type Constraints' (K1 i a) c Source # 
type Constraints' (K1 i a) c = c a
type Constraints' ((:+:) f g) c Source # 
type Constraints' ((:+:) f g) c = (Constraints' f c, Constraints' g c)
type Constraints' ((:*:) f g) c Source # 
type Constraints' ((:*:) f g) c = (Constraints' f c, Constraints' g c)
type Constraints' (M1 i t f) c Source # 
type Constraints' (M1 i t f) c = Constraints' f c

class ADT' t where Source #

Minimal complete definition

generic'

Methods

generic' :: (Constraints' t c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p (t x) (t x) Source #

Instances

ADT' V1 Source # 

Methods

generic' :: (Constraints' V1 c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p (V1 x) (V1 x) Source #

ADT' U1 Source # 

Methods

generic' :: (Constraints' U1 c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p (U1 x) (U1 x) Source #

ADT' (K1 i v) Source # 

Methods

generic' :: (Constraints' (K1 i v) c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p (K1 i v x) (K1 i v x) Source #

(ADT' f, ADT' g) => ADT' ((:+:) f g) Source # 

Methods

generic' :: (Constraints' (f :+: g) c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p ((f :+: g) x) ((f :+: g) x) Source #

(ADT' f, ADT' g) => ADT' ((:*:) f g) Source # 

Methods

generic' :: (Constraints' (f :*: g) c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p ((f :*: g) x) ((f :*: g) x) Source #

ADT' f => ADT' (M1 i t f) Source # 

Methods

generic' :: (Constraints' (M1 i t f) c, GenericProfunctor p) => for c -> (forall s. c s => p s s) -> p (M1 i t f x) (M1 i t f x) Source #

class ADTNonEmpty' t where Source #

Minimal complete definition

nonEmpty'

Methods

nonEmpty' :: (Constraints' t c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p (t x) (t x) Source #

Instances

ADTNonEmpty' U1 Source # 

Methods

nonEmpty' :: (Constraints' U1 c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p (U1 x) (U1 x) Source #

ADTNonEmpty' (K1 i v) Source # 

Methods

nonEmpty' :: (Constraints' (K1 i v) c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p (K1 i v x) (K1 i v x) Source #

(ADTNonEmpty' f, ADTNonEmpty' g) => ADTNonEmpty' ((:+:) f g) Source # 

Methods

nonEmpty' :: (Constraints' (f :+: g) c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p ((f :+: g) x) ((f :+: g) x) Source #

(ADTNonEmpty' f, ADTNonEmpty' g) => ADTNonEmpty' ((:*:) f g) Source # 

Methods

nonEmpty' :: (Constraints' (f :*: g) c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p ((f :*: g) x) ((f :*: g) x) Source #

ADTNonEmpty' f => ADTNonEmpty' (M1 i t f) Source # 

Methods

nonEmpty' :: (Constraints' (M1 i t f) c, GenericNonEmptyProfunctor p) => for c -> (forall s. c s => p s s) -> p (M1 i t f x) (M1 i t f x) Source #

class ADTRecord' t where Source #

Minimal complete definition

record'

Methods

record' :: (Constraints' t c, GenericRecordProfunctor p) => for c -> (forall s. c s => p s s) -> p (t x) (t x) Source #

Instances

ADTRecord' U1 Source # 

Methods

record' :: (Constraints' U1 c, GenericRecordProfunctor p) => for c -> (forall s. c s => p s s) -> p (U1 x) (U1 x) Source #

ADTRecord' (K1 i v) Source # 

Methods

record' :: (Constraints' (K1 i v) c, GenericRecordProfunctor p) => for c -> (forall s. c s => p s s) -> p (K1 i v x) (K1 i v x) Source #

(ADTRecord' f, ADTRecord' g) => ADTRecord' ((:*:) f g) Source # 

Methods

record' :: (Constraints' (f :*: g) c, GenericRecordProfunctor p) => for c -> (forall s. c s => p s s) -> p ((f :*: g) x) ((f :*: g) x) Source #

ADTRecord' f => ADTRecord' (M1 i t f) Source # 

Methods

record' :: (Constraints' (M1 i t f) c, GenericRecordProfunctor p) => for c -> (forall s. c s => p s s) -> p (M1 i t f x) (M1 i t f x) Source #

type family Constraints1' (t :: * -> *) (c :: (* -> *) -> Constraint) :: Constraint Source #

Instances

type Constraints1' V1 c Source # 
type Constraints1' V1 c = ()
type Constraints1' U1 c Source # 
type Constraints1' U1 c = ()
type Constraints1' Par1 c Source # 
type Constraints1' Par1 c = ()
type Constraints1' (Rec1 f) c Source # 
type Constraints1' (Rec1 f) c = c f
type Constraints1' ((:+:) f g) c Source # 
type Constraints1' ((:*:) f g) c Source # 
type Constraints1' ((:.:) f g) c Source # 
type Constraints1' ((:.:) f g) c = (c f, Constraints1' g c)
type Constraints1' (M1 i t f) c Source # 
type Constraints1' (M1 i t f) c = Constraints1' f c

class ADT1' t where Source #

Minimal complete definition

generic1'

Methods

generic1' :: (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 #

Instances

ADT1' V1 Source # 

Methods

generic1' :: (Constraints1' V1 c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (V1 a) (V1 b) Source #

ADT1' U1 Source # 

Methods

generic1' :: (Constraints1' U1 c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (U1 a) (U1 b) Source #

ADT1' Par1 Source # 

Methods

generic1' :: (Constraints1' Par1 c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (Par1 a) (Par1 b) Source #

ADT1' (Rec1 f) Source # 

Methods

generic1' :: (Constraints1' (Rec1 f) c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (Rec1 f a) (Rec1 f b) Source #

(ADT1' f, ADT1' g) => ADT1' ((:+:) f g) Source # 

Methods

generic1' :: (Constraints1' (f :+: g) c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :+: g) a) ((f :+: g) b) Source #

(ADT1' f, ADT1' g) => ADT1' ((:*:) f g) Source # 

Methods

generic1' :: (Constraints1' (f :*: g) c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :*: g) a) ((f :*: g) b) Source #

ADT1' g => ADT1' ((:.:) f g) Source # 

Methods

generic1' :: (Constraints1' (f :.: g) c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :.: g) a) ((f :.: g) b) Source #

ADT1' f => ADT1' (M1 i t f) Source # 

Methods

generic1' :: (Constraints1' (M1 i t f) c, GenericProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (M1 i t f a) (M1 i t f b) Source #

class ADTNonEmpty1' t where Source #

Minimal complete definition

nonEmpty1'

Methods

nonEmpty1' :: (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 #

Instances

ADTNonEmpty1' U1 Source # 

Methods

nonEmpty1' :: (Constraints1' U1 c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (U1 a) (U1 b) Source #

ADTNonEmpty1' Par1 Source # 

Methods

nonEmpty1' :: (Constraints1' Par1 c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (Par1 a) (Par1 b) Source #

ADTNonEmpty1' (Rec1 f) Source # 

Methods

nonEmpty1' :: (Constraints1' (Rec1 f) c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (Rec1 f a) (Rec1 f b) Source #

(ADTNonEmpty1' f, ADTNonEmpty1' g) => ADTNonEmpty1' ((:+:) f g) Source # 

Methods

nonEmpty1' :: (Constraints1' (f :+: g) c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :+: g) a) ((f :+: g) b) Source #

(ADTNonEmpty1' f, ADTNonEmpty1' g) => ADTNonEmpty1' ((:*:) f g) Source # 

Methods

nonEmpty1' :: (Constraints1' (f :*: g) c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :*: g) a) ((f :*: g) b) Source #

ADTNonEmpty1' g => ADTNonEmpty1' ((:.:) f g) Source # 

Methods

nonEmpty1' :: (Constraints1' (f :.: g) c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :.: g) a) ((f :.: g) b) Source #

ADTNonEmpty1' f => ADTNonEmpty1' (M1 i t f) Source # 

Methods

nonEmpty1' :: (Constraints1' (M1 i t f) c, GenericNonEmptyProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (M1 i t f a) (M1 i t f b) Source #

class ADTRecord1' t where Source #

Minimal complete definition

record1'

Methods

record1' :: (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 #

Instances

ADTRecord1' U1 Source # 

Methods

record1' :: (Constraints1' U1 c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (U1 a) (U1 b) Source #

ADTRecord1' Par1 Source # 

Methods

record1' :: (Constraints1' Par1 c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (Par1 a) (Par1 b) Source #

ADTRecord1' (Rec1 f) Source # 

Methods

record1' :: (Constraints1' (Rec1 f) c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (Rec1 f a) (Rec1 f b) Source #

(ADTRecord1' f, ADTRecord1' g) => ADTRecord1' ((:*:) f g) Source # 

Methods

record1' :: (Constraints1' (f :*: g) c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :*: g) a) ((f :*: g) b) Source #

ADTRecord1' g => ADTRecord1' ((:.:) f g) Source # 

Methods

record1' :: (Constraints1' (f :.: g) c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p ((f :.: g) a) ((f :.: g) b) Source #

ADTRecord1' f => ADTRecord1' (M1 i t f) Source # 

Methods

record1' :: (Constraints1' (M1 i t f) c, GenericRecordProfunctor p) => for c -> (forall d e s. c s => p d e -> p (s d) (s e)) -> p a b -> p (M1 i t f a) (M1 i t f b) Source #

absurd :: V1 a -> b Source #

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

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

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

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.

Minimal complete definition

unit, mult

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 # 

Methods

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

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

Applicative f => GenericRecordProfunctor (Star f) Source # 

Methods

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

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

Functor f => GenericRecordProfunctor (Costar f) Source # 

Methods

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

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

GenericRecordProfunctor (Tagged *) Source # 

Methods

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

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

GenericRecordProfunctor (Ctor *) Source # 

Methods

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

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

Applicative f => GenericRecordProfunctor (Joker * * f) Source # 

Methods

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

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

Divisible f => GenericRecordProfunctor (Clown * * f) Source # 

Methods

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

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

(GenericRecordProfunctor p, GenericRecordProfunctor q) => GenericRecordProfunctor (Product * * p q) Source # 

Methods

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

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, GenericRecordProfunctor p) => GenericRecordProfunctor (Tannen * * * f p) Source # 

Methods

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

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

(Functor f, Applicative g) => GenericRecordProfunctor (Biff * * * * (->) f g) Source # 

Methods

unit :: Biff * * * * (->) f g (U1 a) (U1 a') Source #

mult :: Biff * * * * (->) f g (f a) (f' a') -> Biff * * * * (->) f g (g a) (g' a') -> Biff * * * * (->) f g ((f :*: g) a) ((f' :*: g') a') 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

plus

Methods

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

Instances

GenericNonEmptyProfunctor (->) Source # 

Methods

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

Applicative f => GenericNonEmptyProfunctor (Star f) Source # 

Methods

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

GenericNonEmptyProfunctor (Ctor *) Source # 

Methods

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

Alternative f => GenericNonEmptyProfunctor (Joker * * f) Source # 

Methods

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

Decidable f => GenericNonEmptyProfunctor (Clown * * f) Source # 

Methods

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

(GenericNonEmptyProfunctor p, GenericNonEmptyProfunctor q) => GenericNonEmptyProfunctor (Product * * p q) Source # 

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, GenericNonEmptyProfunctor p) => GenericNonEmptyProfunctor (Tannen * * * f p) Source # 

Methods

plus :: Tannen * * * f p (f a) (f' a') -> Tannen * * * f p (g a) (g' a') -> Tannen * * * f p ((f :+: g) a) ((f' :+: g') a') 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

zero

Methods

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

Instances

GenericProfunctor (->) Source # 

Methods

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

Applicative f => GenericProfunctor (Star f) Source # 

Methods

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

GenericProfunctor (Ctor *) Source # 

Methods

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

Alternative f => GenericProfunctor (Joker * * f) Source # 

Methods

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

Decidable f => GenericProfunctor (Clown * * f) Source # 

Methods

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

(GenericProfunctor p, GenericProfunctor q) => GenericProfunctor (Product * * p q) Source # 

Methods

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

(Applicative f, GenericProfunctor p) => GenericProfunctor (Tannen * * * f p) Source # 

Methods

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

data Ctor a b Source #

Constructors

Ctor 

Fields

Instances

Profunctor (Ctor *) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Ctor * b c -> Ctor * a d #

lmap :: (a -> b) -> Ctor * b c -> Ctor * a c #

rmap :: (b -> c) -> Ctor * a b -> Ctor * a c #

(#.) :: Coercible * c b => (b -> c) -> Ctor * a b -> Ctor * a c #

(.#) :: Coercible * b a => Ctor * b c -> (a -> b) -> Ctor * a c #

GenericProfunctor (Ctor *) Source # 

Methods

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

GenericNonEmptyProfunctor (Ctor *) Source # 

Methods

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

GenericRecordProfunctor (Ctor *) Source # 

Methods

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

mult :: Ctor * (f a) (f' a') -> Ctor * (g a) (g' a') -> Ctor * ((f :*: g) a) ((f' :*: g') a') 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 #

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 #

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 #

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 ADTRecord t = (Generic t, ADTRecord' (Rep t), Constraints t AnyType) Source #

ADTRecord is a constraint type synonym. An instance is an ADT with *exactly* one constructor.

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 ADT t = (Generic t, ADT' (Rep t), Constraints t AnyType) Source #

ADT is a constraint type synonym. The Generic instance can be derived, and any generic representation will be an instance of ADT' and AnyType.

data For 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 

ctorIndex :: 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 (For :: For Binary) put t

ctorIndex1 :: ADT1 t => t a -> Int Source #

class AnyType a Source #

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

Instances