You've already forked docker-erlang-example
mirror of
https://github.com/erlang/docker-erlang-example.git
synced 2025-08-01 10:06:50 +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:
22
advanced_examples/logstash/dockerwatch/config/sys.config
Normal file
22
advanced_examples/logstash/dockerwatch/config/sys.config
Normal 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}
|
||||
]}
|
||||
].
|
2
advanced_examples/logstash/dockerwatch/config/vm.args
Normal file
2
advanced_examples/logstash/dockerwatch/config/vm.args
Normal file
@ -0,0 +1,2 @@
|
||||
-sname dockerwatch
|
||||
|
17
advanced_examples/logstash/dockerwatch/rebar.config
Normal file
17
advanced_examples/logstash/dockerwatch/rebar.config
Normal 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
|
@ -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, []}
|
||||
]}.
|
54
advanced_examples/logstash/dockerwatch/src/dockerwatch.erl
Normal file
54
advanced_examples/logstash/dockerwatch/src/dockerwatch.erl
Normal 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.
|
@ -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.
|
@ -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)}}.
|
@ -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>">>.
|
@ -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]).
|
Reference in New Issue
Block a user