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.Free.Extensible

Description

An implementation of an open union for first-order effects using the extensible package as a backend.

Synopsis

Documentation

newtype ExtensibleUnion fs a Source #

An implementation of an open union for first-order effects using the extensible package as a backend.

Constructors

ExtensibleUnion 

Fields

Instances

Instances details
Union ExtensibleUnion Source # 
Instance details

Defined in Data.Free.Extensible

Associated Types

type HasMembership ExtensibleUnion f fs Source #

Methods

inject :: forall (f :: Instruction) (fs :: [Instruction]). HasMembership ExtensibleUnion f fs => f ~> ExtensibleUnion fs Source #

project :: forall f (fs :: [Instruction]) a. HasMembership ExtensibleUnion f fs => ExtensibleUnion fs a -> Maybe (f a) Source #

absurdUnion :: ExtensibleUnion '[] a -> x Source #

comp :: forall f a (fs :: [Instruction]). Either (f a) (ExtensibleUnion fs a) -> ExtensibleUnion (f ': fs) a Source #

decomp :: forall f (fs :: [Instruction]) a. ExtensibleUnion (f ': fs) a -> Either (f a) (ExtensibleUnion fs a) Source #

(|+|:) :: forall f a r (fs :: [Instruction]). (f a -> r) -> (ExtensibleUnion fs a -> r) -> ExtensibleUnion (f ': fs) a -> r Source #

inject0 :: forall (f :: Type -> Type) (fs :: [Type -> Type]). f ~> ExtensibleUnion (f ': fs) Source #

injectUnder :: forall (f2 :: Type -> Type) (f1 :: Type -> Type) (fs :: [Type -> Type]). f2 ~> ExtensibleUnion (f1 ': (f2 ': fs)) Source #

injectUnder2 :: forall (f3 :: Type -> Type) (f1 :: Type -> Type) (f2 :: Type -> Type) (fs :: [Type -> Type]). f3 ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) Source #

injectUnder3 :: forall (f4 :: Type -> Type) (f1 :: Type -> Type) (f2 :: Type -> Type) (f3 :: Type -> Type) (fs :: [Type -> Type]). f4 ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': (f4 ': fs)))) Source #

weaken :: forall (fs :: [Instruction]) a (f :: Instruction). ExtensibleUnion fs a -> ExtensibleUnion (f ': fs) a Source #

weaken2 :: forall (fs :: [Instruction]) a (f1 :: Instruction) (f2 :: Instruction). ExtensibleUnion fs a -> ExtensibleUnion (f1 ': (f2 ': fs)) a Source #

weaken3 :: forall (fs :: [Instruction]) a (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction). ExtensibleUnion fs a -> ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) a Source #

weaken4 :: forall (fs :: [Instruction]) a (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (f4 :: Instruction). ExtensibleUnion fs a -> ExtensibleUnion (f1 ': (f2 ': (f3 ': (f4 ': fs)))) a Source #

weakenUnder :: forall (f1 :: Instruction) (fs :: [Instruction]) (f2 :: Instruction). ExtensibleUnion (f1 ': fs) ~> ExtensibleUnion (f1 ': (f2 ': fs)) Source #

weakenUnder2 :: forall (f1 :: Instruction) (f2 :: Instruction) (fs :: [Instruction]) (f3 :: Instruction). ExtensibleUnion (f1 ': (f2 ': fs)) ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) Source #

weakenUnder3 :: forall (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (fs :: [Instruction]) (f4 :: Instruction). ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': (f4 ': fs)))) Source #

weaken2Under :: forall (f1 :: Instruction) (fs :: [Instruction]) (f2 :: Instruction) (f3 :: Instruction). ExtensibleUnion (f1 ': fs) ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) Source #

weaken2Under2 :: forall (f1 :: Instruction) (f2 :: Instruction) (fs :: [Instruction]) (f3 :: Instruction) (f4 :: Instruction). ExtensibleUnion (f1 ': (f2 ': fs)) ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': (f4 ': fs)))) Source #

weaken3Under :: forall (f1 :: Instruction) (fs :: [Instruction]) (f2 :: Instruction) (f3 :: Instruction) (f4 :: Instruction). ExtensibleUnion (f1 ': fs) ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': (f4 ': fs)))) Source #

flipUnion :: forall (f1 :: Instruction) (f2 :: Instruction) (fs :: [Instruction]). ExtensibleUnion (f1 ': (f2 ': fs)) ~> ExtensibleUnion (f2 ': (f1 ': fs)) Source #

flipUnion3 :: forall (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (fs :: [Instruction]). ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) ~> ExtensibleUnion (f3 ': (f2 ': (f1 ': fs))) Source #

flipUnionUnder :: forall (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (fs :: [Instruction]). ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) ~> ExtensibleUnion (f1 ': (f3 ': (f2 ': fs))) Source #

rot3 :: forall (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (fs :: [Instruction]). ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) ~> ExtensibleUnion (f2 ': (f3 ': (f1 ': fs))) Source #

rot3' :: forall (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (fs :: [Instruction]). ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) ~> ExtensibleUnion (f3 ': (f1 ': (f2 ': fs))) Source #

bundleUnion2 :: forall (u' :: [Instruction] -> Instruction) (f1 :: Instruction) (f2 :: Instruction) (fs :: [Instruction]). Union u' => ExtensibleUnion (f1 ': (f2 ': fs)) ~> ExtensibleUnion (u' '[f1, f2] ': fs) Source #

bundleUnion3 :: forall (u' :: [Instruction] -> Instruction) (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (fs :: [Instruction]). Union u' => ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) ~> ExtensibleUnion (u' '[f1, f2, f3] ': fs) Source #

bundleUnion4 :: forall (u' :: [Instruction] -> Instruction) (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (f4 :: Instruction) (fs :: [Instruction]). Union u' => ExtensibleUnion (f1 ': (f2 ': (f3 ': (f4 ': fs)))) ~> ExtensibleUnion (u' '[f1, f2, f3, f4] ': fs) Source #

unbundleUnion2 :: forall (u' :: [Instruction] -> Instruction) (f1 :: Instruction) (f2 :: Instruction) (fs :: [Instruction]). Union u' => ExtensibleUnion (u' '[f1, f2] ': fs) ~> ExtensibleUnion (f1 ': (f2 ': fs)) Source #

unbundleUnion3 :: forall (u' :: [Instruction] -> Instruction) (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (fs :: [Instruction]). Union u' => ExtensibleUnion (u' '[f1, f2, f3] ': fs) ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': fs))) Source #

unbundleUnion4 :: forall (u' :: [Instruction] -> Instruction) (f1 :: Instruction) (f2 :: Instruction) (f3 :: Instruction) (f4 :: Instruction) (fs :: [Instruction]). Union u' => ExtensibleUnion (u' '[f1, f2, f3, f4] ': fs) ~> ExtensibleUnion (f1 ': (f2 ': (f3 ': (f4 ': fs)))) Source #

Forall Functor fs => Functor (ExtensibleUnion fs) Source # 
Instance details

Defined in Data.Free.Extensible

Methods

fmap :: (a -> b) -> ExtensibleUnion fs a -> ExtensibleUnion fs b #

(<$) :: a -> ExtensibleUnion fs b -> ExtensibleUnion fs a #

type HasMembership ExtensibleUnion f fs Source # 
Instance details

Defined in Data.Free.Extensible

newtype FieldApp a (f :: Instruction) Source #

Constructors

FieldApp 

Fields

findFirstMembership :: forall xs x. KnownNat (TypeIndex xs x) => Membership xs x Source #

type family TypeIndex (xs :: [k]) (x :: k) :: Nat where ... Source #

Equations

TypeIndex (x ': xs) x = 0 
TypeIndex (y ': xs) x = 1 + TypeIndex xs x