summaryrefslogtreecommitdiff
path: root/ip/ip.pl
diff options
context:
space:
mode:
Diffstat (limited to 'ip/ip.pl')
-rw-r--r--ip/ip.pl65
1 files changed, 45 insertions, 20 deletions
diff --git a/ip/ip.pl b/ip/ip.pl
index ba37602..259ecf9 100644
--- a/ip/ip.pl
+++ b/ip/ip.pl
@@ -5,23 +5,28 @@
:- 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).
+big(A, B, C) :- C #= A^B.
-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).
+make_ip4(A, B, C, D, Addr) :-
+ A #>= 0, A #=< 255,
+ B #>= 0, B #=< 255,
+ C #>= 0, C #=< 255,
+ D #>= 0, D #=< 255,
+ Addr #= ((A * 2^24) + (B * 2^16) + (C * 2^8) + D),
+ ip4(Addr).
-ip4_range(ip4(_, _, _, _), Range) :-
+ip4(Addr) :- Addr >= 0, Addr < 2^32.
+
+ip4_range(Addr, Range) :-
+ ip4(Addr),
Range in 0..32.
-ip_format(ip4(A, B, C, D, _), Str) :-
+ip_format(ip4(Addr), Str) :-
+ make_ip4(A, B, C, D, Addr),
phrase(format_("~w.~w.~w.~w", [A, B, C, D]), Str).
-ip_format(ip4_range(ip4(A, B, C, D, _), Range), Str) :-
+ip_format(ip4_range(Addr, Range), Str) :-
+ make_ip4(A, B, C, D, Addr),
phrase(format_("~w.~w.~w.~w/~w", [A, B, C, D, Range]), Str).
hexd(D) --> abnf_hexdig(D).
@@ -48,14 +53,31 @@ ip4_range_syntax(A, B, C, D, R) -->
ip4_syntax(A, B, C, D), "/",
int_(R), { R >= 0, R =< 32 }.
-ip4_parse(Str, Obj) :-
+ip4_parse(Str, Ip) :-
phrase(ip4_syntax(A, B, C, D), Str),
- Obj = ip4(A, B, C, D).
+ make_ip4(A, B, C, D, Addr),
+ Ip = ip4(Addr).
-ip4_range_parse(Str, Obj) :-
+ip4_range_parse(Str, IpR) :-
phrase(ip4_range_syntax(A, B, C, D, Range), Str),
- make_ip4(A, B, C, D, Ip),
- Obj = ip4_range(Ip, Range).
+ make_ip4(A, B, C, D, Addr),
+ IpR = ip4_range(Addr, Range).
+
+make_ip6(A, B, C, D, E, F, G, H, Addr) :-
+ A #>= 0, A #=< 65335,
+ B #>= 0, B #=< 65335,
+ C #>= 0, C #=< 65335,
+ D #>= 0, D #=< 65335,
+ E #>= 0, E #=< 65335,
+ F #>= 0, F #=< 65335,
+ G #>= 0, G #=< 65335,
+ H #>= 0, H #=< 65335,
+ Addr #=
+ (A * 2^56) + (B * 2^48) + (C * 2^40) + (D * 2^32) +
+ (E * 2^24) + (F * 2^16) + (G * 2^8) + H,
+ ip6(Addr).
+
+ip6(Addr) :- Addr >= 0, Addr < 2^128.
ip6_syntax(A, B, C, D, E, F, G, H) -->
ip6_num(A), ":",
@@ -68,19 +90,22 @@ ip6_syntax(A, B, C, D, E, F, G, H) -->
ip6_num(H).
ip6_num(D) --> xint_(D), { D >= 0, D =< 65535 }.
-ip6_parse(Str, Obj) :-
+ip6_parse(Str, Ip) :-
phrase(ip6_syntax(A, B, C, D, E, F, G, H), Str),
- Obj = ip6(A, B, C, D, E, F, G, H).
+ make_ip6(A, B, C, D, E, F, G, H, Addr),
+ Ip = ip6(Addr).
ip_parse(Str, Obj) :-
(
phrase(ip4_syntax(A, B, C, D), Str)
- -> Obj = ip4(A, B, C, D)
+ -> make_ip4(A, B, C, D, Addr),
+ Obj = ip4(Addr)
; (
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)
+ make_ip6(A, B, C, D, E, F, G, H, Addr),
+ Obj = ip6(Addr)
)
).