Designing Boring Software with Functional Programming - Part 1

Posted on August 5, 2024

Introduction

Functional programming languages, such as Haskell, have a reputation for being languages that are designed for researchers to write white papers and not for practical software.

I believe this reputation is undeserved.

In this post I’m going to show you how I design software in Haskell for businesses. Functional programming languages are all good at this. I happen to use Haskell at my job and on my stream and I think it is particularly well suited to the task of designing and building line-of-business software.

We’re going to design an accounting ledger system for a bank. We’re going to necessarily limit the scope of this project to fit into a couple of blog posts. That means we will leave out features you would find in a real banking system. A good number of folks have some familiarity with what a bank is and does which should help keep us grounded.

Design with Types

The essence of this process is to ask questions and write definitions. We write our definitions directly in a Haskell module. This module will serve both as our documentation and as our interface that we will use in our code.

The process starts with a blank file ready to receive our definitions. Let’s start our Bank.hs module:

module Bank where

We’re now going to sit down with our domain expert. They are someone who knows the problem space well. We can turn to them for answers when we have questions.

After some discussion about what an account is we arrive at this definition:

An account is a collection of entries that categorize amounts of funds that have been credited or debited.

Let’s write those definitions in Haskell:

newtype Amount = Amount { getAmount :: Integer }
  deriving (Eq, Num, Show)

Here, newtype is like an alias for another type. We could represent amounts with Integer but we don’t want to get them mixed up with other Integer values in our program. And after some discussion on how amounts are represented and used in our accounting system, they aren’t integers at all; amounts are represented as positive values. It’s the category, or cost type that determines how to interpret the amount.

We should prefer the words our domain expert would use. It helps them understand the definitions in our module. And it keeps our code clear so we can understand it later. In Domain Driven Design, we call this Ubiquitous Language.

Let’s add the definition for CostType:

data CostType = Credit | Debit
  deriving (Eq, Show)

The data keyword here is defining a type. Types represent important concepts and entities in our domain. After the = sign we have Credit, a | (vertical bar) sign, and the word Debit. You can read this as:

A CostType is a Credit or a Debit.

The | (vertical bar) sign means or and represents a choice in our domain. When you have a CostType it can either be a Credit or a Debit but never both at the same time. We call these sum types in Haskell if you or your domain expert are curious.

With these definitions we can create our entry:

data Entry
  = Entry
  { costType :: CostType
  , amount   :: Amount
  }
  deriving (Eq, Show)

Here we are defining another type. But unlike the CostType this doesn’t have a | (vertical bar). This is a record. Inside the braces we have a list of things: costType :: CostType and amount :: Amount. These are fields of our record and can be read as, costType has type CostType. A record is like a row of data in a spreadsheet. We call it a product type in Haskell.

Finally we can write the definition of our account:

newtype Account = Account { getAccountEntries :: [Entry] }
  deriving (Eq, Show)

We’re using Account as an alias for the type, [Entry] which is Haskell for a list of Entry. This is the most simple way to represent a collection of zero or more entries in Haskell.

Separation of Program and State

Let’s take a moment to point out that we haven’t specified what an Account ID is. The intention here is that we’re declaring what the entities in our domain are which doesn’t include implementation details like database identifiers. At this level we don’t want to concern ourselves with such details.

We want to focus on what an Account is and what the operations on it mean (in other words, semantics). We need types to represent these concepts and the logic that governs how they can be used. The nice thing is that we can use this code in those later stages when we are accessing databases.

In a different part of our program we will define how these entities can be stored and retrieved from a database and served over a network. These are separate concerns from what an account is and what “deposit” means.

Functions are Types Too

A new Account is one that has no entries in it.

newAccount :: Account
newAccount = Account []

We have that :: showing up again. It can be read as, newAccount has type Account just like the definition of the fields of the Entry record. The [] denotes the empty list.

Next we will add our first function type for the definition of addEntries. This function will add a list of entries to an account.

addEntries :: Account -> [Entry] -> Account
addEntries account entries = Account $ account.getAccountEntries ++ entries

The first line of our definition is specifying the type. Note the -> (arrow). This tells us we’re looking at a function. Functions model relationships, mappings, and change in our domain. In addEntries we take an account, a list of entries, and we are left with an account: the entries of the original account combined with the additional entries.

Another common operation on Account is to check the balance: the available funds the bank is liable to the customer for. We can model that with a function from Account to Integer. When we render the balance to the customer they will often expect to see a signed number where the sign represents an overdrawn or negative balance:

balance :: Account -> Integer
balance = sum . map toIntegerAmounts . getAccountEntries
  where
    toIntegerAmounts :: Entry -> Integer
    toIntegerAmounts entry = case entry.costType of
      Credit -> entry.amount.getAmount
      Debit -> -entry.amount.getAmount

If we focus on the first line, the type, we see that we start with an Account and go to an Integer; the balance.

We also see the :: again in the definition of toIntegerAmounts which maps values of type Entry to values of type Integer. Recall earlier when we learned that, It’s the cost type that determines how to interpret the amount. This function represents that definition when we use the case expression to pattern match over the cost type.

Properties

The types we are defining in our program denote sets of values. For example, the CostType type is the set of values, {Credit, Debit}. The set of values for Entry is much too large to write down here but you can try writing out a few to get an idea.

A property is a predicate we want to hold true for all values in a set or sets.

What this means is that we want to define what the relationships in our program mean; what limits and rules they have… what the properties are.

In this post we will use a simple convention to get the idea across. In a real implementation you will want to use a library like QuickCheck to help you write and check these.

Let’s start with a super trivial one: the balance of a new account is always zero:

propertyBalanceOfNewAccount :: Bool
propertyBalanceOfNewAccount =
  balance newAccount == 0

If we have implemented balance and newAccount properly this definition will evaluate to True.

We will use property as a prefix in our definitions to denote a property test.

Let’s add another definition, total which is the sum of all Entry amounts in an Account regardless of their CostType:

total :: Account -> Integer
total = sum . map toIntegerAmounts . getAccountEntries
  where
    toIntegerAmounts :: Entry -> Integer
    toIntegerAmounts = getAmount . amount

Notice how our definition of toIntegerAmounts in this function doesn’t pattern match on CostType at all. This matches the plain-language specification we (or our domain expert) gave before.

We can now write another property:

propertyTotalBalance :: Bool
propertyTotalBalance =
  let account = addEntries newAccount
                [ Entry Credit 100 0
                , Entry Debit 27 1
                ]
  in balance account <= total account

Here we choose an example account to check. In a good property test we should be able to change this so that the test runner will generate an arbitrary Account with any list of possible Entry. If we’re right this assumption will always hold True for all of them.

Ledger

These are sufficient definitions of Account and Entry and some basic types to enable us to start defining our Ledger.

Our domain expert explains that we will need to use double-entry accounting in our system and explains:

Double-entry accounting, is a method of bookkeeping that relies on a two-sided ledger to maintain financial information. Every entry to an account requires a corresponding and opposite entry to a different account.

We ask them to explain what the different accounts are called and how they should work:

One account is called assets and the other, liabilities. The sum of the balances of each account must always equal 0.

Let’s write the definition of a Ledger:

data Ledger
  = Ledger
  { assets      :: Account
  , liabilities :: Account
  }
  deriving (Eq, Show)

newLedger :: Ledger
newLedger = Ledger { assets = newAccount, liabilities = newAccount }

Simple enough. Our domain expert will hopefully be able to read this. If they’ve been paying attention they may agree that our definition is correct.

While we may not use it in our production code, it is a good idea to record the definitions of predicates that ensure our ledger is correct:

isBalanced :: Ledger -> Bool
isBalanced ledger
  = balance ledger.assets + balance ledger.liabilities == 0

Translated directly from the specification.

It will aid us in the design phase and our tests. If we trust that our design ensures our code is correct by definition and our tests are sufficiently exercising our assumptions then we wouldn’t need to use this in our production application code to verify our assumptions at run-time. It will always be balanced and cannot enter an unbalanced state.

Ledgers need to support transactions in our bank. We will define two kinds of transactions for this post but there could be more:

data Transaction
  = Withdraw Amount
  | Deposit Amount
  deriving (Eq, Show)

This says that a Transaction can either Withdraw an Amount or Deposit an Amount.

And when we want to change a ledger we need to create a transaction. This means we need a function:

transact :: [Transaction] -> Ledger -> Ledger

Here we say that transact is a type that goes from a list of Transaction and a Ledger to a Ledger. The definition follows:

transact txns ledger
  = Ledger
  { assets = addEntries ledger.assets $ map assetEntry txns
  , liabilities = addEntries ledger.liabilities $ map liabilityEntry txns
  }
  where
    assetEntry :: Transaction -> Entry
    assetEntry transaction = case transaction of
      Withdraw amt -> Entry Debit amt
      Deposit amt  -> Entry Credit amt

    liabilityEntry :: Transaction -> Entry
    liabilityEntry transaction = case transaction of
      Withdraw amt -> Entry Credit amt
      Deposit amt  -> Entry Debit amt

Here we update the accounts as directed by the specification. In the case of a Withdraw we create a Debit on the assets account and a Deposit against the liabilities account. We do the opposite in the case of a Deposit.

And if we implemented this properly then the following property would hold for any list of transactions. Again, we pick a list of transactions but any list of transactions should hold:

propertyAlwaysBalanced :: Bool
propertyAlwaysBalanced =
  isBalanced . transact [Deposit 100, Withdraw 27] 1 $ newLedger

This says that we take isBalanced after we transact on a newLedger.

On Formalisms

Let’s take another moment to note that nothing we’ve said about accounts or ledgers comes from outside this module. We haven’t waved our hands and left a definition as an exercise to the reader. We haven’t had to exercise our program against a live database with a web server and a host operating system in order to verify our assumptions.

While we’re not writing proofs we are inspired by formal proofs in mathematics where definitions and axioms are explicitly stated and every theorem follows from prior ones.

Conclusion

Designing software in Haskell is often as straight-forward as chatting with a domain expert and writing down some types and functions. Our project should have a module that contains these definitions. The definitions should be readable by a domain expert who isn’t necessarily a Haskell programmer. So keep it simple!

In order to be useful our program may have to access a database or talk to other systems over the network. We should strive to keep these concerns separate from the business logic of our system. It will make our code easier to structure and easier to test.

In the next post we will explore persisting our ledger system to a data store!