1
0
mirror of https://github.com/erlang/docker-erlang-example.git synced 2025-07-30 22:43:04 +03:00

Refactoring: Copy Logstash example

This commit copies Siri Hansen's (@sirihansen) Logstash example from:

https://github.com/erlang/docker-erlang-example/tree/logstash
This commit is contained in:
Kjell Winblad
2019-05-20 14:03:14 +02:00
parent 36d97779cc
commit 61d3fe2a44
19 changed files with 660 additions and 0 deletions

2
advanced_examples/logstash/.gitignore vendored Normal file
View File

@ -0,0 +1,2 @@
_build/
rebar.lock

View File

@ -0,0 +1,35 @@
sudo: required
addons:
apt:
packages:
- curl
env:
before_script:
script:
- ./create-certs
- docker build -t logstash logstash/
- docker run --name logstash -d -p 9600:9600 -p 44622:44622/udp logstash
- docker build -t dockerwatch .
- docker run --name dockerwatch -d -p 8443:8443 --volume="$PWD/ssl:/etc/ssl/certs" --log-driver=gelf --log-opt gelf-address=udp://0.0.0.0:44622 dockerwatch
- IP=$(docker inspect --format='{{range .NetworkSettings.Networks}}{{.IPAddress}}{{end}}' dockerwatch)
# Wait for logstash to finis startup
- until curl -s 'localhost:9600/_node'; do sleep 5; echo "waiting for logstash to finish startup"; done
# Create counter via http
- "curl -H 'Content-Type: application/json' -X POST -d '' http://$IP:8080/cnt"
# Increment counter via http
- "curl -H 'Content-Type: application/json' -X POST -d '{}' http://$IP:8080/cnt"
# Read all counters via https
- "curl --cacert ssl/dockerwatch-ca.pem -H 'Accept: application/json' https://localhost:8443/"
# Read the counter `cnt` as json using https
- "curl --cacert ssl/dockerwatch-ca.pem -H 'Accept: application/json' https://localhost:8443/cnt"
# Increment the counter `cnt` by 20 using http
- "curl -H 'Content-Type: application/json' -X POST -d '{\"value\":20}' http://$IP:8080/cnt"
# Read the counter `cnt` as text using http
- "curl -H 'Accept: text/plain' http://$IP:8080/cnt"
# Check that there are 6 lines in the log (one for each curl command above)
- sleep 5
- test "$(docker exec logstash cat /usr/share/logstash/logs/output.log | wc -l)" = "6"

View File

@ -0,0 +1,26 @@
## Docker Cheatsheet
* Remove all containers that are not running:
$ docker rm $(docker ps -aq -f status=exited)
* Remove dangling images:
$ docker rmi $(docker images -f dangling=true -q)
* Attach to running docker:
$ docker exec -i -t NameOrId /bin/sh
## Core generation
* `/proc/sys/core_pattern` is clearly persisted on the host. Taking note of
its content before starting any endeavour is therefore highly encouraged.
* dockers `--privileged` is necessary for a gdb session to catch the stack,
without privileges, gdb just complains about No stack. Google still is
hardly knowledgeable about this phenomenon...
* setting ulimit on docker run works perfectly, for future googlers (syntax hard to find),
a docker-compose example:
ulimits:
core: -1

View File

@ -0,0 +1,37 @@
# Build stage 0
FROM erlang:alpine
# Install Rebar3
RUN mkdir -p /buildroot/rebar3/bin
ADD https://s3.amazonaws.com/rebar3/rebar3 /buildroot/rebar3/bin/rebar3
RUN chmod a+x /buildroot/rebar3/bin/rebar3
# Setup Environment
ENV PATH=/buildroot/rebar3/bin:$PATH
# Reset working directory
WORKDIR /buildroot
# Copy our Erlang test application
COPY dockerwatch dockerwatch
# And build the release
WORKDIR dockerwatch
RUN rebar3 as prod release
# Build stage 1
FROM alpine
# Install some libs
RUN apk add --no-cache openssl && \
apk add --no-cache ncurses-libs
# Install the released application
COPY --from=0 /buildroot/dockerwatch/_build/prod/rel/dockerwatch /dockerwatch
# Expose relevant ports
EXPOSE 8080
EXPOSE 8443
CMD ["/dockerwatch/bin/dockerwatch", "foreground"]

View File

@ -0,0 +1,23 @@
## Generating Certificate
Generate certificates in subdirectory `ssl`.
### Root CA
$ openssl genrsa -out dockerwatch-ca.key 4096
$ openssl req -x509 -new -nodes -key dockerwatch-ca.key -sha256 -days 1024 -out dockerwatch-ca.pem
### Server Certificate
$ openssl genrsa -out dockerwatch-server.key 4096
Certificate signing request
$ openssl req -new -key dockerwatch-server.key -out dockerwatch-server.csr
The most important field: `Common Name (eg, YOUR name) []: localhost`. We use localhost in this example.
### Sign it
$ openssl x509 -req -in dockerwatch-server.csr -CA dockerwatch-ca.pem -CAkey dockerwatch-ca.key -CAcreateserial -out dockerwatch-server.pem -days 500 -sha256

View File

@ -0,0 +1,162 @@
## Using Logstash to collect log events
This example runs a Logstash instance which takes `gelf` messages as
input on UDP port `44622`.
Build the image with
docker build -t logstash logstash/
Run it with
docker run --rm -p 44622:44622/udp logstash
### Configuration
The Logstash pipeline configuration is specified in
`logstash/pipeline/logstash.conf`.
```
input {
gelf {
use_udp => true
port => 44622
}
}
filter {
# If a log message can be parsed as json, do so, and populate the
# log event with fields found.
json {
skip_on_invalid_json => "true"
source => "message"
}
# Convert the level field to an integer
mutate {
convert => {
"level" => "integer"
}
}
}
output {
stdout {
}
file {
path => "/usr/share/logstash/logs/output.log"
}
}
```
### Run the example
Build the docker-erlang-example image:
docker build -t dockerwatch .
To forward log events (single line printouts to STDOUT) from the
docker-erlang-example image into the Logstash container, use the
`gelf` log driver and specify the UDP port number, for example:
docker run -p 8443:8443 --volume="$PWD/ssl:/etc/ssl/certs" --log-driver=gelf --log-opt gelf-address=udp://0.0.0.0:44622 dockerwatch
In general, a single line printout from Erlang's Logger can for
instance be:
2018-11-12T15:32:20.284863+00:00 notice: Hello world
When forwarded to Logstash as is, this will result in the following
log event:
```
{
"image_id" => "sha256:63bb61c199d0d649d178cfdbedfc88e6253f24e534f09fd15c3ef79302931ed0",
"command" => "/dockerwatch/bin/dockerwatch console",
"version" => "1.1",
"source_host" => "172.17.0.1",
"container_id" => "a83600195dd0867c5996ea625d7f7c5fc1b87a97043c649a7cb0ed52058d75f1",
"tag" => "a83600195dd0",
"level" => 6,
"image_name" => "erlang-dockerwatch",
"@timestamp" => 2018-11-12T15:32:20.463Z,
"container_name" => "epic_chebyshev",
"message" => "2018-11-12T15:32:20.284863+00:00 notice: Hello world\r",
"host" => "elxa19vlx02",
"created" => "2018-11-12T15:12:55.198308117Z",
"@version" => "1"
}
```
Notice that the message itself includes a timestamp, but it is not
exactly the same as the `@timestamp` field of the log event. Also, the
`level` field of the log event is `6` (info), while the level of the
actual message was `notice` (5). To overcome this, and popluate the
Logstash log event with the real values from a logger event, we can
format the log event as json and let Logstash parse it (enabled by the
json filter specified in logstash.conf). The following sys.config can
be used:
```
[{kernel, [{logger,
[%% Set formatter template to print jason
{handler,default,logger_std_h,
#{formatter=>
{logger_formatter,
#{template=>
["{ \"@timestamp\": \"",time,
"\", \"level\": \"",{level_int,[level_int],[level]},
"\", \"message\": \"",msg,"\" }\n"]}}}},
%% Add a primary filter to insert 'level_int' field in metadata
{filters,log,
[{level_int,{fun dockerwatch_filter:add_level_int/2,[]}}]},
%% Set log level 'debug' for module dockerwatch - to get
%% some log printouts when sending requests
{module_level,debug,[dockerwatch]}
]}
]}
].
```
The log printout from Logger will now be:
{ "@timestamp": "2018-11-12T15:41:05.531172+00:00", "level": "5", "message": "Hello world" }
And the Logstash log event will be:
```
{
"image_id" => "sha256:63bb61c199d0d649d178cfdbedfc88e6253f24e534f09fd15c3ef79302931ed0",
"command" => "/dockerwatch/bin/dockerwatch console",
"version" => "1.1",
"source_host" => "172.17.0.1",
"container_id" => "a83600195dd0867c5996ea625d7f7c5fc1b87a97043c649a7cb0ed52058d75f1",
"tag" => "a83600195dd0",
"level" => 5,
"image_name" => "erlang-dockerwatch",
"@timestamp" => 2018-11-12T15:41:05.531Z,
"container_name" => "epic_chebyshev",
"message" => "Hello world",
"host" => "elxa19vlx02",
"created" => "2018-11-12T15:12:55.198308117Z",
"@version" => "1"
}
```
So, instead of including all information in the `message` field, the
log event is populated with the actual timestamp, level and message as
specified by the logging client.
NOTE: A currently necessary trick to get the level correct is to
include a `level_int` field in the logger metadata, allowing the level
to be represented as an integer. This is done by the primary logger
filter specified in sys.config.
The docker-erlang-example is modified to issue a log event for each
REST request it receives. Using the curl example lines from the simple
example will therefore trigger a few events which can be seen on
stdout in the logstash container.
Logstash also prints all events to a file (see output plugin file in
logstash.conf). This is done mainly for the Travis build - which
checks the number of lines in this file.

View File

@ -0,0 +1,22 @@
#!/bin/sh
set -e
if [ ! -d ssl ]; then
mkdir ssl
fi
# Create the root CA (Certificate Authority)
openssl genrsa -out ssl/dockerwatch-ca.key 4096
## Certificate signing request for root CA
openssl req -x509 -new -nodes -key ssl/dockerwatch-ca.key -sha256 -days 1024 -subj "/C=SE/" -out ssl/dockerwatch-ca.pem
# Create the server certificate
openssl genrsa -out ssl/dockerwatch-server.key 4096
## Certificate signing request for server certificate
openssl req -new -key ssl/dockerwatch-server.key -subj "/C=SE/CN=localhost/" -out ssl/dockerwatch-server.csr
## Sign the server certificate using the root CA
openssl x509 -req -in ssl/dockerwatch-server.csr -CA ssl/dockerwatch-ca.pem -CAkey ssl/dockerwatch-ca.key -CAcreateserial -out ssl/dockerwatch-server.pem -days 500 -sha256

View File

@ -0,0 +1,22 @@
[{kernel, [{logger,
[%% Set formatter template to print jason
{handler,default,logger_std_h,
#{formatter=>
{logger_formatter,
#{template=>
["{ \"@timestamp\": \"",time,
"\", \"level\": \"",{level_int,[level_int],[level]},
"\", \"message\": \"",msg,"\" }\n"]}}}},
%% Add a primary filter to insert 'level_int' field in metadata
{filters,log,
[{level_int,{fun dockerwatch_filter:add_level_int/2,[]}}]},
%% Set log level 'debug' for module dockerwatch - to get
%% some log printouts when sending requests
{module_level,debug,[dockerwatch]}
]}
%% For debugging
%%,{logger_level,debug}
]}
].

View File

@ -0,0 +1,2 @@
-sname dockerwatch

View File

@ -0,0 +1,17 @@
{deps, [{jsone, "1.4.7"}, %% JSON Encode/Decode
{cowboy, "2.5.0"}]}. %% HTTP Server
{relx, [{release, {"dockerwatch", "1.0.0"}, [dockerwatch]},
{vm_args, "config/vm.args"},
{sys_config, "config/sys.config"},
{dev_mode, true},
{include_erts, false},
{extended_start_script, true}
]}.
{profiles, [{prod, [{relx, [{dev_mode, false},
{include_erts, true},
{include_src, false}]}]}
]}.
%% vim: ft=erlang

View File

@ -0,0 +1,16 @@
%% Feel free to use, reuse and abuse the code in this file.
{application, dockerwatch, [
{description, "Cowboy REST Hello World example."},
{vsn, "1.0.0"},
{modules, []},
{registered, [dockerwatch_sup]},
{applications, [
kernel,
stdlib,
jsone,
cowboy
]},
{mod, {dockerwatch_app, []}},
{env, []}
]}.

View File

@ -0,0 +1,54 @@
%%
%% Copyright (C) 2014 Björn-Egil Dahlberg
%%
%% File: dockerwatch.erl
%% Author: Björn-Egil Dahlberg
%% Created: 2014-09-10
%%
-module(dockerwatch).
-export([start_link/0, all/0, create/1, get/1, increment/2, decrement/2]).
-include_lib("kernel/include/logger.hrl").
-type counter() :: binary().
-spec start_link() -> {ok, pid()}.
start_link() ->
?LOG_DEBUG("~p starting",[?MODULE]),
{ok, spawn_link(fun() -> ets:new(?MODULE, [named_table, public]),
receive after infinity -> ok end end)}.
-spec all() -> [counter()].
all() ->
?LOG_DEBUG("~p all",[?MODULE]),
ets:select(?MODULE, [{{'$1','_'},[],['$1']}]).
-spec create(counter()) -> ok | already_exists.
create(CounterName) ->
case ets:insert_new(?MODULE, {CounterName, 0}) of
true ->
?LOG_DEBUG("Counter ~s created",[CounterName]),
ok;
false ->
?LOG_DEBUG("Counter ~s already exists",[CounterName]),
already_exists
end.
-spec get(counter()) -> integer().
get(CounterName) ->
?LOG_DEBUG("Counter ~s, get",[CounterName]),
ets:lookup_element(?MODULE, CounterName, 2).
-spec increment(counter(), integer()) -> ok.
increment(CounterName, Howmuch) ->
?LOG_DEBUG("Counter ~s, increment ~p",[CounterName,Howmuch]),
_ = ets:update_counter(?MODULE, CounterName, [{2, Howmuch}]),
ok.
-spec decrement(counter(), integer()) -> ok.
decrement(CounterName, Howmuch) ->
?LOG_DEBUG("Counter ~s, decrement ~p",[CounterName,Howmuch]),
_ = ets:update_counter(?MODULE, CounterName, [{2, -1 * Howmuch}]),
ok.

View File

@ -0,0 +1,19 @@
%%
%% Copyright (C) 2014 Björn-Egil Dahlberg
%%
%% File: dockerwatch_app.erl
%% Author: Björn-Egil Dahlberg
%% Created: 2014-09-10
%%
-module(dockerwatch_app).
-behaviour(application).
-export([start/2,stop/1]).
%% API.
start(_Type, _Args) ->
dockerwatch_sup:start_link().
stop(_State) ->
ok.

View File

@ -0,0 +1,9 @@
-module(dockerwatch_filter).
-export([add_level_int/2]).
%% Add a field named level_int to the metadata of each log event. For
%% the formatter to insert in the message string when required by the
%% log target
add_level_int(#{level:=L,meta:=M}=E,_) ->
E#{meta=>M#{level_int=>logger_config:level_to_int(L)}}.

View File

@ -0,0 +1,103 @@
%%
%% Copyright (C) 2014 Björn-Egil Dahlberg
%%
%% File: dockerwatch_handler.erl
%% Author: Björn-Egil Dahlberg
%% Created: 2014-09-10
%%
-module(dockerwatch_handler).
-export([init/2]).
-export([allowed_methods/2]).
-export([content_types_accepted/2]).
-export([content_types_provided/2]).
-export([handle_post/2]).
-export([to_html/2]).
-export([to_json/2]).
-export([to_text/2]).
init(Req, []) ->
{cowboy_rest, Req, []}.
%% Which HTTP methods are allowed
allowed_methods(Req, State) ->
{[<<"GET">>, <<"POST">>], Req, State}.
%% Which content types are accepted by POST/PUT requests
content_types_accepted(Req, State) ->
{[{{<<"application">>, <<"json">>, []}, handle_post}],
Req, State}.
%% Handle the POST/PUT request
handle_post(Req, State) ->
case cowboy_req:binding(counter_name, Req) of
undefined ->
{false, Req, State};
Name ->
case cowboy_req:has_body(Req) of
true ->
{ok, Body, Req3} = cowboy_req:read_body(Req),
Json = jsone:decode(Body),
ActionBin = maps:get(<<"action">>, Json, <<"increment">>),
Value = maps:get(<<"value">>, Json, 1),
Action = list_to_atom(binary_to_list(ActionBin)),
ok = dockerwatch:Action(Name, Value),
{true, Req3, State};
false ->
ok = dockerwatch:create(Name),
{true, Req, State}
end
end.
%% Which content types we handle for GET/HEAD requests
content_types_provided(Req, State) ->
{[{<<"text/html">>, to_html},
{<<"application/json">>, to_json},
{<<"text/plain">>, to_text}
], Req, State}.
%% Return counters/counter as json
to_json(Req, State) ->
Resp = case cowboy_req:binding(counter_name, Req) of
undefined ->
dockerwatch:all();
Counter ->
#{ Counter => dockerwatch:get(Counter) }
end,
{jsone:encode(Resp), Req, State}.
%% Return counters/counter as plain text
to_text(Req, State) ->
Resp = case cowboy_req:binding(counter_name, Req) of
undefined ->
[io_lib:format("~s~n",[Counter]) || Counter <- dockerwatch:all()];
Counter ->
io_lib:format("~p",[dockerwatch:get(Counter)])
end,
{Resp, Req, State}.
%% Return counters/counter as html
to_html(Req, State) ->
Body = case cowboy_req:binding(counter_name, Req) of
undefined ->
Counters = dockerwatch:all(),
["<ul>\n",
[io_lib:format("<li>~s</li>\n", [Counter]) || Counter <- Counters],
"</ul>\n"];
Counter ->
Value = dockerwatch:get(Counter),
io_lib:format("~s = ~p",[Counter, Value])
end,
{[html_head(),Body,html_tail()], Req, State}.
html_head() ->
<<"<html>
<head>
<meta charset=\"utf-8\">
<title>dockerwatch</title>
</head>">>.
html_tail() ->
<<"</body>
</html>">>.

View File

@ -0,0 +1,73 @@
%%
%% Copyright (C) 2014 Björn-Egil Dahlberg
%%
%% File: dockerwatch_sup.erl
%% Author: Björn-Egil Dahlberg
%% Created: 2014-09-10
%%
-module(dockerwatch_sup).
-behaviour(supervisor).
-export([start_link/0,init/1]).
-include_lib("kernel/include/logger.hrl").
%% API.
-spec start_link() -> {ok, pid()}.
start_link() ->
supervisor:start_link({local, ?MODULE}, ?MODULE, []).
%% supervisor.
init([]) ->
CertsDir = "/etc/ssl/certs/",
Dispatch = cowboy_router:compile([
{'_', [{"/[:counter_name]", dockerwatch_handler, []}]}
]),
HTTPS = ranch:child_spec(
cowboy_https, 100, ranch_ssl,
[{port, 8443},
{cacertfile, filename:join(CertsDir, "dockerwatch-ca.pem")},
{certfile, filename:join(CertsDir, "dockerwatch-server.pem")},
{keyfile, filename:join(CertsDir, "dockerwatch-server.key")}],
cowboy_tls,
#{env=>#{dispatch=>Dispatch},
metrics_callback=>log_fun(),
stream_handlers => [cowboy_metrics_h,cowboy_stream_h]}),
HTTP = ranch:child_spec(
cowboy_http, 100, ranch_tcp,
[{port, 8080}],
cowboy_clear,
#{env=>#{dispatch=>Dispatch},
metrics_callback=>log_fun(),
stream_handlers => [cowboy_metrics_h,cowboy_stream_h]}),
Counter = {dockerwatch, {dockerwatch, start_link, []},
permanent, 5000, worker, [dockerwatch]},
Procs = [Counter, HTTP, HTTPS],
{ok, {{one_for_one, 10, 10}, Procs}}.
log_fun() ->
fun(#{resp_status:=RS}=M) when RS>=100, RS<200 ->
do_log(M,"Info");
(#{resp_status:=RS}=M) when RS>=200, RS<300 ->
do_log(M,"OK");
(#{resp_status:=RS}=M) when RS>=300, RS<400 ->
do_log(M,"Redirect");
(#{resp_status:=RS}=M) when RS>=400, RS<500 ->
do_log(M,"Client error");
(#{resp_status:=RS}=M) when RS>=500 ->
do_log(M,"Server error")
end.
do_log(#{req:=#{scheme:=S,method:=M,path:=P},resp_status:=RS},_What) ->
?LOG_DEBUG("scheme=~s, method=~s, path=~s, resp_status=~p",[S,M,P,RS]);
do_log(#{reason:=Reason,resp_status:=RS},_What) ->
?LOG_DEBUG("reason=~p, resp_status=~p",[Reason,RS]).

View File

@ -0,0 +1,9 @@
FROM docker.elastic.co/logstash/logstash:6.4.3
# Replace logstash config files
RUN rm -f /usr/share/logstash/pipeline/logstash.conf
ADD pipeline/ /usr/share/logstash/pipeline/
ADD config/ /usr/share/logstash/config/
EXPOSE 9600
EXPOSE 44622/udp

View File

@ -0,0 +1,2 @@
log.level: info
http.host: "0.0.0.0"

View File

@ -0,0 +1,27 @@
input {
gelf {
use_udp => true
port => 44622
}
}
filter {
# If a log message can be parsed as json, do so, and populate the
# log event with fields found.
json {
skip_on_invalid_json => "true"
source => "message"
}
# Convert the level field to an integer
mutate {
convert => {
"level" => "integer"
}
}
}
output {
stdout {
}
file {
path => "/usr/share/logstash/logs/output.log"
}
}