summaryrefslogtreecommitdiff
path: root/7/bgp.pl
diff options
context:
space:
mode:
Diffstat (limited to '7/bgp.pl')
-rw-r--r--7/bgp.pl116
1 files changed, 116 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).