{-# OPTIONS_HADDOCK hide #-} module Nettle.Discovery.Topology_Internal where import Nettle.OpenFlow.Switch (SwitchID) import Nettle.OpenFlow.Port hiding (Port) import qualified Data.Set as S -- |Port definition that references a specific port on a specific switch type Port = (SwitchID, PortID) -- |A set of two Ports (as defined above) that represents a connection from -- the PortID of a switch with a certain DataPathID to the PortID of another -- switch with a different DataPathID type Link = S.Set Port -- |Definition of Topology, that is, a set of two-member sets of ports -- It's constructors are not made available in other modules; Topologies -- can only be manipulated by the functions defined in this module. This is -- done so that certain properties can be assumed of any Topology, namely that -- all Links contain two members type Topology = S.Set Link --try newtype Link, type Topology, then you can use set operations on Topologies -- |Deconstructor for Topology constructor unTopology :: Topology -> S.Set Link unTopology topo = topo -- |Merge two topologies merge :: Topology -> Topology -> Topology merge t1 t2 = S.union t1 t2 -- |Provides a Topology with no links empty :: Topology empty = S.empty -- | Construct a link link :: (Port, Port) -> Link link (p1,p2) = S.fromList [p1,p2] -- |Add a link into an existing topology. Use with empty to make a new Topology. addLink :: Port -> Port -> Topology -> Topology addLink p1 p2 = S.insert $ S.insert p1 $ S.insert p2 S.empty -- |Removes all links that include a certain switch's DataPathID -- from the Topology. removeSwitch :: SwitchID -> Topology -> Topology removeSwitch dpid = S.filter $ not . containsDataPathID dpid -- |Given two topologies, merge them into one combine :: Topology -> Topology -> Topology combine t1 t2 = S.union t1 t2 removePort :: Port -> Topology -> Topology removePort pt = S.filter $ not . containsPort pt removeLink :: Link -> Topology -> Topology removeLink lk = removePort $ S.findMin lk -- |Find the subset of Links in a Topology that all -- include a certain switch's DataPathID subset :: SwitchID -> Topology -> Topology subset dpid = S.filter $ containsDataPathID dpid -- Predicate that returns true if the DataPathID provided matches -- the DataPathID in either of the two Ports in the Link. containsDataPathID :: SwitchID -> Link -> Bool containsDataPathID dpid lk = not $ S.null $ S.filter (\ (x, _) -> dpid == x) lk containsPort :: Port -> Link -> Bool containsPort pt lk = S.member pt lk