tigerbeetle-hs: A Haskell client library for Tigerbeetle database

[ bsd3, database, experimental, library, program ] [ Propose Tags ] [ Report a vulnerability ]

Modules

  • Database
    • TigerBeetle
      • Database.TigerBeetle.Account
      • Database.TigerBeetle.Amount
      • Database.TigerBeetle.Client
        • Database.TigerBeetle.Client.Async
        • Database.TigerBeetle.Client.Sync
      • Database.TigerBeetle.Code
      • Internal
        • FFI
          • Database.TigerBeetle.Internal.FFI.Account
          • Database.TigerBeetle.Internal.FFI.Client
      • Database.TigerBeetle.Ledger
      • Raw
        • Database.TigerBeetle.Raw.Account
        • Database.TigerBeetle.Raw.Client
        • Database.TigerBeetle.Raw.Transfer
      • Database.TigerBeetle.Response
        • Database.TigerBeetle.Response.Account
        • Database.TigerBeetle.Response.Transfer
      • Database.TigerBeetle.Timestamp
      • Database.TigerBeetle.Transfer

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0
Change log CHANGELOG.md
Dependencies base (>=4.18.0.0 && <4.19), binary (>=0.8.9 && <0.9), bytestring (>=0.11.5 && <0.12), containers (>=0.6.7 && <0.7), mtl (>=2.3.1 && <2.4), stm (>=2.5.1 && <2.6), text (>=2.0.2 && <2.1), tigerbeetle-hs, vector (>=0.13.1 && <0.14), wide-word (==0.1.6.0) [details]
License BSD-3-Clause
Author James King
Maintainer james@agentultra.com
Category Experimental, Database
Home page https://github.com/agentultra/tigerbeetle-hs#README
Bug tracker https://github.com/agentultra/tigerbeetle-hs/issues
Source repo head: git clone https://github.com/agentultra/tigerbeetle-hs
Uploaded by agentultra at 2025-09-05T19:33:04Z
Distributions
Executables tigerbeetle-hs
Downloads 2 total (2 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2025-09-05 [all 2 reports]

Readme for tigerbeetle-hs-0.1.0.0

[back to package description]

tigerbeetle-hs

An unofficial community Haskell client for the financial transaction database, Tigerbeetle.

The current release supports Tigerbeetle 0.16.33.

Note that at this stage the API is subject to change. Consider this experimental. We will aim to make major version releases have a stable API.

This project will aim to support the upstream release cycle and version policies in future releases.

The aim of this client library is to provide a high-level, Haskell-friendly API as well as access to lower level bindings in case your project needs them.

It is not a full-featured application framework.

It is a good starting point for building a framework. Or a snappy tool.

Sync Client

The synchronous client interface blocks and awaits the result of each command sent to the server. This is useful mainly for prototyping, basic scripting, and exploring the API in ghci.

Example usage:

module Main where

import Database.TigerBeetle.Account
import Database.TigerBeetle.Client
import qualified Database.TigerBeetle.Client.Sync qualified as Sync

main :: IO ()
main = do
  withClient (ClusterId 0) (Address "3000") $ do
    result <- createAccounts [CreateAccount (AccountId 0) (LedgerId 0) (AccountCode 100)]
    print result

It is important to note that each action, such as createAccounts, will block and await the response from the server.

Async Client

The asynchronous client interface is what most application developers should use. It is minimal and requires you to write your own loop and manage requests.

Example usage:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Control.Concurrent
import Control.Concurrent.STM
import Database.TigerBeetle.Account
import Database.TigerBeetle.Client
import qualified Database.TigerBeetle.Client.Async as Async
import Database.TigerBeetle.Response

main :: IO ()
main = do
  result <- newTVarIO Nothing

  -- When we initialize a thread, this context will associate responses from the
  -- server to the thread that issued the command.
  let mainContext = Async.ThreadContext 0

  let completionCallback _ response = do
        atomically $ writeTVar result (Just response)

  -- In this example we're awaiting all responses on the main thread but we
  -- could assemble our main loop to run more work in parallel across more
  -- threads as needed.
  Async.withClient (ClusterId 0) (Address "3000") mainContext completionCallback $ do
    Async.createAccounts [CreateAccount (AccountId 9) (LedgerId 9) (AccountCode 1)]

  -- For example, instead of awaiting the result we could feed results from
  -- child threads over an STM channel or queue.
  --
  -- For this example though we await the result on our TVar.
  await result

await :: TVar (Maybe Response) -> IO ()
await result = do
  r <- readTVarIO result
  case r of
    Nothing -> threadDelay 3000 >> await result
    Just yay -> print yay

This API enables you to build the event loop suitable for your application. Be aware that your callback will need to match responses to commands on your own.

Future versions of this library may include a framework based on STM that will give you a common setup based on this API.

Commands

The essential commands are available:

  • Create Accounts
  • Create Transfers

And the essential queries:

  • Lookup Accounts
  • Lookup Transfers
  • Get Account Balances
  • Get Account Transfers
  • Query Accounts
  • Query Transfers

What's not supported (yet):

  • User data: The Tigerbeetle client has fields for user metadata. We're planning on supporting this in a Haskell friendly way in the future.

Raw

The modules in Database.TigerBeetle.Raw are meant to be wrappers for the FFI calls. If you want to build your own higher-level client library you should be able to use code from this layer as a starting point that is one level above raw FFI code.

Reporting Issues

Please feel free to report issues or suggest improvements via Github Issues.

Include as much detail and context as you can.

Contributing

We welcome contributions from all interested hackers and developers of all skill levels.

Interested in contributing? Check out CONTRIBUTING.