Safe Haskell | None |
---|---|
Language | Haskell98 |
Documentation
absurdZero :: Const Void a -> b Source #
class ConvSum (rep1 :: k -> Type) where Source #
convToSum :: Proxy end -> rep1 ~> ToSum rep1 end Source #
convToSumSkip :: end ~> ToSum rep1 end Source #
convFromSum :: ToSum rep1 end a -> (rep1 a -> res) -> (end a -> res) -> res Source #
Instances
ConvSum (V1 :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal | |
ConvSum rep1 => ConvSum (D1 meta rep1 :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal convToSum :: forall (end :: k0 -> Type). Proxy end -> D1 meta rep1 ~> ToSum (D1 meta rep1) end Source # convToSumSkip :: forall (end :: k0 -> Type). end ~> ToSum (D1 meta rep1) end Source # convFromSum :: forall end (a :: k0) res. ToSum (D1 meta rep1) end a -> (D1 meta rep1 a -> res) -> (end a -> res) -> res Source # | |
(ConvSum rep1, ConvSum rep1') => ConvSum (rep1 :+: rep1' :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal convToSum :: forall (end :: k0 -> Type). Proxy end -> (rep1 :+: rep1') ~> ToSum (rep1 :+: rep1') end Source # convToSumSkip :: forall (end :: k0 -> Type). end ~> ToSum (rep1 :+: rep1') end Source # convFromSum :: forall end (a :: k0) res. ToSum (rep1 :+: rep1') end a -> ((rep1 :+: rep1') a -> res) -> (end a -> res) -> res Source # | |
ConvProduct rep1 => ConvSum (C1 meta rep1 :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal convToSum :: forall (end :: k0 -> Type). Proxy end -> C1 meta rep1 ~> ToSum (C1 meta rep1) end Source # convToSumSkip :: forall (end :: k0 -> Type). end ~> ToSum (C1 meta rep1) end Source # convFromSum :: forall end (a :: k0) res. ToSum (C1 meta rep1) end a -> (C1 meta rep1 a -> res) -> (end a -> res) -> res Source # |
class ConvProduct (rep1 :: k -> Type) where Source #
convToProduct :: rep1 a -> end a -> ToProduct rep1 end a Source #
convFromProduct :: ToProduct rep1 end a -> (rep1 a -> end a -> res) -> res Source #
Instances
ConvProduct (U1 :: k -> Type) Source # | |
(ConvProduct rep1, ConvProduct rep1') => ConvProduct (rep1 :*: rep1' :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal | |
ConvField rep1 => ConvProduct (S1 meta rep1 :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal |
class ConvField (rep1 :: k -> Type) where Source #
Nothing
convToField :: rep1 ~> ToField rep1 Source #
convFromField :: ToField rep1 ~> rep1 Source #
type ConvBæSum rep1 = ConvBæSum_ (CheckSum rep1) rep1 Source #
class CheckSum rep1 ~ tag => ConvBæSum_ tag (rep1 :: k -> Type) where Source #
Instances
CheckSum rep1 ~ 'NotSum => ConvBæSum_ 'NotSum (rep1 :: k -> Type) Source # | |
(CheckSum (Sum rep1 rep1') ~ 'NormalSum, ConvBæProduct rep1, ConvBæSum rep1') => ConvBæSum_ 'NormalSum (Sum rep1 rep1' :: k -> Type) Source # | |
(ConvBæProduct rep1, CheckSum (Sum rep1 (Const Void :: k -> Type)) ~ 'RightZero, void ~ Void) => ConvBæSum_ 'RightZero (Sum rep1 (Const void :: k -> Type) :: k -> Type) Source # | |
type family CheckProduct rep1 where ... Source #
CheckProduct (Product rep1 (Const ())) = 'RightOne | |
CheckProduct (Product rep1 rep') = 'NormalProduct | |
CheckProduct rep = 'NotProduct |
type BæProduct rep1 = BæProduct_ (CheckProduct rep1) rep1 Source #
type ConvBæProduct rep1 = ConvBæProduct_ (CheckProduct rep1) rep1 Source #
class tag ~ CheckProduct rep1 => ConvBæProduct_ tag (rep1 :: k -> Type) where Source #
type BæProduct_ tag (rep1 :: k -> Type) :: k -> Type Source #
convBæProduct :: rep1 ~> BæProduct rep1 Source #
convHæProduct :: BæProduct rep1 ~> rep1 Source #
Instances
CheckProduct rep1 ~ 'NotProduct => ConvBæProduct_ 'NotProduct (rep1 :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal type BæProduct_ 'NotProduct rep1 :: k -> Type Source # convBæProduct :: rep1 ~> BæProduct rep1 Source # convHæProduct :: BæProduct rep1 ~> rep1 Source # | |
unit ~ () => ConvBæProduct_ 'RightOne (Product rep1 (Const unit :: k -> Type) :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal | |
(CheckProduct (Product rep1 rep1') ~ 'NormalProduct, ConvBæProduct rep1') => ConvBæProduct_ 'NormalProduct (Product rep1 rep1' :: k -> Type) Source # | |
Defined in Generic.Applicative.Internal type BæProduct_ 'NormalProduct (Product rep1 rep1') :: k -> Type Source # |
type family ReplaceSums sums rep1 where ... Source #
ReplaceSums (sum ': sums) (Sum rep1 rep1') = rep1 `sum` ReplaceSums sums rep1' | |
ReplaceSums '[] rep1 = rep1 |
replaceSums :: forall sums rep1. rep1 ~> ReplaceSums sums rep1 Source #
placeSums :: forall sums rep1. ReplaceSums sums rep1 ~> rep1 Source #
newtype Generically1 f a Source #
Generically1 (f a) |