|
|
|
|
@@ -1,76 +1,61 @@
|
|
|
|
|
-module(rfc5424_parser).
|
|
|
|
|
-compile([pri/1]).
|
|
|
|
|
|
|
|
|
|
% TODO: end facility
|
|
|
|
|
-type facility() :: kernel | user | mail | daemon.
|
|
|
|
|
|
|
|
|
|
% TODO: end severity:
|
|
|
|
|
-type severity() :: error | warning | info | notice | debug.
|
|
|
|
|
|
|
|
|
|
-type priority() :: #{ severity => severity(), facility => facility() }.
|
|
|
|
|
-export([priority/1]).
|
|
|
|
|
-include("rfc5424.hrl").
|
|
|
|
|
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
%%
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
-spec pri(Data) -> Return when
|
|
|
|
|
Data :: bitstring(),
|
|
|
|
|
Return :: {ok, Priority} | {ok, Priority, Rest},
|
|
|
|
|
Priority :: priority(),
|
|
|
|
|
Rest :: bitstring().
|
|
|
|
|
pri(<<"<0",_,">">>) -> {error, bad_value};
|
|
|
|
|
pri(<<"<00",_,">">>) -> {error, bad_value};
|
|
|
|
|
pri(<<"<", I0:8/bitstring, ">">>) ->
|
|
|
|
|
pri_to_map(I0);
|
|
|
|
|
pri(<<"<", I0:8/bitstring, I1:8/bitstring, ">">>) ->
|
|
|
|
|
pri_to_map(<<I0/bitstring, I1/bitstring>>);
|
|
|
|
|
pri(<<"<", I0:8/bitstring, I1:8/bitstring, I2:8/bitstring, ">">>) ->
|
|
|
|
|
pri_to_map(<<I0/bitstring, I1/bitstring, I2/bitstring>>);
|
|
|
|
|
pri(<<"<", I:8/bitstring, ">", Rest/bitstring>>) ->
|
|
|
|
|
case pri(<<"<", I/bitstring, ">">>) of
|
|
|
|
|
{ok, Value} -> {ok, Value, Rest}
|
|
|
|
|
end;
|
|
|
|
|
pri(<<"<", I:16/bitstring, ">", Rest/bitstring>>) ->
|
|
|
|
|
case pri(<<"<", I/bitstring, ">">>) of
|
|
|
|
|
{ok, Value} -> {ok, Value, Rest}
|
|
|
|
|
end;
|
|
|
|
|
pri(<<"<", I:24/bitstring, ">", Rest/bitstring>>) ->
|
|
|
|
|
case pri(<<"<", I/bitstring, ">">>) of
|
|
|
|
|
{ok, Value} -> {ok, Value, Rest}
|
|
|
|
|
end.
|
|
|
|
|
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
%%
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
pri_to_map(Data) ->
|
|
|
|
|
case pri_to_integer(Data) of
|
|
|
|
|
{ok, Value} -> pri_converter(Value);
|
|
|
|
|
priority(<<"<0",_,">", _Rest/bitstring>> = Data) ->
|
|
|
|
|
{error, {priority, bad_value, Data}};
|
|
|
|
|
priority(<<"<00",_,">", _Rest/bitstring>> = Data) ->
|
|
|
|
|
{error, {priority, bad_value, Data}};
|
|
|
|
|
priority(<<"<", I0:8/bitstring, ">", Rest/bitstring>> = _Data) ->
|
|
|
|
|
case priority_converter(I0) of
|
|
|
|
|
{ok, Result} -> {ok, Result, Rest};
|
|
|
|
|
{error, Reason} -> {error, Reason}
|
|
|
|
|
end;
|
|
|
|
|
priority(<<"<", I0:8/bitstring, I1:8/bitstring, ">", Rest/bitstring>> = _Data) ->
|
|
|
|
|
case priority_converter(<<I0/bitstring, I1/bitstring>>) of
|
|
|
|
|
{ok, Result} -> {ok, Result, Rest};
|
|
|
|
|
{error, Reason} -> {error, Reason}
|
|
|
|
|
end;
|
|
|
|
|
priority(<<"<", I0:8/bitstring, I1:8/bitstring, I2:8/bitstring, ">", Rest/bitstring>> = _Data) ->
|
|
|
|
|
case priority_converter(<<I0/bitstring, I1/bitstring, I2/bitstring>>) of
|
|
|
|
|
{ok, Result} -> {ok, Result, Rest};
|
|
|
|
|
{error, Reason} -> {error, Reason}
|
|
|
|
|
end;
|
|
|
|
|
priority(Data) ->
|
|
|
|
|
{error, {priority, bad_value, Data}}.
|
|
|
|
|
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
%%
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
priority_converter(Data) ->
|
|
|
|
|
try
|
|
|
|
|
{ok, Priority} = priority_to_integer(Data),
|
|
|
|
|
Facility = erlang:trunc(Priority/8),
|
|
|
|
|
FacilityAtom = facility(Facility),
|
|
|
|
|
Severity = Priority-(Facility*8),
|
|
|
|
|
SeverityAtom = severity(Severity),
|
|
|
|
|
{ok
|
|
|
|
|
, #{ <<"facility">> => FacilityAtom
|
|
|
|
|
, <<"severity">> => SeverityAtom
|
|
|
|
|
}
|
|
|
|
|
}
|
|
|
|
|
catch
|
|
|
|
|
_:_ -> {error, {priority, Data}}
|
|
|
|
|
end.
|
|
|
|
|
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
%%
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
pri_to_integer(Data) ->
|
|
|
|
|
priority_to_integer(Data) ->
|
|
|
|
|
try erlang:binary_to_integer(Data) of
|
|
|
|
|
Integer -> {ok, Integer}
|
|
|
|
|
catch
|
|
|
|
|
_:Reason -> {error, Reason}
|
|
|
|
|
end.
|
|
|
|
|
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
%%
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
pri_converter(Integer) ->
|
|
|
|
|
try
|
|
|
|
|
Facility = erlang:trunc(Integer/8),
|
|
|
|
|
FacilityAtom = facility(Facility),
|
|
|
|
|
Severity = Integer-(Facility*8),
|
|
|
|
|
SeverityAtom = severity(Severity),
|
|
|
|
|
{ok, #{ facility => FacilityAtom, severity => SeverityAtom }}
|
|
|
|
|
catch
|
|
|
|
|
_:_ -> {error, not_supported}
|
|
|
|
|
end.
|
|
|
|
|
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
%%
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
@@ -110,3 +95,8 @@ severity(4) -> warning;
|
|
|
|
|
severity(5) -> notice;
|
|
|
|
|
severity(6) -> info;
|
|
|
|
|
severity(7) -> debug.
|
|
|
|
|
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
%%
|
|
|
|
|
%%--------------------------------------------------------------------
|
|
|
|
|
version(<<"1", Rest/bitstring>>) -> ok.
|
|
|
|
|
|