codec-beam: Erlang VM byte code assembler

[ bsd3, codec, language, library ] [ Propose Tags ]

Erlang VM byte code assembler.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0, 0.1.1, 0.2.0
Dependencies base (>=4.8 && <5), bytestring (>=0.10.6), containers (>=0.5.6.2), text (>=1.2.2), zlib (>=0.6.1.1) [details]
License BSD-3-Clause
Author
Maintainer h.kofigumbs@gmail.com
Category Language, Codec
Home page https://github.com/hkgumbs/codec-beam#readme
Bug tracker https://github.com/hkgumbs/codec-beam/issues
Source repo head: git clone git://github.com/hkgumbs/codec-beam.git
Uploaded by hkgumbs at 2018-04-06T21:51:32Z
Distributions LTSHaskell:0.2.0, Stackage:0.2.0
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 2192 total (15 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-04-14 [all 1 reports]

Readme for codec-beam-0.1.1

[back to package description]

Build Status Erlant/OTP Release

NOTE: Participation is encouraged! Make issues, ask questions, submit pull requests (even if it’s your first time contributing to open-source — you’ll get lots of help), and give feedback!

Erlang VM byte code assembler for implementing compile-to-beam languages. The goal is to a provide delightful API for generating BEAM instructions from pure Haskell.

Usage

This example writes a simple module to a file:

{-# LANGUAGE OverloadedStrings #-}
module Main where
import qualified Data.ByteString.Lazy as LBS

import Codec.Beam.Instructions (func_info, label, move, return')
import qualified Codec.Beam as Beam

main :: IO ()
main =
  LBS.writeFile "test_module.beam" $
    Beam.encode "test_module"
      [ Beam.export "tuple_of_one" 0
      ]
      [ label (Beam.Label 1)
      , func_info "tuple_of_one" 0
      , label (Beam.Label 2)
      , move (Beam.Tuple [Beam.Integer 1]) (Beam.X 0)
      , return'
      ]

After you run that program, you can load the resulting module from the Erlang shell!

$ erl
1> l(test_module).
2> test_module:tuple_of_one().
{1}

You can find an example project on GitHub.

Build

Use Stack:

stack build --test

Acknowledgements

Thanks to the following projects, which helped me understand the BEAM file format: