File 3581-Implement-DNS-LOC-record-RFC-1876.patch of Package erlang
From 73810a2c13bd3abd2a7e096ce84ac48d6cbb0b81 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Sat, 4 Mar 2023 12:21:38 +0100
Subject: [PATCH] Implement DNS LOC record (RFC 1876)
The record data Erlang representation is chosen to
be similar to the Master File Format described in RFC section 3,
i.e latitude and longitude in degrees, and altitude, size and precision
in meters; all as floating point values.
Encoding also supports integers with latitude and longitude
in thounsands of an arc second, and alitude, size and precision
in centimeters, as the RDATA format in RFC section 2.
Encoding of size and precision encodes the smallest encoding
value not less than the input value; e.g 100 encodes as 100,
4711 encodes as 5000, and 90001 encodes as 100000.
---
lib/kernel/src/inet_dns.erl | 91 ++++++++++++++++++-
lib/kernel/src/inet_dns.hrl | 6 +-
lib/kernel/test/inet_res_SUITE.erl | 5 +-
.../inet_res_SUITE_data/otptest/otptest.zone | 3 +
4 files changed, 102 insertions(+), 3 deletions(-)
diff --git a/lib/kernel/src/inet_dns.erl b/lib/kernel/src/inet_dns.erl
index c236dfd0d6..7867c55501 100644
--- a/lib/kernel/src/inet_dns.erl
+++ b/lib/kernel/src/inet_dns.erl
@@ -49,6 +49,7 @@
make_dns_query/2, make_dns_query/3]).
-include("inet_dns_record_adts.hrl").
+
%% Function merge of #dns_rr{} and #dns_rr_opt{}
%%
@@ -112,6 +113,10 @@ lists_member(H, [H|_]) -> true;
lists_member(H, [_|T]) -> lists_member(H, T).
+-define(in_range(Low, X, High), ((Low =< (X)) andalso ((X) =< High))).
+-define(is_decimal(X), (?in_range(0, (X), 9))).
+
+
%% must match a clause in inet_res:query_nss_e?dns
-define(DECODE_ERROR, formerr).
@@ -360,6 +365,7 @@ decode_type(Type) ->
?T_MX -> ?S_MX;
?T_TXT -> ?S_TXT;
?T_AAAA -> ?S_AAAA;
+ ?T_LOC -> ?S_LOC;
?T_SRV -> ?S_SRV;
?T_NAPTR -> ?S_NAPTR;
?T_OPT -> ?S_OPT;
@@ -401,6 +407,7 @@ encode_type(Type) ->
?S_MX -> ?T_MX;
?S_TXT -> ?T_TXT;
?S_AAAA -> ?T_AAAA;
+ ?S_LOC -> ?T_LOC;
?S_SRV -> ?T_SRV;
?S_NAPTR -> ?T_NAPTR;
?S_OPT -> ?T_OPT;
@@ -539,6 +546,21 @@ decode_data(Data, ?S_MX, Buffer) ->
Data,
<<Prio:16,Dom/binary>>,
{Prio,decode_domain(Dom, Buffer)});
+decode_data(Data, ?S_LOC, _) ->
+ ?MATCH_ELSE_DECODE_ERROR(
+ Data,
+ <<Version:8, SizeBase:4, SizeExp:4,
+ HorizPreBase:4, HorizPreExp:4, VertPreBase:4, VertPreExp:4,
+ Latitude:32, Longitude:32, Altitude:32>>,
+ ((Version =:= 0) andalso
+ ?is_decimal(SizeBase) andalso ?is_decimal(SizeExp) andalso
+ ?is_decimal(HorizPreBase) andalso ?is_decimal(HorizPreExp) andalso
+ ?is_decimal(VertPreBase) andalso ?is_decimal(VertPreExp)),
+ {{decode_loc_angle(Latitude), decode_loc_angle(Longitude)},
+ decode_loc_altitude(Altitude),
+ decode_loc_size(SizeBase, SizeExp),
+ {decode_loc_size(HorizPreBase, HorizPreExp),
+ decode_loc_size(VertPreBase, VertPreExp)}});
decode_data(Data, ?S_SRV, Buffer) ->
?MATCH_ELSE_DECODE_ERROR(
Data,
@@ -735,6 +757,25 @@ encode_data(Comp, Pos, ?S_MINFO, Data) ->
encode_data(Comp, Pos, ?S_MX, Data) ->
{Pref,Exch} = Data,
encode_name(<<Pref:16>>, Comp, Pos+2, Exch);
+encode_data(Comp, _, ?S_LOC, Data) ->
+ %% Similar to the Master File Format in section 3 of RFC 1876
+ case Data of
+ {{Latitude, Longitude}, Altitude, Size, {HorizPre, VertPre}} ->
+ ok;
+ {{Latitude, Longitude}, Altitude, Size} ->
+ HorizPre = 10_000_00, VertPre = 10_00,
+ ok;
+ {{Latitude, Longitude}, Altitude} ->
+ Size = 1_00, HorizPre = 10_000_00, VertPre = 10_00,
+ ok
+ end,
+ Version = 0,
+ {<<Version:8, (encode_loc_size(Size))/binary,
+ (encode_loc_size(HorizPre))/binary, (encode_loc_size(VertPre))/binary,
+ (encode_loc_angle(Latitude)):32,
+ (encode_loc_angle(Longitude)):32,
+ (encode_loc_altitude(Altitude)):32>>,
+ Comp};
encode_data(Comp, Pos, ?S_SRV, Data) ->
{Prio,Weight,Port,Target} = Data,
encode_name(<<Prio:16,Weight:16,Port:16>>, Comp, Pos+(2+2+2), Target);
@@ -854,3 +895,51 @@ encode_labels(Bin, Comp0, Pos, [L|Ls]=Labels)
%% Name compression - point to already encoded name
{<<Bin/binary,3:2,Ptr:14>>,Comp0}
end.
+
+
+decode_loc_angle(X) ->
+ (X - 16#8000_0000) / 3600_000.
+
+encode_loc_angle(X) when is_float(X) ->
+ %% Degrees (1/360 of a turn)
+ encode_loc_angle(round(X * 3600_000));
+encode_loc_angle(X)
+ when is_integer(X), -16#8000_0000 =< X, X =< 16#7FFF_FFFF ->
+ %% 1/1000:s of arc second
+ X + 16#8000_0000. % Zero is encoded as 2^31
+
+
+decode_loc_altitude(X) ->
+ (X - 100_000_00) / 100.
+
+encode_loc_altitude(X) when is_float(X) ->
+ %% Meters
+ encode_loc_altitude(round(X * 100));
+encode_loc_altitude(X)
+ when is_integer(X), -100_000_00 =< X, X =< 16#FFFF_FFFF - 100_000_00 ->
+ %% Centimeters above a base level 100_000 m below
+ %% the GPS reference spheroid [DoD WGS-1984]
+ X + 100_000_00.
+
+
+decode_loc_size(Base, Exponent) ->
+ round(Base * math:pow(10, Exponent)) / 100.
+
+%% Return the smallest encoded value >= X;
+%% a bit like ceil(X) of encoded values
+%%
+encode_loc_size(X) when is_float(X) ->
+ %% Meters
+ encode_loc_size(round(X * 100));
+encode_loc_size(0) ->
+ 0;
+encode_loc_size(X)
+ when is_integer(X), 0 =< X, X =< 9000_000_000 ->
+ %% Centimeters, to be encoded as Digit * 10^Exponent
+ %% with both Digit and Exponent in 0..9,
+ %% limiting the range to 0..9e9
+ %%
+ Exponent = floor(math:log10((X - 0.05) / 0.9)),
+ Multiplier = round(math:pow(10, Exponent)),
+ Base = (X + Multiplier - 1) div Multiplier,
+ <<Base:4, Exponent:4>>.
diff --git a/lib/kernel/src/inet_dns.hrl b/lib/kernel/src/inet_dns.hrl
index 5288c570b2..52b38b9ad1 100644
--- a/lib/kernel/src/inet_dns.hrl
+++ b/lib/kernel/src/inet_dns.hrl
@@ -72,6 +72,8 @@
-define(T_MX, 15). %% mail routing information
-define(T_TXT, 16). %% text strings
-define(T_AAAA, 28). %% ipv6 address
+%% LOC (RFC 1876)
+-define(T_LOC, 29). %% location information
%% SRV (RFC 2052)
-define(T_SRV, 33). %% services
%% NAPTR (RFC 2915)
@@ -114,6 +116,8 @@
-define(S_MX, mx). %% mail routing information
-define(S_TXT, txt). %% text strings
-define(S_AAAA, aaaa). %% ipv6 address
+%% LOC (RFC 1876)
+-define(S_LOC, loc). %% location information
%% SRV (RFC 2052)
-define(S_SRV, srv). %% services
%% NAPTR (RFC 2915)
diff --git a/lib/kernel/test/inet_res_SUITE.erl b/lib/kernel/test/inet_res_SUITE.erl
index 5adce7156e..ac147551f2 100644
--- a/lib/kernel/test/inet_res_SUITE.erl
+++ b/lib/kernel/test/inet_res_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2009-2022. All Rights Reserved.
+%% Copyright Ericsson AB 2009-2023. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -886,6 +886,9 @@ resolve(Config) when is_list(Config) ->
{ptr,"c.1.0.0.0.0.f.7."++RDomain6,[{ptr,Name}],undefined},
{hinfo,Name,[{hinfo,{"BEAM","Erlang/OTP"}}],undefined},
{mx,RDomain4,[{mx,{10,"mx."++Domain}}],undefined},
+ {loc,"loc."++Name,
+ [{loc,{{42.0625,13.125},17.0,100.0,{10000.0,10.0}}}],
+ undefined},
{srv,"_srv._tcp."++Name,[{srv,{10,3,4711,Name}}],undefined},
{naptr,"naptr."++Name,
[{naptr,{10,5,"s","http","","_srv._tcp."++Name}}],
diff --git a/lib/kernel/test/inet_res_SUITE_data/otptest/otptest.zone b/lib/kernel/test/inet_res_SUITE_data/otptest/otptest.zone
index 9e4a3513f8..98b195fd97 100644
--- a/lib/kernel/test/inet_res_SUITE_data/otptest/otptest.zone
+++ b/lib/kernel/test/inet_res_SUITE_data/otptest/otptest.zone
@@ -42,6 +42,9 @@ wks.resolve IN WKS 127.0.0.28 TCP ( telnet smtp )
resolve IN HINFO "BEAM" "Erlang/OTP"
ns.resolve IN NS resolve
mx.resolve IN MX 10 resolve
+;; The LOC latitude and longitude is chosen to have an exact
+;; decimal degrees floating point representation
+loc.resolve IN LOC 42 3 45 N 13 7 30 E 17m 100m 10000m 10m
_srv._tcp.resolve IN SRV 10 3 4711 resolve
naptr.resolve IN NAPTR 10 5 "S" "HTTP" "" _srv._tcp.resolve
txt.resolve IN TXT "Hej " "du " "glade "
--
2.35.3