heftia-0.5.0.0: higher-order algebraic effects done right
Copyright(c) 2024 Sayo Koyoneda
LicenseMPL-2.0 (see the LICENSE file)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Control.Monad.Hefty.Transform

Description

This module provides functions for transforming effects. Please refer to the documentation of the top-level module.

Synopsis

Rewriting effectful operations

transform :: forall (e :: Type -> Type) (e' :: Type -> Type) (ef :: [Type -> Type]) (eh :: [EffectH]). (e ~> e') -> Eff eh (e ': ef) ~> Eff eh (e' ': ef) Source #

Transforms the first-order effect e at the head of the list into another first-order effect e'.

transformH :: forall (e :: (Type -> Type) -> Type -> Type) (e' :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]). HFunctor e => (e (Eff (e' ': eh) ef) ~> e' (Eff (e' ': eh) ef)) -> Eff (e ': eh) ef ~> Eff (e' ': eh) ef Source #

Transforms the higher-order effect e at the head of the list into another higher-order effect e'.

translate :: forall (e :: Type -> Type) (e' :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]). e' <| ef => (e ~> e') -> Eff eh (e ': ef) ~> Eff eh ef Source #

Transforms the first-order effect e at the head of the list into another first-order effect e' and embeds it into the list.

If multiple instances of e' exist in the list, the one closest to the head (with the smallest index) will be targeted.

translateH :: forall (e :: (Type -> Type) -> Type -> Type) (e' :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]). (e' <<| eh, HFunctor e) => (e (Eff eh ef) ~> e' (Eff eh ef)) -> Eff (e ': eh) ef ~> Eff eh ef Source #

Transforms the higher-order effect e at the head of the list into another higher-order effect e' and embeds it into the list.

If multiple instances of e' exist in the list, the one closest to the head (with the smallest index) will be targeted.

rewrite :: forall (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]). e <| ef => (e ~> e) -> Eff eh ef ~> Eff eh ef Source #

Rewrites the first-order effect e in the list.

If multiple instances of e exist in the list, the one closest to the head (with the smallest index) will be targeted.

rewriteH :: forall (e :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]). (e <<| eh, HFunctor e) => (e (Eff eh ef) ~> e (Eff eh ef)) -> Eff eh ef ~> Eff eh ef Source #

Rewrites the higher-order effect e in the list.

If multiple instances of e exist in the list, the one closest to the head (with the smallest index) will be targeted.

transEff :: forall (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). (Union ef ~> Union ef') -> Eff eh ef ~> Eff eh ef' Source #

Transforms all first-order effects in the open union at once.

transEffH :: forall (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). (UnionH eh (Eff eh' ef) ~> UnionH eh' (Eff eh' ef)) -> Eff eh ef ~> Eff eh' ef Source #

Transforms all higher-order effects in the open union at once.

transEffHF :: forall (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]) (ef' :: [EffectF]). (UnionH eh (Eff eh' ef') ~> UnionH eh' (Eff eh' ef')) -> (Union ef ~> Union ef') -> Eff eh ef ~> Eff eh' ef' Source #

Transforms all higher-order and first-order effects in the open union at once.

Manipulating the effect list (without rewriting effectful operations)

Insertion functions

raise :: forall (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]) x. Eff eh ef x -> Eff eh (e ': ef) x Source #

Adds an arbitrary first-order effect e to the head of the list.

raises :: forall (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). IsSuffixOf ef ef' => Eff eh ef ~> Eff eh ef' Source #

Adds multiple arbitrary first-order effects to the head of the list.

raiseN :: forall (len :: Natural) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). WeakenN len ef ef' => Eff eh ef ~> Eff eh ef' Source #

Adds a specified number len of arbitrary first-order effects to the head of the list.

raiseAll :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff eh ('[] :: [EffectF]) x -> Eff eh ef x Source #

Raises an empty first-order effect list to an arbitrary effect list.

raiseUnder :: forall (e1 :: EffectF) (e2 :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]) x. Eff eh (e1 ': ef) x -> Eff eh (e1 ': (e2 ': ef)) x Source #

Inserts an arbitrary first-order effect e2 just below the head of the list.

raisesUnder :: forall (offset :: Natural) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). WeakenUnder offset ef ef' => Eff eh ef ~> Eff eh ef' Source #

Inserts multiple arbitrary first-order effects at a position offset steps below the head of the list.

raiseNUnder :: forall (len :: Natural) (offset :: Natural) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). WeakenNUnder len offset ef ef' => Eff eh ef ~> Eff eh ef' Source #

Inserts len arbitrary first-order effects at a position offset steps below the head of the list.

raiseH :: forall (e :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]) x. Eff eh ef x -> Eff (e ': eh) ef x Source #

Adds a specified number len of arbitrary higher-order effects to the head of the list.

raisesH :: forall (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). IsSuffixOf eh eh' => Eff eh ef ~> Eff eh' ef Source #

Inserts an arbitrary higher-order effect e2 just below the head of the list.

raiseNH :: forall (len :: Natural) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). WeakenN len eh eh' => Eff eh ef ~> Eff eh' ef Source #

Adds a specified number len of arbitrary higher-order effects to the head of the list.

raiseAllH :: forall (ef :: [EffectF]) (eh :: [EffectH]) x. Eff ('[] :: [EffectH]) ef x -> Eff eh ef x Source #

Raises an empty first-order effect list to an arbitrary effect list.

raiseUnderH :: forall (e1 :: EffectH) (e2 :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]) x. Eff (e1 ': eh) ef x -> Eff (e1 ': (e2 ': eh)) ef x Source #

Inserts an arbitrary higher-order effect e2 just below the head of the list.

raiseNUnderH :: forall (len :: Natural) (offset :: Natural) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). WeakenNUnder len offset eh eh' => Eff eh ef ~> Eff eh' ef Source #

Inserts len arbitrary higher-order effects at a position offset steps below the head of the list.

Merging functions

subsume :: forall (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]). e <| ef => Eff eh (e ': ef) ~> Eff eh ef Source #

Merges the first first-order effect e at the head of the list into the same type of effect e that is below it.

If multiple candidates of e exist in the list, the one closest to the head (with the smallest index) will be targeted.

subsumes :: forall (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). Strengthen ef ef' => Eff eh ef ~> Eff eh ef' Source #

Merges multiple first-order effects at the head of the list into effects of the same types that are below them.

subsumeN :: forall (len :: Natural) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). StrengthenN len ef ef' => Eff eh ef ~> Eff eh ef' Source #

Merges a specified number len of first-order effects at the head of the list into effects of the same types that are below them.

subsumeUnder :: forall (e2 :: EffectF) (e1 :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]). e2 <| ef => Eff eh (e1 ': (e2 ': ef)) ~> Eff eh (e1 ': ef) Source #

Merges the first-order effect e2 located just below the head into the same type of effect e2 that is below it.

subsumesUnder :: forall (offset :: Natural) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). StrengthenUnder offset ef ef' => Eff eh ef ~> Eff eh ef' Source #

Merges multiple first-order effects at an offset below the head into effects of the same types that are below them.

subsumeNUnder :: forall (len :: Natural) (offset :: Natural) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). StrengthenNUnder len offset ef ef' => Eff eh ef ~> Eff eh ef' Source #

Merges len first-order effects at an offset below the head into effects of the same types that are below them.

subsumeH :: forall (e :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]). e <<| eh => Eff (e ': eh) ef ~> Eff eh ef Source #

Merges the first higher-order effect e at the head of the list into the same type of effect e that is below it.

If multiple candidates of e exist in the list, the one closest to the head (with the smallest index) will be targeted.

subsumesH :: forall (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). Strengthen eh eh' => Eff eh ef ~> Eff eh' ef Source #

Merges multiple higher-order effects at the head of the list into effects of the same types that are below them.

subsumeNH :: forall (len :: Natural) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). StrengthenN len eh eh' => Eff eh ef ~> Eff eh' ef Source #

Merges a specified number len of higher-order effects at the head of the list into effects of the same types that are below them.

subsumeUnderH :: forall (e2 :: EffectH) (e1 :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]). e2 <<| eh => Eff (e1 ': (e2 ': eh)) ef ~> Eff (e1 ': eh) ef Source #

Merges the higher-order effect e2 located just below the head into the same type of effect e2 that is below it.

subsumeNUnderH :: forall (len :: Natural) (offset :: Natural) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). StrengthenNUnder len offset eh eh' => Eff eh ef ~> Eff eh' ef Source #

Merges len higher-order effects at an offset below the head into effects of the same types that are below them.

Bundling functions

bundle :: forall (ef :: [EffectF]) (bundle :: [EffectF]) (rest :: [EffectF]) (eh :: [EffectH]). Split ef bundle rest => Eff eh ef ~> Eff eh (Union bundle ': rest) Source #

Bundles several effects at the head of the list into a single element using an open union.

bundleN :: forall (len :: Nat) (ef :: [EffectF]) (eh :: [EffectH]). KnownNat len => Eff eh ef ~> Eff eh (Union (Take len ef) ': Drop len ef) Source #

Bundles the first len effects at the head of the list into a single element using an open union.

unbundle :: forall (ef :: [EffectF]) (bundle :: [EffectF]) (rest :: [EffectF]) (eh :: [EffectH]). Split ef bundle rest => Eff eh (Union bundle ': rest) ~> Eff eh ef Source #

Expands effects that have been bundled into an open union.

unbundleN :: forall (len :: Nat) (ef :: [EffectF]) (eh :: [EffectH]). KnownNat len => Eff eh (Union (Take len ef) ': Drop len ef) ~> Eff eh ef Source #

Expands the first len effects that have been bundled into an open union.

bundleUnder :: forall (offset :: Natural) (bundle :: [EffectF]) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). BundleUnder Union offset ef ef' bundle => Eff eh ef ~> Eff eh ef' Source #

Expands effects at an offset below the head of the list into a single element using an open union.

unbundleUnder :: forall (offset :: Natural) (bundle :: [EffectF]) (ef :: [EffectF]) (ef' :: [EffectF]) (eh :: [EffectH]). BundleUnder Union offset ef ef' bundle => Eff eh ef' ~> Eff eh ef Source #

Expands effects that have been bundled into an open union at an offset below the head of the list.

bundleAll :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff eh ef x -> Eff eh '[Union ef] x Source #

Bundles all first-order effects into a single open union.

unbundleAll :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff eh '[Union ef] x -> Eff eh ef x Source #

Expands all first-order effects from a single open union.

bundleH :: forall (eh :: [EffectH]) (bundle :: [EffectH]) (rest :: [EffectH]) (ef :: [EffectF]). Split eh bundle rest => Eff eh ef ~> Eff (UnionH bundle ': rest) ef Source #

Bundles several effects at the head of the list into a single element using an open union.

unbundleH :: forall (eh :: [EffectH]) (bundle :: [EffectH]) (rest :: [EffectH]) (ef :: [EffectF]). Split eh bundle rest => Eff (UnionH bundle ': rest) ef ~> Eff eh ef Source #

Expands effects that have been bundled into an open union.

bundleUnderH :: forall (offset :: Natural) (bundle :: [EffectH]) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). BundleUnder UnionH offset eh eh' bundle => Eff eh ef ~> Eff eh' ef Source #

Expands effects at an offset below the head of the list into a single element using an open union.

unbundleUnderH :: forall (offset :: Natural) (bundle :: [EffectH]) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). BundleUnder UnionH offset eh eh' bundle => Eff eh' ef ~> Eff eh ef Source #

Expands effects that have been bundled into an open union at an offset below the head of the list.

bundleAllH :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff eh ef x -> Eff '[UnionH eh] ef x Source #

Bundles all higher-order effects into a single open union.

unbundleAllH :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff '[UnionH eh] ef x -> Eff eh ef x Source #

Expands all higher-order effects from a single open union.

Manipulating Tags & Keys

tag :: forall {k} (tag :: k) (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]) x. Eff eh (e ': ef) x -> Eff eh ((e # tag) ': ef) x Source #

Attaches the tag to the first-order effect at the head of the list.

untag :: forall {k} (tag :: k) (e :: EffectF) (ef :: [Type -> Type]) (eh :: [EffectH]) x. Eff eh ((e # tag) ': ef) x -> Eff eh (e ': ef) x Source #

Removes the tag from the tagged first-order effect at the head of the list.

retag :: forall {k1} {k2} (tag' :: k1) (tag :: k2) (e :: EffectF) (ef :: [Type -> Type]) (eh :: [EffectH]) x. Eff eh ((e # tag) ': ef) x -> Eff eh ((e # tag') ': ef) x Source #

Changes the tag of the tagged first-order effect at the head of the list to another tag tag'.

tagH :: forall {k} (tag :: k) (e :: (Type -> Type) -> Type -> Type) (ef :: [EffectF]) (eh :: [(Type -> Type) -> Type -> Type]). HFunctor e => Eff (e ': eh) ef ~> Eff ((e ## tag) ': eh) ef Source #

Attaches the tag to the higher-order effect at the head of the list.

untagH :: forall {k} (tag :: k) (e :: (Type -> Type) -> Type -> Type) (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]). HFunctor e => Eff ((e ## tag) ': eh) ef ~> Eff (e ': eh) ef Source #

Removes the tag from the tagged higher-order effect at the head of the list.

retagH :: forall {k1} {k2} (tag' :: k1) (tag :: k2) (e :: (Type -> Type) -> Type -> Type) (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]). HFunctor e => Eff ((e ## tag) ': eh) ef ~> Eff ((e ## tag') ': eh) ef Source #

Changes the tag of the tagged higher-order effect at the head of the list to another tag tag'.

key :: forall {k} (key :: k) (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]) x. Eff eh (e ': ef) x -> Eff eh ((key #> e) ': ef) x Source #

Attaches the key to the first-order effect at the head of the list.

unkey :: forall {k} (key :: k) (e :: EffectF) (ef :: [Type -> Type]) (eh :: [EffectH]) x. Eff eh ((key #> e) ': ef) x -> Eff eh (e ': ef) x Source #

Removes the key from the keyed first-order effect at the head of the list.

rekey :: forall {k1} {k2} (key' :: k1) (key :: k2) (e :: EffectF) (ef :: [Type -> Type]) (eh :: [EffectH]) x. Eff eh ((key #> e) ': ef) x -> Eff eh ((key' #> e) ': ef) x Source #

Changes the key of the keyed first-order effect at the head of the list to another key key'.

keyH :: forall {k} (key :: k) (e :: (Type -> Type) -> Type -> Type) (ef :: [EffectF]) (eh :: [(Type -> Type) -> Type -> Type]). HFunctor e => Eff (e ': eh) ef ~> Eff ((key ##> e) ': eh) ef Source #

Attaches the key to the higher-order effect at the head of the list.

unkeyH :: forall {k} (key :: k) (e :: (Type -> Type) -> Type -> Type) (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]). HFunctor e => Eff ((key ##> e) ': eh) ef ~> Eff (e ': eh) ef Source #

Removes the key from the keyed higher-order effect at the head of the list.

rekeyH :: forall {k1} {k2} (key' :: k1) (key :: k2) (e :: (Type -> Type) -> Type -> Type) (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]). HFunctor e => Eff ((key ##> e) ': eh) ef ~> Eff ((key' ##> e) ': eh) ef Source #

Changes the key of the keyed higher-order effect at the head of the list to another key key'.