one-liner-0.6: 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

p

Associated Types

type CtorCount' t :: Nat Source #

Methods

ctorIndex' :: t x -> Int Source #

ctorCount :: proxy t -> Int Source #

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

Instances

ADT' V1 Source # 

Associated Types

type CtorCount' (V1 :: * -> *) :: Nat Source #

Methods

ctorIndex' :: V1 x -> Int Source #

ctorCount :: proxy V1 -> Int Source #

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

ADT' U1 Source # 

Associated Types

type CtorCount' (U1 :: * -> *) :: Nat Source #

Methods

ctorIndex' :: U1 x -> Int Source #

ctorCount :: proxy U1 -> Int Source #

p :: (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 # 

Associated Types

type CtorCount' (K1 i v :: * -> *) :: Nat Source #

Methods

ctorIndex' :: K1 i v x -> Int Source #

ctorCount :: proxy (K1 i v) -> Int Source #

p :: (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 # 

Associated Types

type CtorCount' ((:+:) f g :: * -> *) :: Nat Source #

Methods

ctorIndex' :: (f :+: g) x -> Int Source #

ctorCount :: proxy (f :+: g) -> Int Source #

p :: (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 # 

Associated Types

type CtorCount' ((:*:) f g :: * -> *) :: Nat Source #

Methods

ctorIndex' :: (f :*: g) x -> Int Source #

ctorCount :: proxy (f :*: g) -> Int Source #

p :: (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 # 

Associated Types

type CtorCount' (M1 i t f :: * -> *) :: Nat Source #

Methods

ctorIndex' :: M1 i t f x -> Int Source #

ctorCount :: proxy (M1 i t f) -> Int Source #

p :: (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 Profunctor p => GenericProfunctor p where Source #

Minimal complete definition

zero, unit, plus, mult

Methods

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

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

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

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

Instances

Applicative f => GenericProfunctor (Star f) Source # 

Methods

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

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

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

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

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

All the above functions have been implemented using this single function, using different profunctors.

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

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

type CtorCount t = CtorCount' (Rep t) Source #

CtorCount is the number of constructors of a type at the type level. F.e. if you want to require that a type has at least two constructors, you can add the constraint (2 <= CtorCount t).

type ADTRecord t = (ADT t, 1 ~ CtorCount t) Source #

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

type ADTNonEmpty t = (ADT t, 1 <= CtorCount t) Source #

ADTNonEmpty is a constraint type synonym. An instance is an ADT with *at least* one constructor.

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