Building on top of OTP with Purescript with Pinto

Published on 2019-8-20

All the posts so far..

Useful links

We left the last post demonstrating that an end-to-end Purescript project was essentially a pile of Purescript written in the right place, in order that the usual Erlang application/rebar3/etc can just work with it.

That entry point again then

We looked at BookApp.purs, which compiled into an Erlang module called bookApp@ps. which ends up in src/compiled_ps and gets picked up with the usual Erlang structure. Let's look at that file and see what we see:

module BookApp where

import Prelude
import BookSup as BookSup

import Pinto.App as App

start = App.simpleStart BookSup.startLink

That simpleStart function is just a Pinto helper that describes an entry point that doesn't worry about inputs, and provided a Supervisor will start that Supervisor when the application is started.

This gets compiled into the following Erlang

% Generated by purs version 0.12.3
-module(bookApp@ps).
-export([start/0, start/2]).
-compile(nowarn_shadow_vars).
-compile(nowarn_unused_vars).
-compile(no_auto_import).
-file("src/BookApp.purs", 8).
start() -> (pinto_app@ps:simpleStart((bookSup@ps:startLink()))).
-file("src/BookApp.purs", 8).
start(_@0,_@1) -> ((pinto_app@ps:simpleStart((bookSup@ps:startLink())))(_@0, _@1)).

If get rid of the cruft, that's essentially just

-module(bookApp@ps).
-export([start/0, start/2]).
start() -> (pinto_app@ps:simpleStart((bookSup@ps:startLink()))).
start(_@0,_@1) -> ((pinto_app@ps:simpleStart((bookSup@ps:startLink())))(_@0, _@1)).

This is just a standard application module that you'd find in an Erlang application, exporting the usual start function that calls into a supervisor to start it. This is the only time I'll be loading up the compiled Purescript as it's the simplest example - but nearly all of the Pinto helpers are about making sure we can end up exposing a module that looks like the equivalent OTP erlang module.

The supervisor? More of the same

module BookSup where

-- [[ imports redacted ]]

startLink :: Effect Pinto.StartLinkResult
startLink = Sup.startLink "book_sup" init

init :: Effect SupervisorSpec
init = do
  connectionString <- BookConfig.connectionString
  webPort <- BookConfig.webPort
  pure $ buildSupervisor
                # supervisorStrategy OneForOne
                # supervisorChildren ( ( buildChild
                                       # childType Worker
                                       # childId "book_web"
                                       # childStart BookWeb.startLink  { webPort } )
                                       : 
                                       ( buildChild
                                       # childType Worker
                                       # childId "book_library"
                                       # childStart BookLibrary.startLink { connectionString } )
                                        : nil)

Sup.startLink is a Pinto helper that'll end up calling our usual supervisor:start_link under the hood, with our init function being invoked within the context of that created supervisor and returning a supervisor spec when invoked.

The supervisor spec structure is quite a complicated tangle of maps in Erlang, and while possible to directly represent these in Purescript with records, there are convenience builders/etc provided by Pinto to describe these specs in a more Purescripty and type safe manner - all of these values are pretty much relatable right back to the OTP documentation which is handy and intentional.

Now, let's break down one of these gen servers to see what we can see - we'll have to do this piece-meal as there is a lot to uncover. We'll be looking at BookLibrary.purs, invoked above in the second child of the supervision tree with BookLibrary.startLink and the code for which is shown below..


serverName :: ServerName State
serverName = ServerName "book_library"

type BookLibraryStartArgs = {
  connectionString :: ConnectionString
}

startLink :: BookLibraryStartArgs -> Effect StartLinkResult
startLink args =
  Gen.startLink serverName $ init args

So there is nothing too special about this, we're exporting a function called startLink that takes some configuration from the supervisor, and that calls into the Pinto function Gen.startLink with the serverName, and an init function to invoke within the context of the started GenServer along with those args. This isn't disimilar to how this looks in the Erlang world so far.

That serverName construct represents both the unique identifier for this started process, and also encapsulates the type of the 'state' that is held by the GenServer, and will be used in all interactions with the Gen module.

That init function?


init :: BookLibraryStartArgs -> Effect State
init args = do
  connection <- Redis.open args.connectionString
  pure $ { connection }

Takes place inside the context of the newly started GenServer, and is responsible for effectfully creating the initial state of the GenServer, which is just a Redis connection (We'll talk about that later). This is actually all we need to create a running GenServer as everything else is entirely optonal.

Obviously that's useless, so let's look at how we can externally call into this GenServer to do something useful


findAll :: Effect (List Book)
findAll = 
  Gen.doCall serverName \state@{ connection } -> do
    books <- Redis.findAll dbPrefix connection
    pure $ CallReply books state

We can export a plain ol' Purescript function called findAll that returns a plain ol' Effect producing a List of Book, and we can do the rest of the work by invoking a 'call' with the Gen module, by giving Gen.doCall our serverName construct, we are able to then provide a typed callback that will be invoked within the context of the gen-server as part of a handle_call, and therefore gain access to the state and return some books by calling into the Redis connection.

The original Erlang would of course look a little like this.


-export([start_link/1, 
         init/1,
         find_all/0]).

-record(args, {
    connection_string :: connection_string()
    }).

-record(state, {
    connection :: redis:connection()
  }).

find_all() ->
  gen_server:call({via, gproc, {n, l, ?MODULE}}, find_all).

start_link(Args) ->
  gen_server:start_link({via, gproc, {n, l, ?MODULE}}, ?MODULE, [Args], []).

init([#args { connection_string = ConnectionString }]) ->
  { ok, Connection } = redis:open(ConnectionString),
  {ok, #state { connection = Connection }}.

handle_call(find_all, _Sender, State = #state { connection = Connection }) ->
  { ok, Result } = redis:find_prefix(dbPrefix, Connection),
  { reply, Result, State }.

This is a bit unwieldy, lacks any notion of type safety across the calls being made, but is still pleasantly relatable to the Purescript variant.


serverName :: ServerName State
serverName = ServerName "book_library"

type BookLibraryStartArgs = {
  connectionString :: ConnectionString
}

type State = {
  connection :: RedisConnection
}

startLink :: BookLibraryStartArgs -> Effect StartLinkResult
startLink args =
  Gen.startLink serverName $ init args

init :: BookLibraryStartArgs -> Effect State
init args = do
  connection <- Redis.open args.connectionString
  pure $ { connection }

findAll :: Effect (List Book)
findAll = 
  Gen.doCall serverName \state@{ connection } -> do
    books <- Redis.findAll dbPrefix connection
    pure $ CallReply books state

Note: Wrapping up a connection behind a genserver is nearly always not the thing you want to do (effectively it introduces a read/write lock), but sample code gonna sample code.

Next up, we'll look at how we could use this GenServer from Stetson to provide a restful JSON API to our client.

2020 © Rob Ashton. ALL Rights Reserved.