Erlang, LFE

Using LFE as a configuration DSL for an Erlang application

This blog describes a use case where you want a more complex configuration language than plain Erlang terms. In other words, you want to have your own language to describe some processing or some other complex logic. What better choice to create such a DSL than LISP itself?

Luckily, LFE, Lisp-Flavoured-Erlang offers a LISP syntax for Erlang VM. This is quite handy, as it allows you to to create your own configuration language using LISP syntax that will actually translate directly into native Erlang terms.

Let’s look at an example of what you might want to achieve, let’s call this DSL ACfg for the purpose of this blog:

(process (id 'process-1)
 (sequence
  (subscribe (topics 'input))
  (transform-message (using 'body (remove-key 'not-useful)))
  (script
   (: lfe_io format "~p~n" (list body)))
  (publish (topics 'output))
  ))

This code could generate a set of Erlang terms, such as:

{{process_id, 'process-1'}, {sequence, [
 {subscriber, [input]},
 {transformer, #{body => #{key => not-useful, op => remove}}}
 {lfe_script, #{sexprs => [':', lfe_io, format, "~p~n", [body]]}}
 {publisher, [output]}
]}}

It is quite clear that using LISP based custom DSL gives you more human readable code and also gives you a lots of flexibility on how the output terms will look like.

Dynamically loading LFE configuration files from Erlang

In order to use configuration files in LFE, they must first be loaded and parsed by LFE itself. It is also reasonable to think that you will want to evaluate the code, so that macros get expanded and all DSL functions get called.

A straightforward way to transform ACfg file into a set of Erlang terms would be something like this:

compile_lfe_mod(PrivDir, ModId, Sexprs) ->
 MacrosPath = filename:join([PrivDir, "acfg-macros.lfe"]),
 Mod0 = lfe_gen:new_module(ModId),
 Mod1 = lfe_gen:add_exports([['cfg', 0]], Mod0),
 Mod2 = lfe_gen:add_form(['include-file', MacrosPath], Mod1),
 Mod3 = lfe_gen:add_form(['defun', 'cfg', [], hd(Sexprs)], Mod2),

 case lfe_gen:compile_mod(Mod3) of
  {ok,ModuleName,Binary,Warnings} ->
    [ error_logger:warning_msg("~p~n", [W]) || W <- Warnings ],
    code:delete(ModuleName),
    code:purge(ModuleName),
    code:load_binary(ModuleName, "nofile", Binary),
    R = ModuleName:cfg(),
    code:delete(ModuleName),
    code:purge(ModuleName),
    {ok, R};

  {error,Reason,Warnings} ->
    [ error_logger:warning_msg("~p~n", [W]) || W <- Warnings ],
    {error, Reason}
  end.

Let’s go through the code a bit now. First we are including a file from a privdir of our application, where we are going to define macros and functions which will actually create our DSL. Next we wrap the S-Expressions into a zero argument function, cfg/0, and eventually we compile the module out of all of this. Then we load the module we just compiled, call the function cfg/0, delete and purge the module and return the result of the call of the function cfg/0.

To load the S-Expressions, we can use following code:

 case lfe_io:read_file(Path) of
  {ok, Sexprs} -> compile_lfe_mod(code:priv_dir(), 'TestMod', Sexprs);
  {error, Reason} -> {error, Reason}
 end.

Of course, we will need to add a dependency on LFE into our rebar.config:

{deps, [
 {lfe, "1.2.0"}
]}

Writing the DSL functions and macros

There is one missing piece to actually making our ACfg language working. That is the acfg-macros.lfe file itself. Let’s look at what this file might look like:

These definitions are just basic examples, I would recommend reading Structure and Interpretation of Computer Programs – The LFE Edition if you are new to LISP or LFE.

We use macro process to build a definition of process. The logic could be more elaborated, there could be some checking of the arguments, adding some extra meta-data and such. In this case we simply turn it into a tuple.

(defmacro process
 ((id args) `(tuple ,id ,args)))

Macro id is used to wrap a process_id:make_id call with the set of arguments.

(defmacro id args
 `(: process_id make_id (list ,@args)))

Here we can see that using a LFE based DSL allows us to actually call some code or transform the arguments in any arbitrary way before the desired configuration is actually built and returned.

Some more examples, used in our ACfg example:

(defmacro topics args
 `(map 'topics (list ,@args)))

(defmacro subscribe args
 (case args
  ([] `(tuple 'subscriber (map #"topics" ,($"topics"))))
  ((x) `(tuple 'subscriber ,x))
 ))

(defmacro publish args
 (case args
  ([] `(tuple 'publisher #M(#"topics" ,($"topics"))))
  ((x) `(tuple 'publisher ,x))
 ))

(defmacro script args
 `(tuple 'lfe_script_runner (map #"sexprs" ',args)))

(defun using
 ((type transformation) `(map ,type ,transformation))
 )

(defun remove-key
 ((key) (map 'key key
 'op 'remove)))

(defun transform-message
 ((args) (tuple 'transformer args)))

As we can see, it is quite easy to prototype a nice and simple configuration DSL in LFE.

This is basically all you need, of course there is a lot more to writing and actually safe DSL, that allows you to only construct meaningful terms but that is beyond the scope of this blog.

It is also a good idea to add some caching on top of these configuration files, so you don’t need to recompile a module each time, perhaps into files on disk or Mnesia or anywhere else.