OpenTelemetry Erlang Configuration

Ship traces from Erlang to OpenSearch with OpenTelemetry

Use OpenTelemetry to easily send Erlang traces to your Logit.io Stack.

APM

This sample app was created and tested with

Erlang/OTP 28 [erts-16.0] [source] [64-bit]

rebar 3.25.0+build.5458.ref6a5805d8 on Erlang/OTP 28 Erts 16.0

Following this guide will create a sample Erlang application that sends traces to OpenTelemetry with basic authentication. This will include the necessary dependencies and configuration.

Key Components

Dependencies: Uses the official OpenTelemetry Erlang libraries

Configuration: Basic auth is configured in sys.config with base64-encoded credentials

Tracing: Examples of creating spans with attributes, events, and nested spans

Worker Pattern: Includes a gen_server example showing how to instrument existing code

Install

Create a new directory for your project and name it ErlangAPMTestApp.

Open a Terminal window or Command Prompt and navigate into the new ErlangAPMTestApp folder.

Create a file in your project folder and call it rebar.config. Open the rebar.config file using your choice of text editor. Copy and Paste the code below into the rebar.config file and then save.

rebar.config
{erl_opts, [debug_info]}.
 
{deps, [
  {opentelemetry, "~> 1.3"},
  {opentelemetry_api, "~> 1.2"},
  {opentelemetry_exporter, "~> 1.6"},
  {hackney, "~> 1.18"}
] }.
 
{shell, [
  {config, "config/sys.config"},
  {apps, [otel_sample_app]}
]}.

Now we need to create two folders in the project folder and call them src and config. Navigate into the new src folder.

Create three additional files in your project folder and call them otel_sample_app.app.src, otel_sample_app.erl and otel_sample_worker.erl. Open the otel_sample_app.app.src file using your text editor. Copy and Paste the code below into the otel_sample_app.app.src file and then save.

otel_sample_app.app.src
{application, otel_sample_app,
  [{description, "OpenTelemetry Sample Application"},
  {vsn, "0.1.0"},
  {registered, []},
  { applications, [
      kernel,
      stdlib,
      opentelemetry,
      opentelemetry_api,
      opentelemetry_exporter,
      hackney
  ]},
  {env, []},
  {modules, []},
  {licenses, ["Apache-2.0"]},
  {links, []}
]}.

Now open the otel_sample_app.erl file with your text editor, Copy and Paste the code below into the otel_sample_app.erl file and then save.

otel_sample_app.erl
-module(otel_sample_app).
-export([start/0, stop/0, create_sample_trace/0]).
 
-include_lib("opentelemetry_api/include/otel_tracer.hrl").
 
%% Start the application
start() ->
    application:ensure_all_started(hackney),
    application:ensure_all_started(opentelemetry_exporter),
    application:ensure_all_started(opentelemetry),
    application:start(otel_sample_app),
    io:format("OpenTelemetry Sample App started~n").
 
%% Stop the application
stop() ->
    application:stop(otel_sample_app),
    application:stop(opentelemetry),
    application:stop(opentelemetry_exporter),
    io:format("OpenTelemetry Sample App stopped~n").
 
%% Create a sample trace with spans
 
create_sample_trace() ->
    % Create multiple traces
    lists:foreach(fun(_) ->
        create_trace_with_spans()
    end, lists:seq(1, 3)).
 
create_trace_with_spans() ->
    % Use the with_span macro to create a parent trace and its spans
    ?with_span(<<"main-operation">>, #{kind => internal},
        fun(_ParentSpanCtx) ->
            % Get the trace ID from the parent span context
            ParentSpanCtx = otel_tracer:current_span_ctx(),
            TraceId = otel_span:trace_id(ParentSpanCtx),
            io:format("Created trace with ID: ~p~n", [TraceId]),
            
            % Add attributes and an event to the main operation
            ?set_attribute(<<"trace.name">>, <<"main-operation">>),
            ?add_event(<<"trace.started">>, #{<<"timestamp">> => erlang:system_time(nanosecond)}),
 
            % Simulate child spans for different operations
            simulate_database_call(),
            simulate_api_request(),
            simulate_processing(),
 
            % Finalize the trace
            ?add_event(<<"trace.completed">>, #{<<"timestamp">> => erlang:system_time(nanosecond)}),
            ok
        end).
 
simulate_database_call() ->
    ?with_span(<<"db-query">>, #{kind => internal},
        fun(_SpanCtx) ->
            ?set_attribute(<<"db.system">>, <<"postgresql">>),
            ?set_attribute(<<"db.operation">>, <<"SELECT">>),
            ?add_event(<<"db.query.start">>, #{<<"query">> => <<"SELECT * FROM users WHERE active = true;">>}),
            timer:sleep(200), % Simulate query execution time
            ?add_event(<<"db.query.end">>, #{<<"rows_returned">> => 42}),
            ok
        end).
 
simulate_api_request() ->
    ?with_span(<<"api-request">>, #{kind => client},
        fun(_SpanCtx) ->
            ?set_attribute(<<"http.method">>, <<"GET">>),
            ?set_attribute(<<"http.url">>, <<"https://api.example.com/data">>),
            ?add_event(<<"http.request.start">>, #{<<"headers">> => #{<<"Authorization">> => <<"Bearer token">>}}),
            timer:sleep(150), % Simulate API request time
            ?add_event(<<"http.request.end">>, #{<<"status_code">> => 200}),
            ok
        end).
 
simulate_processing() ->
    ?with_span(<<"data-processing">>, #{kind => internal},
        fun(_SpanCtx) ->
            ?set_attribute(<<"processing.step">>, <<"aggregation">>),
            ?add_event(<<"processing.start">>, #{<<"input_records">> => 1000}),
            timer:sleep(300), % Simulate processing time
            ?add_event(<<"processing.end">>, #{<<"output_records">> => 900}),
            ok
        end).

Now we need to update the final file in this folder. open the otel_sample_worker.erl file with your text editor, Copy and Paste the code below into the otel_sample_worker.erl file and then save.

otel_sample_worker.erl
-module(otel_sample_worker).
-export([start_link/0, simulate_work/0]).
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_change/3]).
 
-behaviour(gen_server).
-include_lib("opentelemetry_api/include/otel_tracer.hrl").
 
start_link() ->
    gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
 
init([]) ->
    {ok, #{}}.
 
simulate_work() ->
    gen_server:call(?MODULE, simulate_work).
 
handle_call(simulate_work, _From, State) ->
    Result = ?with_span(<<"worker_task">>, #{}, fun() ->
        otel_span:set_attributes([
            {<<"worker.id">>, <<"worker_001">>},
            {<<"task.type">>, <<"data_processing">>}
        ]),
        
        % Simulate some processing
        timer:sleep(200),
        
        % Add some events
        otel_span:add_event(<<"processing_started">>, #{}),
        
        % Simulate different processing steps
        lists:foreach(fun(Step) ->
            ?with_span(list_to_binary("step_" ++ integer_to_list(Step)), #{}, fun() ->
                otel_span:set_attributes([
                    {<<"step.number">>, Step},
                    {<<"step.status">>, <<"processing">>}
                ]),
                timer:sleep(30),
                otel_span:set_attributes([{<<"step.status">>, <<"completed">>}]),
                ok
            end)
        end, lists:seq(1, 3)),
        
        otel_span:add_event(<<"processing_completed">>, #{
            <<"items_processed">> => 100,
            <<"duration_ms">> => 290
        }),
        
        {ok, processed}
    end),
    
    {reply, Result, State}.
 
handle_cast(_Msg, State) ->
    {noreply, State}.
 
handle_info(_Info, State) ->
    {noreply, State}.
 
terminate(_Reason, _State) ->
    ok.
 
code_change(_OldVsn, State, _Extra) ->
    {ok, State}.

Configuring the App

Now navigate back to the project folder and then navigate into the config folder that we created earlier.

Create a file in your config folder and call it sys.config. Open the sys.config file using your choice of text editor. Copy and Paste the code below into the sys.config file and then save.

Please ensure you are logged in to your Logit.io account to ensure correct population of the endpoint address, base64 encoded auth string and port values.

sys.config
[
    {opentelemetry, [
    {resource, [
        {service, #{name => <<"Open Telemetry Tracing - Test App">>, 
                version => <<"1.0.0">>}}
    ]},
    {span_processor, batch},
    {traces_exporter, otlp}
    ]},
    {opentelemetry_exporter, [
        {otlp_endpoint, "https://@opentelemetry.endpointAddress:@opentelemetry.httpsPort"},
        {otlp_headers, [
            {"authorization", "Basic @opentelemetry.base64encodedAuthString"} % base64 encoded "username:password"
        ]},
        {otlp_compression, none}
    ]},
    {kernel, [
        {logger_level, info}
    ]}
].

We have now created the project structure so we need to navigate back to the project folder.

Run the Erlang App

Run the following command in Terminal window or Command Prompt to fetch dependencies:

rebar3 deps

Run the following command to build the application:

rebar3 compile

Start the application with the following:

rebar3 shell

Wait until you see the following message:

OTLP exporter successfully initialized

Inside the shell execute the following command:

otel_sample_app:create_sample_trace().

You will see feedback from the app so that you know that is running. This will include messages starting with 'Created trace with ID:'.

Traces will now have been sent to your stack.

Important Features:

Basic Authentication: Configured in the otlp_headers section with base64-encoded credentials

Span Attributes: Shows how to add metadata like service name, database queries, HTTP requests

Nested Spans: Demonstrates parent-child span relationships

Events: Shows how to add timestamped events to spans

Error Handling: Proper span status setting

Launch Logit.io to view your traces

Launch Jaeger

How to diagnose no data in stack

If you don't see data appearing in your stack after following this integration, take a look at the troubleshooting guide for steps to diagnose and resolve the problem or contact our support team and we'll be happy to assist.