netcore-1.0.0: The NetCore compiler and runtime system for OpenFlow networks.

Safe HaskellSafe-Infered

Frenetic.NetCore

Contents

Description

Everything necessary to build a controller atop NetCore, using Nettle as a backend.

Synopsis

OpenFlow Controllers

controller :: Policy -> IO ()Source

Starts an OpenFlow controller that runs a static NetCore program.

dynControllerSource

Arguments

:: Chan Policy 
-> Chan (Loc, ByteString)

packets to emit

-> IO () 

Starts an OpenFlow controller that runs dynamic NetCore programs.

The controller reads NetCore programs from the given channel. When the controller receives a program on the channel, it compiles it and reconfigures the network to run it.

Policies

data Policy Source

Policies denote functions from (switch, packet) to packets.

Constructors

PoBottom

Performs no actions.

PoBasic Predicate Action

Performs the given action on packets matching the given predicate.

PoUnion Policy Policy

Performs the actions of both P1 and P2.

(==>) :: Predicate -> Action -> PolicySource

Abbreviation for constructing a basic policy from a predicate and an action.

(<%>) :: Policy -> Predicate -> PolicySource

Restrict a policy to act over packets matching the predicate.

(<+>) :: Monoid a => a -> a -> aSource

Join: overloaded to find the union of policies and the join of actions.

Predicates

data Predicate Source

Predicates to match packets.

exactMatch :: Packet -> PredicateSource

A predicate that exactly matches a packet's headers.

inport :: Switch -> Port -> PredicateSource

Construct the predicate matching packets on this switch and port

(<||>) :: Predicate -> Predicate -> PredicateSource

Abbreviation for predicate union.

(<&&>) :: Predicate -> Predicate -> PredicateSource

Abbreviation for predicate intersection.

matchAll :: PredicateSource

Matches all packets.

matchNone :: PredicateSource

Matches no packets.

neg :: Predicate -> PredicateSource

Abbreviation for predicate negation.

prSubtract :: Predicate -> Predicate -> PredicateSource

Construct the set difference between p1 and p2

prOr :: [Predicate] -> PredicateSource

Construct nary union of a list of predicates

prAnd :: [Predicate] -> PredicateSource

Construct nary intersection of a list of predicates

Exact match predicate constructors

onSwitch :: Switch -> PredicateSource

Match switch identifier.

dlSrc :: Word48 -> PredicateSource

Match ethernet source address.

dlDst :: Word48 -> PredicateSource

Match ethernet destination address.

dlTyp :: Word16 -> PredicateSource

Match ethernet type code (e.g., 0x0800 for IP packets).

dlVlan :: Word16 -> PredicateSource

Match VLAN tag.

dlNoVlan :: PredicateSource

Match Vlan untagged

dlVlanPcp :: Word8 -> PredicateSource

Match VLAN priority

nwSrc :: Word32 -> PredicateSource

Match source IP address.

This is only meaningful in combination with 'dlTyp 0x0800'.

nwDst :: Word32 -> PredicateSource

Match destination IP address.

nwSrcPrefix :: Word32 -> Int -> PredicateSource

Match a prefix of the source IP address.

nwDstPrefix :: Word32 -> Int -> PredicateSource

Match a prefix of the destination IP address.

nwProto :: Word8 -> PredicateSource

Match IP protocol code (e.g., 0x6 indicates TCP segments).

nwTos :: Word8 -> PredicateSource

Match IP TOS field.

tpSrc :: Word16 -> PredicateSource

Match IP source port.

tpDst :: Word16 -> PredicateSource

Match IP destination port.

inPort :: Port -> PredicateSource

Match the ingress port on which packets arrive.

Actions

data Action Source

Actions to perform on packets.

Constructors

forward :: [Port] -> ActionSource

Forward the packet out of the specified physical ports.

allPortsSource

Arguments

:: Modification

modifications to apply to the packet. Use 'allPorts unmodified' to make no modifications.

-> Action 

Forward the packet out of all physical ports, except the packet's ingress port.

modify :: [(Port, Modification)] -> ActionSource

Forward the packet out of the specified physical ports with modifications.

Each port has its own record of modifications, so modifications at one port do not interfere with modifications at another port.

countBytesSource

Arguments

:: Int

polling interval, in milliseconds

-> IO (Chan (Switch, Integer), Action) 

Sends packets to the controller.

Returns an Action and a channel. When the Action is used in the active Policy, all matching packets are sent to the controller. These packets are written into the channel.

countPktsSource

Arguments

:: Int

polling interval, in milliseconds

-> IO (Chan (Switch, Integer), Action) 

Periodically polls the network to counts the number of bytes received.

Returns an Action and a channel. When the Action is used in the active Policy, the controller periodically reads the packet counters on the network. The controller returns the number of matching packets on each switch.

Modifications

data Modification Source

For each fields with a value Just v, modify that field to be v. If the field is Nothing then there is no modification of that field.

Network Elements

type Switch = Word64Source

A switch's unique identifier.

type Port = Word16Source

The number of a physical port.

type Vlan = Word16Source

VLAN tags. Only the lower 12-bits are used.

data Loc Source

Loc uniquely identifies a port at a switch.

Constructors

Loc Switch Port 

Instances

type Word48 = EthernetAddressSource

Ethernet addresses are 48-bits wide.

Packets

data Packet Source

Packets' headers.

Constructors

Packet 

Fields

pktDlSrc :: Word48

source ethernet address

pktDlDst :: Word48

destination ethernet address

pktDlTyp :: Word16

ethernet type code (e.g., 0x800 for IP packets)

pktDlVlan :: Maybe Vlan

VLAN tag

pktDlVlanPcp :: Word8

VLAN priority code

pktNwSrc :: Maybe Word32

source IP address for IP packets

pktNwDst :: Maybe Word32

destination IP address for IP packets

pktNwProto :: Word8

IP protocol number (e.g., 6 for TCP segments)

pktNwTos :: Word8

IP TOS field

pktTpSrc :: Maybe Word16

source port for IP packets

pktTpDst :: Maybe Word16

destination port for IP packets

pktInPort :: Port

ingress port on the switch where the packet was received

Instances

Packet modifications

Channels

select :: Chan a -> Chan b -> IO (Chan (Either a b))Source

Produce a new channel that carries updates from both of the input channels, but does not wait for both to be ready. Analogous to Unix SELECT(2) followed by READ(2) on the ready file descriptor.

both :: Chan a -> Chan b -> IO (Chan (a, b))Source

Produce a new channel that waits for both input channels to produce a value, and then yields the latest version of both values. If one channel produces multiple values before the other produces any, then the early values are discarded. Afterwards, whenever one channel updates, the output channel yields that update along with whatever the current version of the other channel is.

Slices

data Slice Source

A slice represents a subgraph of the network for the purposes of isolating programs from each other.

The interface to a slice has two components: a topology comprising switches, ports, and links; and a collection of predicates, one for each outward-facing edge port.

We represent the topology as a collection of locations in the network, and the predicates as a mapping from locations to predicates.

Intuitively, packets may travel freely between internal locations, but must satisfy the associated predicate to enter the slice at an ingress location, or leave the slice at an egress location. If an external port is not listed in the ingress or egress set, then no packets may enter or leave (respectively) on that port.

Constructors

Slice 

Fields

internal :: Set Loc

Ports internal to the slice.

ingress :: Map Loc Predicate

External ports, and restrictions on inbound packets.

egress :: Map Loc Predicate

External ports, and restrictions on outbound packets.

Instances

Topology constructors

buildGraph :: [((Node, Port), (Node, Port))] -> TopoSource

Build a graph from list of undirected edges labeled with their ports Ensures that the resulting graph is undirected-equivalent, and labels each directed edge with the appropriate port to send a packet over that edge from the source switch.

By convention, hosts have a single port 0, and non-hosts have any number of non-zero ports. If 0 is in the ports of a node, it is considered to be a host regardless of other ports that may be present.

Slice constructors

internalSlice :: Topo -> SliceSource

Produce a slice that exactly covers the given topology, with no ingress or egress ports.

simpleSlice :: Topo -> Predicate -> SliceSource

Produce a slice with all the switches in topo, and predicate applied to all in- and out-bound connections to hosts

Compilation

transform :: [(Slice, Policy)] -> PolicySource

Produce the combined policy by compiling a list of slices and policies with the vanilla compiler

transformEdge :: Topo -> [(Slice, Policy)] -> PolicySource

Produce the combined policy by compiling a list of slices and policies with the edge compiler

dynTransform :: [(Slice, Chan Policy)] -> IO (Chan Policy)Source

Compile a list of slices and dynamic policies as they change.