summaryrefslogtreecommitdiff
path: root/ip/ip.pl
diff options
context:
space:
mode:
Diffstat (limited to 'ip/ip.pl')
-rw-r--r--ip/ip.pl86
1 files changed, 86 insertions, 0 deletions
diff --git a/ip/ip.pl b/ip/ip.pl
new file mode 100644
index 0000000..ba37602
--- /dev/null
+++ b/ip/ip.pl
@@ -0,0 +1,86 @@
+% vim: syntax=prolog
+
+:- use_module(library(clpz)).
+:- use_module(library(format)).
+:- use_module(library(charsio)).
+:- use_module(library(serialization/abnf)).
+
+make_ip4(A, B, C, D, ip4(A, B, C, D, Addr)) :-
+ Addr #= (A * 2^24 + B * 2^16 + C * 2^8 + D).
+
+ip4(A, B, C, D, Addr) :-
+ A in 0..255,
+ B in 0..255,
+ C in 0..255,
+ D in 0..255,
+ Addr #= (A * 2^24 + B * 2^16 + C * 2^8 + D).
+
+ip4_range(ip4(_, _, _, _), Range) :-
+ Range in 0..32.
+
+ip_format(ip4(A, B, C, D, _), Str) :-
+ phrase(format_("~w.~w.~w.~w", [A, B, C, D]), Str).
+
+ip_format(ip4_range(ip4(A, B, C, D, _), Range), Str) :-
+ phrase(format_("~w.~w.~w.~w/~w", [A, B, C, D, Range]), Str).
+
+hexd(D) --> abnf_hexdig(D).
+hexd('a') --> "a".
+hexd('b') --> "b".
+hexd('c') --> "c".
+hexd('d') --> "d".
+hexd('e') --> "e".
+hexd('f') --> "f".
+
+int_(N) --> abnf_digit(D), { number_chars(V, [D]) }, int_(V, N).
+int_(N, N) --> [].
+int_(A, N) --> abnf_digit(D), { number_chars(V, [D]), A1 is A*10+V }, int_(A1, N).
+
+xint_(N) --> hexd(D), { number_chars(V, ['0', 'x', D]) }, xint_(V, N).
+xint_(N, N) --> [].
+xint_(A, N) --> hexd(D), { number_chars(V, ['0', 'x', D]), A1 is A*16+V }, xint_(A1, N).
+
+%ip4_num(V) --> int_(Ds, Ds), { number_chars(V, Ds), V >= 0, V =< 255 }.
+ip4_num(V) --> int_(V), { V >= 0, V =< 255 }.
+
+ip4_syntax(A, B, C, D) --> ip4_num(A), ".", ip4_num(B), ".", ip4_num(C), ".", ip4_num(D).
+ip4_range_syntax(A, B, C, D, R) -->
+ ip4_syntax(A, B, C, D), "/",
+ int_(R), { R >= 0, R =< 32 }.
+
+ip4_parse(Str, Obj) :-
+ phrase(ip4_syntax(A, B, C, D), Str),
+ Obj = ip4(A, B, C, D).
+
+ip4_range_parse(Str, Obj) :-
+ phrase(ip4_range_syntax(A, B, C, D, Range), Str),
+ make_ip4(A, B, C, D, Ip),
+ Obj = ip4_range(Ip, Range).
+
+ip6_syntax(A, B, C, D, E, F, G, H) -->
+ ip6_num(A), ":",
+ ip6_num(B), ":",
+ ip6_num(C), ":",
+ ip6_num(D), ":",
+ ip6_num(E), ":",
+ ip6_num(F), ":",
+ ip6_num(G), ":",
+ ip6_num(H).
+ip6_num(D) --> xint_(D), { D >= 0, D =< 65535 }.
+
+ip6_parse(Str, Obj) :-
+ phrase(ip6_syntax(A, B, C, D, E, F, G, H), Str),
+ Obj = ip6(A, B, C, D, E, F, G, H).
+
+ip_parse(Str, Obj) :-
+ (
+ phrase(ip4_syntax(A, B, C, D), Str)
+ -> Obj = ip4(A, B, C, D)
+ ; (
+ phrase(ip4_range_syntax(A, B, C, D, R), Str)
+ -> make_ip4(A, B, C, D, Ip),
+ Obj = ip4_range(Ip, R)
+ ; phrase(ip6_syntax(A, B, C, D, E, F, G, H), Str),
+ Obj = ip6(A, B, C, D, E, F, G, H)
+ )
+ ).