idiomatic-0.1.0.0: Deriving Applicative for sum types.. Idiomatically.
Safe HaskellNone
LanguageHaskell98

Generic.Applicative.Internal

Documentation

type SumKind k = (k -> Type) -> (k -> Type) -> k -> Type Source #

type (~>) f g = forall x. f x -> g x Source #

absurdV1 :: V1 a -> b Source #

class ConvSum (rep1 :: k -> Type) where Source #

Associated Types

type ToSum (rep1 :: k -> Type) (end :: k -> Type) :: k -> Type Source #

Methods

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

Instances details
ConvSum (V1 :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToSum V1 end :: k -> Type Source #

Methods

convToSum :: forall (end :: k0 -> Type). Proxy end -> V1 ~> ToSum V1 end Source #

convToSumSkip :: forall (end :: k0 -> Type). end ~> ToSum V1 end Source #

convFromSum :: forall end (a :: k0) res. ToSum V1 end a -> (V1 a -> res) -> (end a -> res) -> res Source #

ConvSum rep1 => ConvSum (D1 meta rep1 :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToSum (D1 meta rep1) end :: k -> Type Source #

Methods

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 # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToSum (rep1 :+: rep1') end :: k -> Type Source #

Methods

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 # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToSum (C1 meta rep1) end :: k -> Type Source #

Methods

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 #

Associated Types

type ToProduct (rep1 :: k -> Type) (end :: k -> Type) :: k -> Type Source #

Methods

convToProduct :: rep1 a -> end a -> ToProduct rep1 end a Source #

convFromProduct :: ToProduct rep1 end a -> (rep1 a -> end a -> res) -> res Source #

Instances

Instances details
ConvProduct (U1 :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToProduct U1 end :: k -> Type Source #

Methods

convToProduct :: forall (a :: k0) end. U1 a -> end a -> ToProduct U1 end a Source #

convFromProduct :: forall end (a :: k0) res. ToProduct U1 end a -> (U1 a -> end a -> res) -> res Source #

(ConvProduct rep1, ConvProduct rep1') => ConvProduct (rep1 :*: rep1' :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToProduct (rep1 :*: rep1') end :: k -> Type Source #

Methods

convToProduct :: forall (a :: k0) end. (rep1 :*: rep1') a -> end a -> ToProduct (rep1 :*: rep1') end a Source #

convFromProduct :: forall end (a :: k0) res. ToProduct (rep1 :*: rep1') end a -> ((rep1 :*: rep1') a -> end a -> res) -> res Source #

ConvField rep1 => ConvProduct (S1 meta rep1 :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToProduct (S1 meta rep1) end :: k -> Type Source #

Methods

convToProduct :: forall (a :: k0) end. S1 meta rep1 a -> end a -> ToProduct (S1 meta rep1) end a Source #

convFromProduct :: forall end (a :: k0) res. ToProduct (S1 meta rep1) end a -> (S1 meta rep1 a -> end a -> res) -> res Source #

class ConvField (rep1 :: k -> Type) where Source #

Minimal complete definition

Nothing

Associated Types

type ToField (rep1 :: k -> Type) :: k -> Type Source #

Methods

convToField :: rep1 ~> ToField rep1 Source #

convToField :: Coercible (rep1 a) (ToField rep1 a) => rep1 a -> ToField rep1 a Source #

convFromField :: ToField rep1 ~> rep1 Source #

convFromField :: Coercible (ToField rep1 a) (rep1 a) => ToField rep1 a -> rep1 a Source #

Instances

Instances details
ConvField (Rec1 f :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToField (Rec1 f) :: k -> Type Source #

ConvField (K1 tag a :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToField (K1 tag a) :: k -> Type Source #

Methods

convToField :: K1 tag a ~> ToField (K1 tag a) Source #

convFromField :: ToField (K1 tag a) ~> K1 tag a Source #

(Functor rep1, ConvField rep1') => ConvField (rep1 :.: rep1' :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToField (rep1 :.: rep1') :: k -> Type Source #

Methods

convToField :: (rep1 :.: rep1') ~> ToField (rep1 :.: rep1') Source #

convFromField :: ToField (rep1 :.: rep1') ~> (rep1 :.: rep1') Source #

ConvField Par1 Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type ToField Par1 :: k -> Type Source #

data SumTag Source #

Constructors

RightZero 
NormalSum 
NotSum 

type family CheckSum rep1 where ... Source #

Equations

CheckSum (Sum rep1 (Const Void)) = 'RightZero 
CheckSum (Sum rep1 rep') = 'NormalSum 
CheckSum rep = 'NotSum 

type BæSum rep1 = BæSum_ (CheckSum 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 #

Associated Types

type BæSum_ tag (rep1 :: k -> Type) :: k -> Type Source #

Methods

convBæSum :: rep1 ~> BæSum rep1 Source #

convHæSum :: BæSum rep1 ~> rep1 Source #

Instances

Instances details
CheckSum rep1 ~ 'NotSum => ConvBæSum_ 'NotSum (rep1 :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type BæSum_ 'NotSum rep1 :: k -> Type Source #

Methods

convBæSum :: rep1 ~> BæSum rep1 Source #

convHæSum :: BæSum rep1 ~> rep1 Source #

(CheckSum (Sum rep1 rep1') ~ 'NormalSum, ConvBæProduct rep1, ConvBæSum rep1') => ConvBæSum_ 'NormalSum (Sum rep1 rep1' :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type BæSum_ 'NormalSum (Sum rep1 rep1') :: k -> Type Source #

Methods

convBæSum :: Sum rep1 rep1' ~> BæSum (Sum rep1 rep1') Source #

convHæSum :: BæSum (Sum rep1 rep1') ~> Sum rep1 rep1' 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 # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type BæSum_ 'RightZero (Sum rep1 (Const void)) :: k -> Type Source #

Methods

convBæSum :: Sum rep1 (Const void) ~> BæSum (Sum rep1 (Const void)) Source #

convHæSum :: BæSum (Sum rep1 (Const void)) ~> Sum rep1 (Const void) Source #

type family CheckProduct rep1 where ... Source #

Equations

CheckProduct (Product rep1 (Const ())) = 'RightOne 
CheckProduct (Product rep1 rep') = 'NormalProduct 
CheckProduct rep = 'NotProduct 

type BæProduct rep1 = BæProduct_ (CheckProduct rep1) rep1 Source #

class tag ~ CheckProduct rep1 => ConvBæProduct_ tag (rep1 :: k -> Type) where Source #

Associated Types

type BæProduct_ tag (rep1 :: k -> Type) :: k -> Type Source #

Instances

Instances details
CheckProduct rep1 ~ 'NotProduct => ConvBæProduct_ 'NotProduct (rep1 :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type BæProduct_ 'NotProduct rep1 :: k -> Type Source #

unit ~ () => ConvBæProduct_ 'RightOne (Product rep1 (Const unit :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type BæProduct_ 'RightOne (Product rep1 (Const unit)) :: k -> Type Source #

Methods

convBæProduct :: Product rep1 (Const unit) ~> BæProduct (Product rep1 (Const unit)) Source #

convHæProduct :: BæProduct (Product rep1 (Const unit)) ~> Product rep1 (Const unit) Source #

(CheckProduct (Product rep1 rep1') ~ 'NormalProduct, ConvBæProduct rep1') => ConvBæProduct_ 'NormalProduct (Product rep1 rep1' :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type BæProduct_ 'NormalProduct (Product rep1 rep1') :: k -> Type Source #

Methods

convBæProduct :: Product rep1 rep1' ~> BæProduct (Product rep1 rep1') Source #

convHæProduct :: BæProduct (Product rep1 rep1') ~> Product rep1 rep1' Source #

type Flatten rep1 = ToSum rep1 (Const Void) Source #

flatten :: ConvSum rep1 => rep1 ~> Flatten rep1 Source #

nest :: ConvSum rep1 => Flatten rep1 a -> rep1 a Source #

type family ReplaceSums sums rep1 where ... Source #

Equations

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 NewSums sums f a Source #

Constructors

NewSums 

Fields

Instances

Instances details
(Generic1 f, ConvBæSum_ (CheckSum (ToSum (Rep1 f) (Const Void :: k -> Type))) (ToSum (Rep1 f) (Const Void :: k -> Type)), ConvSum (Rep1 f)) => Generic1 (NewSums sums f :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type Rep1 (NewSums sums f) :: k -> Type #

Methods

from1 :: forall (a :: k0). NewSums sums f a -> Rep1 (NewSums sums f) a #

to1 :: forall (a :: k0). Rep1 (NewSums sums f) a -> NewSums sums f a #

type Rep1 (NewSums sums f :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

type Rep1 (NewSums sums f :: k -> Type) = ReplaceSums sums (BæSum_ (CheckSum (ToSum (Rep1 f) (Const Void :: k -> Type))) (ToSum (Rep1 f) (Const Void :: k -> Type)))

newtype Generically1 f a Source #

Constructors

Generically1 (f a) 

Instances

Instances details
Generic1 f => Generic1 (Generically1 f :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

Associated Types

type Rep1 (Generically1 f) :: k -> Type #

Methods

from1 :: forall (a :: k0). Generically1 f a -> Rep1 (Generically1 f) a #

to1 :: forall (a :: k0). Rep1 (Generically1 f) a -> Generically1 f a #

(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # 
Instance details

Defined in Generic.Applicative.Internal

Methods

fmap :: (a -> b) -> Generically1 f a -> Generically1 f b #

(<$) :: a -> Generically1 f b -> Generically1 f a #

(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # 
Instance details

Defined in Generic.Applicative.Internal

Methods

pure :: a -> Generically1 f a #

(<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b #

liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c #

(*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b #

(<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a #

type Rep1 (Generically1 f :: k -> Type) Source # 
Instance details

Defined in Generic.Applicative.Internal

type Rep1 (Generically1 f :: k -> Type) = Rep1 f