summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--ip.pl118
-rw-r--r--ip/ip.pl86
-rw-r--r--ip/ip_test.pl120
-rw-r--r--ip/test.pl0
4 files changed, 206 insertions, 118 deletions
diff --git a/ip.pl b/ip.pl
deleted file mode 100644
index d5a6e33..0000000
--- a/ip.pl
+++ /dev/null
@@ -1,118 +0,0 @@
-% vim: syntax=prolog
-
-:- use_module(library(clpfd)).
-:- use_module(library(dcg/basics)).
-
-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) :-
- format(string(Str), "~w.~w.~w.~w", [A, B, C, D]).
-
-ip_format(ip4_range(ip4(A, B, C, D, _), Range), Str) :-
- format(string(Str), "~w.~w.~w.~w/~w", [A, B, C, D, Range]).
-
-ip4_num(D) --> integer(D), { D >= 0, D =< 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), "/", number(R),
- { R >= 0, R =< 32 }.
-
-ip4_parse(Str, Obj) :-
- string_codes(Str, Codes),
- phrase(ip4_syntax(A, B, C, D), Codes),
- Obj = ip4(A, B, C, D).
-
-ip4_range_parse(Str, Obj) :-
- string_codes(Str, Codes),
- phrase(ip4_range_syntax(A, B, C, D, Range), Codes),
- 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) --> xinteger(D), { D >= 0, D =< 65535 }.
-
-ip6_parse(Str, Obj) :-
- string_codes(Str, Codes),
- phrase(ip6_syntax(A, B, C, D, E, F, G, H), Codes),
- Obj = ip6(A, B, C, D, E, F, G, H).
-
-ip_parse(Str, Obj) :-
- string_codes(Str, Codes),
- (
- phrase(ip4_syntax(A, B, C, D), Codes)
- -> Obj = ip4(A, B, C, D)
- ; (
- phrase(ip4_range_syntax(A, B, C, D, R), Codes)
- -> make_ip4(A, B, C, D, Ip),
- Obj = ip4_range(Ip, R)
- ; phrase(ip6_syntax(A, B, C, D, E, F, G, H), Codes),
- Obj = ip6(A, B, C, D, E, F, G, H)
- )
- ).
-
-:- begin_tests(lists).
-:- use_module(library(lists)).
-
-test(ip4) :-
- ip4(127, 0, 0, 1, A),
- assertion(A =:= (127 * 2**24 + 1)).
-
-test(ip_format) :-
- ip_format(ip4(127, 0, 0, 1, _), Str),
- assertion(Str == "127.0.0.1").
-
-test(ip_format) :-
- Ip = ip4_range(ip4(192, 168, 0, 0, _), 24),
- ip_format(Ip, Str),
- assertion(Str == "192.168.0.0/24").
-
-test(ip4_parse) :-
- ip4_parse("1.2.3.4", Ip),
- assertion(Ip == ip4(1, 2, 3, 4)).
-
-test(ip4_range_parse) :-
- ip4_range_parse("1.2.3.4/24", Ip),
- A #= 2^24 + 2 * 2^16 + 3 * 2^8 + 4,
- assertion(Ip == ip4_range(ip4(1, 2, 3, 4, A), 24)).
-
-test(ip6_parse) :-
- ip6_parse("1:2:3:4:5:6:a:b", Ip),
- assertion(Ip == ip6(1, 2, 3, 4, 5, 6, 10, 11)).
-
-test(ip6_parse) :-
- ip6_parse("0:2:3:4:5:6:a:b", Ip),
- assertion(Ip == ip6(0, 2, 3, 4, 5, 6, 10, 11)).
-
-test(ip_parse) :-
- ip_parse("127.0.0.1", Ip),
- assertion(Ip == ip4(127, 0, 0, 1)).
-
-test(ip_parse) :-
- ip_parse("192.168.10.4/24", R),
- make_ip4(192, 168, 10, 4, Ip),
- assertion(R == ip4_range(Ip, 24)).
-
-test(ip_parse) :-
- ip_parse("0:2:3:4:5:6:a:b", Ip),
- assertion(Ip == ip6(0, 2, 3, 4, 5, 6, 10, 11)).
-
-:- end_tests(lists).
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)
+ )
+ ).
diff --git a/ip/ip_test.pl b/ip/ip_test.pl
new file mode 100644
index 0000000..39a0abb
--- /dev/null
+++ b/ip/ip_test.pl
@@ -0,0 +1,120 @@
+% vim: syntax=prolog
+
+:- use_module(library(clpz)).
+:- use_module(library(format)).
+
+test("ip4", (
+ ip4(127, 0, 0, 1, A),
+ A =:= (127 * 2**24 + 1)
+ )).
+
+test("ip_format", (
+ ip_format(ip4(127, 0, 0, 1, _), Str),
+ Str == "127.0.0.1"
+ )).
+
+test("ip_format #2", (
+ Ip = ip4_range(ip4(192, 168, 0, 0, _), 24),
+ ip_format(Ip, Str),
+ Str == "192.168.0.0/24"
+ )).
+
+test("ip4_parse #1", (
+ ip4_parse("1.2.3.4", Ip),
+ Ip == ip4(1, 2, 3, 4)
+ )).
+
+test("ip4_range_parse", (
+ ip4_range_parse("1.2.3.4/24", Ip),
+ A #= 2^24 + 2 * 2^16 + 3 * 2^8 + 4,
+ Ip == ip4_range(ip4(1, 2, 3, 4, A), 24)
+ )).
+
+test("ip6_parse", (
+ ip6_parse("1:2:3:4:5:6:a:b", Ip),
+ Ip == ip6(1, 2, 3, 4, 5, 6, 10, 11)
+ )).
+
+test("ip6_parse #2", (
+ ip6_parse("0:2:3:4:5:6:a:b", Ip),
+ Ip == ip6(0, 2, 3, 4, 5, 6, 10, 11)
+ )).
+
+test("ip_parse #1", (
+ ip_parse("127.0.0.1", Ip),
+ Ip == ip4(127, 0, 0, 1)
+ )).
+
+test("ip_parse #2", (
+ ip_parse("192.168.10.4/24", R),
+ make_ip4(192, 168, 10, 4, Ip),
+ R == ip4_range(Ip, 24)
+ )).
+
+test("ip_parse #3", (
+ ip_parse("0:2:3:4:5:6:a:b", Ip),
+ Ip == ip6(0, 2, 3, 4, 5, 6, 10, 11)
+ )).
+
+main :-
+ consult(ip),
+ findall(test(Name, Goal), test(Name, Goal), Tests),
+ run_tests(Tests, Failed),
+ show_failed(Failed),
+ halt.
+
+main_quiet :-
+ consult(ip),
+ findall(test(Name, Goal), test(Name, Goal), Tests),
+ run_tests_quiet(Tests, Failed),
+ ( Failed = [] ->
+ format("All tests passed", [])
+ ; format("Some tests failed", [])
+ ),
+ halt.
+
+portray_failed_([]) --> [].
+portray_failed_([F|Fs]) -->
+ "\"", F, "\"", "\n", portray_failed_(Fs).
+
+portray_failed([]) --> [].
+portray_failed([F|Fs]) -->
+ "\n", "Failed tests:", "\n", portray_failed_([F|Fs]).
+
+show_failed(Failed) :-
+ phrase(portray_failed(Failed), F),
+ format("~s", [F]).
+
+run_tests([], []).
+run_tests([test(Name, Goal)|Tests], Failed) :-
+ format("Running test \"~s\"~n", [Name]),
+ ( call(Goal) ->
+ Failed = Failed1
+ ; format("Failed test \"~s\"~n", [Name]),
+ Failed = [Name|Failed1]
+ ),
+ run_tests(Tests, Failed1).
+
+run_tests_quiet([], []).
+run_tests_quiet([test(Name, Goal)|Tests], Failed) :-
+ ( call(Goal) ->
+ Failed = Failed1
+ ; Failed = [Name|Failed1]
+ ),
+ run_tests_quiet(Tests, Failed1).
+
+assert_p(A, B) :-
+ phrase(portray_clause_(A), Portrayed),
+ phrase((B, ".\n"), Portrayed).
+
+call_residual_goals(Goal, ResidualGoals) :-
+ call_residue_vars(Goal, Vars),
+ variables_residual_goals(Vars, ResidualGoals).
+
+variables_residual_goals(Vars, Goals) :-
+ phrase(variables_residual_goals(Vars), Goals).
+
+variables_residual_goals([]) --> [].
+variables_residual_goals([Var|Vars]) -->
+ dif:attribute_goals(Var),
+ variables_residual_goals(Vars).
diff --git a/ip/test.pl b/ip/test.pl
new file mode 100644
index 0000000..e69de29
--- /dev/null
+++ b/ip/test.pl