summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTrygve Laugstøl <trygvis@inamo.no>2023-11-23 10:49:21 +0100
committerTrygve Laugstøl <trygvis@inamo.no>2023-11-23 10:49:21 +0100
commit2583897e4c5cbe56525365206c2a64bcd0c75e5f (patch)
treea98e8c51917e7690a79c939d16c46c9bf837cfb4
parent3d1c40ea667a25c1dde11a44a9e2e87a8cf51112 (diff)
downloadprolog-firewall-2583897e4c5cbe56525365206c2a64bcd0c75e5f.tar.gz
prolog-firewall-2583897e4c5cbe56525365206c2a64bcd0c75e5f.tar.bz2
prolog-firewall-2583897e4c5cbe56525365206c2a64bcd0c75e5f.tar.xz
prolog-firewall-2583897e4c5cbe56525365206c2a64bcd0c75e5f.zip
wip
-rw-r--r--7/bgp.pl116
-rwxr-xr-x7/bgp.py34
-rw-r--r--7/firewall.pl37
-rw-r--r--7/hosts.pl53
-rw-r--r--7/main.pl26
-rw-r--r--7/utils.pl41
6 files changed, 307 insertions, 0 deletions
diff --git a/7/bgp.pl b/7/bgp.pl
new file mode 100644
index 0000000..d8c7ded
--- /dev/null
+++ b/7/bgp.pl
@@ -0,0 +1,116 @@
+% vim set ft=prolog
+:- module(bgp, [
+ warning/1,
+ create_firewall/0,
+ neighbor/2,
+ bgp_config/2,
+ bird_config/1,
+ remote_network/2,
+ remote_networks/2
+]).
+
+:- use_module(library(assoc)).
+:- use_module(library(format)).
+:- use_module(library(lists)).
+
+:- use_module(hosts, [
+ host/1,
+ host_config/2,
+ router_link/3,
+ attached_network/2]).
+:- use_module(firewall, [
+ fw_rule/2,
+ retract_all_from/1]).
+
+router(R) :- host(R), hosts:host_config(R, _).
+routers(Routers) :- setof(router(R), router(R), Routers).
+
+neighbor(H, R) :-
+ router(H), router(R),
+ router_link(H, R, _),
+ router_link(R, H, _).
+
+warning(Msg) :-
+ host(H), host(R),
+ router_link(H, R, _),
+ \+ router_link(R, H, _),
+ phrase(format_("Missing router_link from '~w' to '~w'", [R, H]), Msg).
+
+neighbors(H, Cs) :- findall(neighbor(H, Name), neighbor(H, Name), Cs).
+
+bgp_config(H, Connections) :- neighbor(H, Connections).
+
+bird_protocol_bgp(Router, Neighbor, Address, AllowedNetworks) :-
+ router_link(Router, Neighbor, _),
+ router_link(Neighbor, Router, Address),
+ AllowedNetworks = [].
+
+% edge(a, b). edge(b, c). edge(c, d). edge(d, a).
+% path(X, Y) :- edge(X, Y).
+% path(X, Y) :- edge(X, Z), path(Z, Y).
+
+attached_networks(Router, Ns) :-
+ findall(N, attached_network(Router, N), Ns).
+
+remote_network(Router, N) :-
+ router_link(Router, Remote, _),
+ attached_network(Remote, N).
+
+remote_networks(Router, Ns) :-
+ router_link(Router, Remote, _),
+ attached_networks(Remote, Ns).
+
+% doesn't recurse
+% available_networks(R, Ns) :-
+% attached_networks(R, Attached),
+% setof(N, remote_network(R, N), Remote),
+% union(Attached, Remote, Xs),
+
+router_path(X, Y) :- router_path(X, Y, []).
+router_path(X, Y, _) :- router_link(X, Y, _).
+router_path(X, Y, V) :- \+ member(X, V), router_link(X, Z, _), router_path(Z, Y, [X|V]).
+
+%to_yaml(neighbor(H, Remote), Dict) :- Dict = yaml(router(H), remote(Remote)).
+%to_json(neighbor(H, Remote), Dict) :- Dict = json(router(H), remote(Remote)).
+
+to_dict(router(R), Dict) :-
+ neighbors(R, Neighbors),
+ maplist(to_dict, Neighbors, NeighborDicts),
+ Dict = {"wat":{
+ "neighbors": NeighborDicts
+ }}
+.
+
+to_dict(neighbor(_, Remote), Dict) :-
+ host_config(Remote, RC),
+ get_assoc("ip", RC, Ip),
+ Dict = {
+ "neighbor":{
+ "name": Remote,
+ "hostname": Ip
+ }
+}.
+
+bird_config(BirdConfig) :-
+ routers(Routers),
+ maplist(to_dict, Routers, RouterDicts),
+ dict_pairs(BirdConfig, bird_config, RouterDicts).
+
+create_firewall :-
+ firewall:retract_all_from(bgp),
+ findall(fw(Host, Attrs), fw(Host, Attrs), Goals),
+ maplist(assert_fw, Goals).
+
+assert_fw(fw(Host, Attrs)) :-
+ put_assoc("from", Attrs, bgp, Attrs2),
+ R = firewall:fw_rule(Host, Attrs2),
+ format("~w", [R]),nl,
+ asserta(R).
+
+fw(Host, Attr) :-
+ hosts:router_link(Host, Remote, _),
+ hosts:host_config(Host, HostConfig),
+ hosts:host_config(Remote, RemoteConfig),
+ get_assoc(ip, RemoteConfig, Src),
+ get_assoc(ip, HostConfig, Dst),
+ utils:to_assoc({src:Src, dst:Dst, family:ip6}, Attr).
diff --git a/7/bgp.py b/7/bgp.py
new file mode 100755
index 0000000..d508762
--- /dev/null
+++ b/7/bgp.py
@@ -0,0 +1,34 @@
+#!/usr/bin/env python3
+
+from swiplserver import PrologMQI, PrologThread
+import yaml
+import os
+
+def to_ansible(kind, hosts):
+ for host, o in hosts.items():
+ print(f"host={host}")
+ os.makedirs(f"host_vars/{host}", exist_ok=True)
+ with open(f"host_vars/{host}/{kind}.yaml", "w") as f:
+ f.write(yaml.dump(o))
+
+with PrologMQI() as mqi:
+ with mqi.create_thread() as p:
+ result = p.query("consult(main), main.")
+ print(result)
+
+ result = p.query("bgp:bird_config(BirdDict)")
+ r = result[0]["BirdDict"]
+ print(yaml.dump(r))
+ to_ansible("bgp", r)
+
+ hosts = {}
+ result = p.query("firewall:fw_rule(Host, Attrs).")
+# print(yaml.dump(result))
+ for r in result:
+ host = r["Host"]
+ if host not in hosts:
+ hosts[host] = h = {}
+ h["firewall_rules"] = rules = []
+ rules.append(r["Attrs"])
+
+ to_ansible("firewall", hosts)
diff --git a/7/firewall.pl b/7/firewall.pl
new file mode 100644
index 0000000..9bb0cc2
--- /dev/null
+++ b/7/firewall.pl
@@ -0,0 +1,37 @@
+% vim set ft=prolog
+
+% rule(src, dst, proto, port, source(..)).
+
+:- module(firewall, [
+ %fw_rule/2,
+ warning/1,
+ retract_all_from/1]).
+
+:- use_module(library(assoc)).
+:- use_module(library(dcgs)).
+
+:- use_module(hosts, [
+ router_link/3]).
+
+:- dynamic(fw_rule/2).
+
+warning(Msg) :-
+ fw_rule(Host, Attr),
+ \+ get_assoc("from", Attr, _),
+ format("Missing 'from' on fw_rule for host '~w', ~w", [Host, Attr], Msg).
+
+rules_from(From, Rules) :-
+ findall(
+ fw_rule(H, Attr),
+ (
+ fw_rule(H, Attr),
+ get_assoc("from", Attr, From)
+ ),
+ Rules).
+
+retract_all_from(From) :-
+ rules_from(From, Rules),
+ retract_rules(Rules).
+
+retract_rules([R|Rules]) :- retract(R), retract_rules(Rules).
+retract_rules([]).
diff --git a/7/hosts.pl b/7/hosts.pl
new file mode 100644
index 0000000..6ec9d97
--- /dev/null
+++ b/7/hosts.pl
@@ -0,0 +1,53 @@
+% vim set ft=prolog
+
+:- module(hosts, [
+ host/1,
+ host_config/2,
+ attached_network/2,
+ router_link/3]).
+
+:- use_module(utils).
+
+host(conflatorio).
+host(hash).
+host(knot).
+host(kv24ix).
+host(lhn2ix).
+
+host_config(knot, Config) :- utils:to_assoc({
+ ip: "fdf3:aad9:a885:0b3a::1"
+ }, Config).
+
+host_config(hash, Config) :- utils:to_assoc({
+ ip: "fdf3:aad9:a885:0b3a::13"
+ }, Config).
+
+host_config(lhn2ix, Config) :- utils:to_assoc({
+ ip: "fdf3:aad9:a885:0b3a::15"
+ }, Config).
+
+host_config(kv24ix, Config) :- utils:to_assoc({
+ ip: "fdf3:aad9:a885:0b3a::16"
+ }, Config).
+
+% (router, remote, router_ip)
+router_link(knot, hash, "0::1").
+router_link(knot, lhn2ix, "0::8").
+router_link(knot, kv24ix, "0::7").
+router_link(hash, knot, "0::2").
+router_link(hash, kv24ix, "0::10").
+router_link(hash, lhn2ix, "0::3").
+router_link(kv24ix, knot, "0::6").
+router_link(kv24ix, hash, "0::5").
+router_link(lhn2ix, hash, "0::9").
+router_link(lhn2ix, knot, "0::4").
+router_link(conflatorio, lhn2ix, "0::11").
+% router_link(lhn2ix, conflatorio,"0::12").
+
+% network(R, address, range)
+attached_network(conflatorio, ipv6_net("1:78e1::", 64)).
+attached_network(hash, ipv6_net("1:e5b0::", 64)).
+attached_network(knot, ipv6_net("1:f11b::", 64)).
+attached_network(lhn2ix, ipv6_net("1:dbe1::", 64)).
+attached_network(lhn2ix, ipv6_net("1:ab69::", 64)).
+attached_network(kv42ix, ipv6_net("1:cd02::", 64)).
diff --git a/7/main.pl b/7/main.pl
new file mode 100644
index 0000000..579f74f
--- /dev/null
+++ b/7/main.pl
@@ -0,0 +1,26 @@
+:- use_module(library(format)).
+:- use_module(library(lists)).
+
+:- use_module(bgp, [
+ create_firewall/0]).
+
+print_warnings([]).
+print_warnings([W|Ws]) :-
+ format("Warning: ~s~n", [W]), print_warnings(Ws).
+
+print_warnings :-
+ findall(W, bgp:warning(W), BgpWs),
+ findall(W, firewall:warning(W), FwWs),
+ append(BgpWs, FwWs, Ws),
+ length(Ws, L),
+ ( L > 0 ->
+ format("Found ~w warning(s):~n", [L]),
+ print_warnings(Ws)
+ ; format("No warnings!~n", [])
+ ).
+
+main :-
+ bgp:create_firewall,
+ print_warnings,
+ bgp:bird_config(BirdDict),
+ yaml_write(current_output, BirdDict).
diff --git a/7/utils.pl b/7/utils.pl
new file mode 100644
index 0000000..ecef72d
--- /dev/null
+++ b/7/utils.pl
@@ -0,0 +1,41 @@
+% vim set ft=prolog
+
+:- module(utils, [
+ to_assoc/2]).
+
+:- use_module(library(assoc)).
+:- use_module(library(lists)).
+
+to_assoc(Obj, Assoc) :-
+ phrase(obj_to_list(Obj), Ls),
+ list_to_assoc(Ls, Assoc).
+
+obj_to_list({}(J)) -->
+ conjunction_to_list(J).
+
+conjunction_to_list((A,B)) --> !,
+ conjunction_to_list(A),
+ conjunction_to_list(B).
+conjunction_to_list(K:V) -->
+ [K-V].
+
+% list_to_obj([L|Ls], {}(In), {}(Out)) :-
+% write('L='),write(L),write(', Ls='),write(Ls),write(', In='),write(In),nl,
+% list_to_obj(Ls, In, Out0),
+% write('Out0='),write(Out0),nl,
+% Out = ','(L, Out0).
+% list_to_obj([], Obj, Obj) :-
+% write('Obj='),write(Obj),nl.
+%
+% obj_kv(Obj, Key, Value) :-
+% phrase(obj_to_list(Obj), Ls),
+% member(Key:Value, Ls).
+%
+% obj_set(Obj, Key, Value, Updated) :-
+% % phrase(obj_to_list(Obj), Ls),
+% % member(Key:Value, Ls),
+% % write('Ls='),write(Ls),nl,
+% % LsU = [Key:Value|Ls],
+% % write('LsU='),write(LsU),nl,
+% % Updated = {LsU}.
+% list_to_obj([Key:Value], Obj, Updated).