License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type J f a = f a a
- class (c a, a ~ b) => D (c :: k -> Constraint) a b
- type Constraints t c = Constraints t t (D c)
- type Constraints1 t c = Constraints1 t t (D c)
- type Constraints01 t c0 c1 = Constraints01 t t (D c0) (D c1)
- type Constraints' t c c1 = Constraints' t t (D c) (D c1)
- type ADTRecord t = (ADTRecord t t, Constraints t AnyType)
- type ADTRecord1 t = (ADTRecord1 t t, Constraints1 t AnyType)
- type ADTNonEmpty t = (ADTNonEmpty t t, Constraints t AnyType)
- type ADTNonEmpty1 t = (ADTNonEmpty1 t t, Constraints1 t AnyType)
- type ADT t = (ADT t t, Constraints t AnyType)
- type ADT1 t = (ADT1 t t, Constraints1 t AnyType)
- record :: forall c p t. (ADTRecord t, Constraints t c, GenericRecordProfunctor p) => (forall s. c s => p s s) -> p t t
- 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)
- 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)
- nonEmpty :: forall c p t. (ADTNonEmpty t, Constraints t c, GenericNonEmptyProfunctor p) => (forall s. c s => p s s) -> p t t
- 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)
- 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)
- generic :: forall c p t. (ADT t, Constraints t c, GenericProfunctor p) => (forall s. c s => p s s) -> p t t
- 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)
- 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)
- ctorIndex :: forall t. ADT t => t -> Int
- ctorIndex1 :: forall t a. ADT1 t => t a -> Int
- class AnyType (a :: k)
Documentation
class (c a, a ~ b) => D (c :: k -> Constraint) a b Source #
Constraint-level duplicate
, of kind (k -> Constraint) -> k -> k -> Constraint
.
Instances
(c a, a ~ b) => D (c :: k -> Constraint) (a :: k) (b :: k) Source # | |
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 ADTRecord1 t = (ADTRecord1 t t, Constraints1 t AnyType) Source #
type ADTNonEmpty t = (ADTNonEmpty t t, Constraints t AnyType) Source #
type ADTNonEmpty1 t = (ADTNonEmpty1 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 #
ctorIndex1 :: forall t a. ADT1 t => t a -> Int Source #