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.Internal.Unary

Description

 
Synopsis

Documentation

type J f a = f a a Source #

Type-level join, of kind (k -> k -> k') -> k -> k'.

class (c a, a ~ b) => D (c :: k -> Constraint) a b Source #

Constraint-level duplicate, of kind (k -> Constraint) -> k -> k -> Constraint.

Instances

Instances details
(c a, a ~ b) => D (c :: k -> Constraint) (a :: k) (b :: k) Source # 
Instance details

Defined in Generics.OneLiner.Internal.Unary

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

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

type Constraints01 t c0 c1 = Constraints01 t t (D c0) (D c1) Source #

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

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

type ADT1 t = (ADT1 t t, Constraints1 t AnyType) Source #

record :: forall c p t. (ADTRecord t, Constraints t c, GenericRecordProfunctor 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 #

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 #

nonEmpty :: forall c p t. (ADTNonEmpty t, Constraints t c, GenericNonEmptyProfunctor p) => (forall s. c s => p s s) -> p t t 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 #

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 #

generic :: forall c p t. (ADT t, Constraints t c, GenericProfunctor p) => (forall s. c s => p s s) -> p t t 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 #

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 #

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

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

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