heftia-0.1.0.0: Higher-order version of Freer.
Copyright(c) 2023 Yamada Ryo
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Hefty.Union

Description

A type class representing a general open union for higher-order effects, independent of the internal implementation.

Synopsis

Documentation

class UnionH (u :: [Signature] -> Signature) where Source #

A type class representing a general open union for higher-order effects, independent of the internal implementation.

Minimal complete definition

injectH, projectH, absurdUnionH, (compH | inject0H, weakenH, decompH | (|+:))

Associated Types

type HasMembershipH u (h :: Signature) (hs :: [Signature]) :: Constraint Source #

Methods

injectH :: HasMembershipH u h hs => h f ~> u hs f Source #

projectH :: HasMembershipH u h hs => u hs f a -> Maybe (h f a) Source #

absurdUnionH :: u '[] f a -> x Source #

compH :: Either (h f a) (u hs f a) -> u (h ': hs) f a Source #

decompH :: u (h ': hs) f a -> Either (h f a) (u hs f a) Source #

(|+:) :: (h f a -> r) -> (u hs f a -> r) -> u (h ': hs) f a -> r infixr 5 Source #

inject0H :: h f ~> u (h ': hs) f Source #

injectUnderH :: h2 f ~> u (h1 ': (h2 ': hs)) f Source #

injectUnder2H :: h3 f ~> u (h1 ': (h2 ': (h3 ': hs))) f Source #

injectUnder3H :: h4 f ~> u (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weakenH :: u hs f ~> u (h ': hs) f Source #

weaken2H :: u hs f ~> u (h1 ': (h2 ': hs)) f Source #

weaken3H :: u hs f ~> u (h1 ': (h2 ': (h3 ': hs))) f Source #

weaken4H :: u hs f ~> u (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weakenUnderH :: u (h1 ': hs) f ~> u (h1 ': (h2 ': hs)) f Source #

weakenUnder2H :: u (h1 ': (h2 ': hs)) f ~> u (h1 ': (h2 ': (h3 ': hs))) f Source #

weakenUnder3H :: u (h1 ': (h2 ': (h3 ': hs))) f ~> u (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weaken2UnderH :: u (h1 ': hs) f ~> u (h1 ': (h2 ': (h3 ': hs))) f Source #

weaken2Under2H :: u (h1 ': (h2 ': hs)) f ~> u (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weaken3UnderH :: u (h1 ': hs) f ~> u (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

flipUnionH :: u (h1 ': (h2 ': hs)) f ~> u (h2 ': (h1 ': hs)) f Source #

flipUnion3H :: u (h1 ': (h2 ': (h3 ': hs))) f ~> u (h3 ': (h2 ': (h1 ': hs))) f Source #

flipUnionUnderH :: u (h1 ': (h2 ': (h3 ': hs))) f ~> u (h1 ': (h3 ': (h2 ': hs))) f Source #

rot3H :: u (h1 ': (h2 ': (h3 ': hs))) f ~> u (h2 ': (h3 ': (h1 ': hs))) f Source #

rot3H' :: u (h1 ': (h2 ': (h3 ': hs))) f ~> u (h3 ': (h1 ': (h2 ': hs))) f Source #

bundleUnion2H :: UnionH u' => u (h1 ': (h2 ': hs)) f ~> u (u' '[h1, h2] ': hs) f Source #

bundleUnion3H :: UnionH u' => u (h1 ': (h2 ': (h3 ': hs))) f ~> u (u' '[h1, h2, h3] ': hs) f Source #

bundleUnion4H :: UnionH u' => u (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f ~> u (u' '[h1, h2, h3, h4] ': hs) f Source #

unbundleUnion2H :: UnionH u' => u (u' '[h1, h2] ': hs) f ~> u (h1 ': (h2 ': hs)) f Source #

unbundleUnion3H :: UnionH u' => u (u' '[h1, h2, h3] ': hs) f ~> u (h1 ': (h2 ': (h3 ': hs))) f Source #

unbundleUnion4H :: UnionH u' => u (u' '[h1, h2, h3, h4] ': hs) f ~> u (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

Instances

Instances details
UnionH ExtensibleUnionH Source # 
Instance details

Defined in Data.Hefty.Extensible

Associated Types

type HasMembershipH ExtensibleUnionH h hs Source #

Methods

injectH :: forall (h :: Signature) (hs :: [Signature]) (f :: Type -> Type). HasMembershipH ExtensibleUnionH h hs => h f ~> ExtensibleUnionH hs f Source #

projectH :: forall h (hs :: [Signature]) (f :: Type -> Type) a. HasMembershipH ExtensibleUnionH h hs => ExtensibleUnionH hs f a -> Maybe (h f a) Source #

absurdUnionH :: forall (f :: Type -> Type) a x. ExtensibleUnionH '[] f a -> x Source #

compH :: forall h (f :: Type -> Type) a (hs :: [Signature]). Either (h f a) (ExtensibleUnionH hs f a) -> ExtensibleUnionH (h ': hs) f a Source #

decompH :: forall h (hs :: [Signature]) (f :: Type -> Type) a. ExtensibleUnionH (h ': hs) f a -> Either (h f a) (ExtensibleUnionH hs f a) Source #

(|+:) :: forall h (f :: Type -> Type) a r (hs :: [Signature]). (h f a -> r) -> (ExtensibleUnionH hs f a -> r) -> ExtensibleUnionH (h ': hs) f a -> r Source #

inject0H :: forall (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h f ~> ExtensibleUnionH (h ': hs) f Source #

injectUnderH :: forall (h2 :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (h1 :: (Type -> Type) -> Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h2 f ~> ExtensibleUnionH (h1 ': (h2 ': hs)) f Source #

injectUnder2H :: forall (h3 :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (h1 :: (Type -> Type) -> Type -> Type) (h2 :: (Type -> Type) -> Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h3 f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

injectUnder3H :: forall (h4 :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (h1 :: (Type -> Type) -> Type -> Type) (h2 :: (Type -> Type) -> Type -> Type) (h3 :: (Type -> Type) -> Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h4 f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weakenH :: forall (hs :: [Signature]) (f :: Type -> Type) (h :: Signature). ExtensibleUnionH hs f ~> ExtensibleUnionH (h ': hs) f Source #

weaken2H :: forall (hs :: [Signature]) (f :: Type -> Type) (h1 :: Signature) (h2 :: Signature). ExtensibleUnionH hs f ~> ExtensibleUnionH (h1 ': (h2 ': hs)) f Source #

weaken3H :: forall (hs :: [Signature]) (f :: Type -> Type) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature). ExtensibleUnionH hs f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

weaken4H :: forall (hs :: [Signature]) (f :: Type -> Type) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature). ExtensibleUnionH hs f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weakenUnderH :: forall (h1 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h2 :: Signature). ExtensibleUnionH (h1 ': hs) f ~> ExtensibleUnionH (h1 ': (h2 ': hs)) f Source #

weakenUnder2H :: forall (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h3 :: Signature). ExtensibleUnionH (h1 ': (h2 ': hs)) f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

weakenUnder3H :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h4 :: Signature). ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weaken2UnderH :: forall (h1 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h2 :: Signature) (h3 :: Signature). ExtensibleUnionH (h1 ': hs) f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

weaken2Under2H :: forall (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h3 :: Signature) (h4 :: Signature). ExtensibleUnionH (h1 ': (h2 ': hs)) f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weaken3UnderH :: forall (h1 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature). ExtensibleUnionH (h1 ': hs) f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

flipUnionH :: forall (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type). ExtensibleUnionH (h1 ': (h2 ': hs)) f ~> ExtensibleUnionH (h2 ': (h1 ': hs)) f Source #

flipUnion3H :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> ExtensibleUnionH (h3 ': (h2 ': (h1 ': hs))) f Source #

flipUnionUnderH :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> ExtensibleUnionH (h1 ': (h3 ': (h2 ': hs))) f Source #

rot3H :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> ExtensibleUnionH (h2 ': (h3 ': (h1 ': hs))) f Source #

rot3H' :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> ExtensibleUnionH (h3 ': (h1 ': (h2 ': hs))) f Source #

bundleUnion2H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => ExtensibleUnionH (h1 ': (h2 ': hs)) f ~> ExtensibleUnionH (u' '[h1, h2] ': hs) f Source #

bundleUnion3H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> ExtensibleUnionH (u' '[h1, h2, h3] ': hs) f Source #

bundleUnion4H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => ExtensibleUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f ~> ExtensibleUnionH (u' '[h1, h2, h3, h4] ': hs) f Source #

unbundleUnion2H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => ExtensibleUnionH (u' '[h1, h2] ': hs) f ~> ExtensibleUnionH (h1 ': (h2 ': hs)) f Source #

unbundleUnion3H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => ExtensibleUnionH (u' '[h1, h2, h3] ': hs) f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

unbundleUnion4H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => ExtensibleUnionH (u' '[h1, h2, h3, h4] ': hs) f ~> ExtensibleUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

UnionH SumUnionH Source # 
Instance details

Defined in Data.Hefty.Sum

Associated Types

type HasMembershipH SumUnionH h hs Source #

Methods

injectH :: forall (h :: Signature) (hs :: [Signature]) (f :: Type -> Type). HasMembershipH SumUnionH h hs => h f ~> SumUnionH hs f Source #

projectH :: forall h (hs :: [Signature]) (f :: Type -> Type) a. HasMembershipH SumUnionH h hs => SumUnionH hs f a -> Maybe (h f a) Source #

absurdUnionH :: forall (f :: Type -> Type) a x. SumUnionH '[] f a -> x Source #

compH :: forall h (f :: Type -> Type) a (hs :: [Signature]). Either (h f a) (SumUnionH hs f a) -> SumUnionH (h ': hs) f a Source #

decompH :: forall h (hs :: [Signature]) (f :: Type -> Type) a. SumUnionH (h ': hs) f a -> Either (h f a) (SumUnionH hs f a) Source #

(|+:) :: forall h (f :: Type -> Type) a r (hs :: [Signature]). (h f a -> r) -> (SumUnionH hs f a -> r) -> SumUnionH (h ': hs) f a -> r Source #

inject0H :: forall (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h f ~> SumUnionH (h ': hs) f Source #

injectUnderH :: forall (h2 :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (h1 :: (Type -> Type) -> Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h2 f ~> SumUnionH (h1 ': (h2 ': hs)) f Source #

injectUnder2H :: forall (h3 :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (h1 :: (Type -> Type) -> Type -> Type) (h2 :: (Type -> Type) -> Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h3 f ~> SumUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

injectUnder3H :: forall (h4 :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) (h1 :: (Type -> Type) -> Type -> Type) (h2 :: (Type -> Type) -> Type -> Type) (h3 :: (Type -> Type) -> Type -> Type) (hs :: [(Type -> Type) -> Type -> Type]). h4 f ~> SumUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weakenH :: forall (hs :: [Signature]) (f :: Type -> Type) (h :: Signature). SumUnionH hs f ~> SumUnionH (h ': hs) f Source #

weaken2H :: forall (hs :: [Signature]) (f :: Type -> Type) (h1 :: Signature) (h2 :: Signature). SumUnionH hs f ~> SumUnionH (h1 ': (h2 ': hs)) f Source #

weaken3H :: forall (hs :: [Signature]) (f :: Type -> Type) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature). SumUnionH hs f ~> SumUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

weaken4H :: forall (hs :: [Signature]) (f :: Type -> Type) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature). SumUnionH hs f ~> SumUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weakenUnderH :: forall (h1 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h2 :: Signature). SumUnionH (h1 ': hs) f ~> SumUnionH (h1 ': (h2 ': hs)) f Source #

weakenUnder2H :: forall (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h3 :: Signature). SumUnionH (h1 ': (h2 ': hs)) f ~> SumUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

weakenUnder3H :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h4 :: Signature). SumUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> SumUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weaken2UnderH :: forall (h1 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h2 :: Signature) (h3 :: Signature). SumUnionH (h1 ': hs) f ~> SumUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

weaken2Under2H :: forall (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h3 :: Signature) (h4 :: Signature). SumUnionH (h1 ': (h2 ': hs)) f ~> SumUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

weaken3UnderH :: forall (h1 :: Signature) (hs :: [Signature]) (f :: Type -> Type) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature). SumUnionH (h1 ': hs) f ~> SumUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

flipUnionH :: forall (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type). SumUnionH (h1 ': (h2 ': hs)) f ~> SumUnionH (h2 ': (h1 ': hs)) f Source #

flipUnion3H :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). SumUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> SumUnionH (h3 ': (h2 ': (h1 ': hs))) f Source #

flipUnionUnderH :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). SumUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> SumUnionH (h1 ': (h3 ': (h2 ': hs))) f Source #

rot3H :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). SumUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> SumUnionH (h2 ': (h3 ': (h1 ': hs))) f Source #

rot3H' :: forall (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). SumUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> SumUnionH (h3 ': (h1 ': (h2 ': hs))) f Source #

bundleUnion2H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => SumUnionH (h1 ': (h2 ': hs)) f ~> SumUnionH (u' '[h1, h2] ': hs) f Source #

bundleUnion3H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => SumUnionH (h1 ': (h2 ': (h3 ': hs))) f ~> SumUnionH (u' '[h1, h2, h3] ': hs) f Source #

bundleUnion4H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => SumUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f ~> SumUnionH (u' '[h1, h2, h3, h4] ': hs) f Source #

unbundleUnion2H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => SumUnionH (u' '[h1, h2] ': hs) f ~> SumUnionH (h1 ': (h2 ': hs)) f Source #

unbundleUnion3H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => SumUnionH (u' '[h1, h2, h3] ': hs) f ~> SumUnionH (h1 ': (h2 ': (h3 ': hs))) f Source #

unbundleUnion4H :: forall (u' :: [Signature] -> Signature) (h1 :: Signature) (h2 :: Signature) (h3 :: Signature) (h4 :: Signature) (hs :: [Signature]) (f :: Type -> Type). UnionH u' => SumUnionH (u' '[h1, h2, h3, h4] ': hs) f ~> SumUnionH (h1 ': (h2 ': (h3 ': (h4 ': hs)))) f Source #

type family IsMemberH (h :: Signature) hs where ... Source #

Equations

IsMemberH h (h ': hs) = 'True 
IsMemberH h (_ ': hs) = IsMemberH h hs 
IsMemberH _ '[] = 'False 

type MemberH u h hs = (HasMembershipH u h hs, IsMemberH h hs ~ 'True) Source #