heftia: higher-order effects done right

[ control, library, monads, mpl ] [ Propose Tags ]

Heftia is a higher-order effects version of Freer.

This library provides "continuation-based semantics" for higher-order effects, the same as lexi-lambda's eff. Instead of using the IO monad to implement delimited continuations for effects, Heftia internally uses Freer monad.

The paper

  • Casper Bach Poulsen and Cas van der Rest. 2023. Hefty Algebras: Modular Elaboration of Higher-Order Algebraic Effects. Proc. ACM Program. Lang. 7, POPL, Article 62 (January 2023), 31 pages. https://doi.org/10.1145/3571255

inspires this library. Hefty trees, proposed by the above paper, are extensions of free monads, allowing for a straightforward treatment of higher-order effects.

This library provides Hefty monads and Freer monads, encoded into data types in several ways to enable tuning in pursuit of high performance.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.2.0.0
Change log ChangeLog.md
Dependencies base (>=4.16.4.0 && <4.17), constraints (>=0.13.4 && <0.14), data-effects (>=0.1 && <0.2), extensible (>=0.9 && <0.10), free (>=5.2 && <5.3), kan-extensions (>=5.2.5 && <5.3), membership (==0.0.1), mtl (>=2.2.2 && <2.3), singletons-base (>=3.1 && <3.2), singletons-th (>=3.1 && <3.2), transformers (>=0.5.6 && <0.6), transformers-base (>=0.4.6 && <0.5), unliftio (>=0.2 && <0.3) [details]
License MPL-2.0
Copyright 2023-2024 Yamada Ryo
Author Yamada Ryo <ymdfield@outlook.jp>
Maintainer Yamada Ryo <ymdfield@outlook.jp>
Category Control, Monads
Bug tracker https://github.com/sayo-hs/heftia
Source repo head: git clone https://github.com/sayo-hs/heftia(tag v0.2.0)(heftia)
Uploaded by YamadaRyo at 2024-07-17T08:12:39Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 54 total (17 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for heftia-0.2.0.0

[back to package description]

Heftia: higher-order effects done right for Haskell

Hackage Hackage

Heftia is a higher-order effects version of Freer.

This library provides "continuation-based semantics" for higher-order effects, the same as lexi-lambda's eff. Instead of using the IO monad to implement delimited continuations for effects, Heftia internally uses Freer monad.

The paper

  • Casper Bach Poulsen and Cas van der Rest. 2023. Hefty Algebras: Modular Elaboration of Higher-Order Algebraic Effects. Proc. ACM Program. Lang. 7, POPL, Article 62 (January 2023), 31 pages. https://doi.org/10.1145/3571255

inspires this library. Hefty trees, proposed by the above paper, are extensions of free monads, allowing for a straightforward treatment of higher-order effects.

This library offers Hefty monads and Freer monads, encoded into data types in several ways to enable tuning in pursuit of high performance.

Status

This library is currently in the beta stage. There may be significant changes and potential bugs.

We are looking forward to your feedback!

Getting Started

To run the SemanticsZoo example:

$ git clone https://github.com/sayo-hs/heftia
$ cd heftia/heftia-effects
$ cabal run exe:SemanticsZoo
...
# State + Except
( evalState . runThrow . runCatch $ action ) = Right True
( runThrow . evalState . runCatch $ action ) = Right True

# NonDet + Except
( runNonDet . runThrow . runCatch . runChooseH $ action1 ) = [Right True,Right False]
( runThrow . runNonDet . runCatch . runChooseH $ action1 ) = Right [True,False]
( runNonDet . runThrow . runCatch . runChooseH $ action2 ) = [Right False,Right True]
( runThrow . runNonDet . runCatch . runChooseH $ action2 ) = Right [False,True]

# NonDet + Writer
( runNonDet . runTell . elaborateWriter . runChooseH $ action ) = [(3,(3,True)),(4,(4,False))]
( runTell . runNonDet . elaborateWriter . runChooseH $ action ) = (6,[(3,True),(4,False)])

[Note] All other permutations will cause type errors.
$

Example

Compared to existing Effect System libraries in Haskell that handle higher-order effects, this library's approach allows for a more effortless and flexible handling of higher-order effects. Here are some examples:

Extracting Multi-shot Delimited Continuations

In handling higher-order effects, it's easy to work with multi-shot delimited continuations. This enables an almost complete emulation of "Algebraic Effects and Handlers". For more details, please refer to the example code.

Two interpretations of the censor effect for Writer

Let's consider the following Writer effectful program:

hello :: (Tell String <: m, Monad m) => m ()
hello = do
    tell "Hello"
    tell " world!"

censorHello :: (Tell String <: m, WriterH String <<: m, Monad m) => m ()
censorHello =
    censor
        ( \s ->
            if s == "Hello" then
                "Goodbye"
            else if s == "Hello world!" then
                "Hello world!!"
            else
                s
        )
        hello

For censorHello, should the final written string be "Goodbye world!" (Pre-applying behavior) ? Or should it be "Hello world!!" (Post-applying behavior) ? With Heftia, you can freely choose either behavior depending on which higher-order effect interpreter (which we call an elaborator) you use.

main :: IO ()
main = runEff do
    (sPre, _) <-
        runTell
            . interpretRecH (elabWriterPre @String)
            $ censorHello

    (sPost, _) <-
        runTell
            . interpretRecH (elabWriterPost @String)
            $ censorHello

    liftIO $ putStrLn $ "Pre-applying: " <> sPre
    liftIO $ putStrLn $ "Post-applying: " <> sPost

Using the elabWriterPre elaborator, you'll get "Goodbye world!", whereas with the elabWriterPost elaborator, you'll get "Hello world!!".

Pre-applying: Goodbye world!
Post-applying: Hello world!!

For more details, please refer to the complete code and the implementation of the elaborator.

Furthermore, the structure of Heftia is theoretically straightforward, with ad-hoc elements being eliminated.

Additionally, Heftia supports not only monadic effectful programs but also applicative effectful programs. This may be useful when writing concurrent effectful code.

Heftia is the current main focus of the Sayo Project.

Documentation

The example codes are located in the heftia-effects/Example/ directory. Also, the following HeftWorld example: https://github.com/sayo-hs/HeftWorld

Examples with explanations can be found in the docs/examples/ directory. Documents have become outdated. Please wait for the documentation for the new version to be written.

Limitation and how to avoid it

The reset behavior of the scopes held by unhandled higher-order effects

When attempting to interpret an effect while there are unhandled higher-order effects present, you cannot obtain delimited continuations beyond the action scope held by these unhandled higher-order effects. It appears as if a reset (in the sense of shift/reset) is applied to each of the scopes still held by the remaining unhandled higher-order effects.

In other words, to obtain delimited continuations beyond their scope, it is necessary to first handle and eliminate all higher-order effects that hold those scopes, and then handle the effect targeted for stateful interpretation in that order. For this purpose, it might sometimes be possible to use multi-layering. For an example of multi-layering, see handleReaderThenShift defined in Example/Continuation2 (particularly, the type signature of prog within it). For more details, please refer to the documentation of the interpretRec family of functions.

Comparison

  • Higher-Order Effects: Does it support higher-order effects?
  • Delimited Continuation: The ability to manipulate delimited continuations.
  • Statically Typed Set of Effects: For a term representing an effectful program, is it possible to statically decidable a type that enumerates all the effects the program may produce?
  • Purely Monadic: Is an effectful program represented as a transparent data structure that is a monad, and can it be interpreted into other data types using only pure operations without side effects or unsafePerformIO?
  • Dynamic Effect Rewriting: Can an effectful program have its internal effects altered afterwards (by functions typically referred to as handle with, intercept, interpose, transform, translate, or rewrite) ?
  • Performance: Time complexity or space complexity.
Library or Language Higher-Order Effects Delimited Continuation Statically Typed Set of Effects Purely Monadic Dynamic Effect Rewriting Performance (TODO)
Heftia Yes 1 Multi-shot Yes Yes (also Applicative and others) Yes ?
freer-simple No Multi-shot Yes Yes Yes ?
Polysemy Yes No Yes Yes Yes ?
Effectful Yes No Yes No (based on the IO monad) Yes ?
eff Yes Multi-shot? Yes No (based on the IO monad) Yes Fast
mtl Yes Multi-shot (ContT) Yes Yes No ?
fused-effects Yes No? Yes Yes No ?
koka-lang No? Multi-shot Yes No (language built-in) ? ?
OCaml-lang 5 Yes One-shot No 2 No (language built-in) ? ?

Heftia can simply be described as a higher-order version of freer-simple. This is indeed true in terms of its internal mechanisms as well.

Compatibility with other libraries

Representation of effects

  • Heftia Effects relies on data-effects for the definitions of standard effects such as Reader, Writer, and State.

  • It is generally recommended to use effects defined with automatic derivation provided by data-effects-th.

  • The representation of first-order effects is compatible with freer-simple. Therefore, effects defined for freer-simple can be used as is in this library. However, to avoid confusion between redundantly defined effects, it is recommended to use the effects defined in data-effects.

  • GADTs for higher-order effects need to be instances of the HFunctor type class for convenient usage. While it is still possible to use them without being instances of HFunctor, the interpretRec family of functions cannot be used when higher-order effects that are not HFunctor are unhandled. If this issue is not a concern, the GADT representation of higher-order effects is compatible with Polysemy and fused-effects. It is not compatible with Effectful and eff.

About mtl

  • Since the representation of effectful programs in Heftia is simply a monad (Eff), it can be used as the base monad for transformers. This means you can stack any transformer on top of it.

  • The Eff monad is an instance of MonadIO, MonadError, MonadRWS, etc., and these behave as the senders for the embedded IO or the effect GADTs defined in data-effects.

Future Plans

  • Enriching the documentation and tests

  • Completing missing definitions such as

    • raise, raiseUnder, and subsume for arbitrary numbers of effects by type classes.
    • more patterns of interpret & transform function-families.
    • handlers for the Accum and others effect classes

    and others.

  • Benchmarking

License

The license is MPL 2.0. Please refer to the NOTICE. Additionally, this README.md and the documents under the docs/docs-ja directory are licensed under CC BY-SA 4.0.

Your contributions are welcome!

Please see CONTRIBUTING.md.

Credits

Parts of this project have been inspired by the following resources:

2

potential for 'unhandled' runtime errors