iproute-1.7.11: IP Routing Table
Safe HaskellNone
LanguageHaskell2010

Data.IP.RouteTable.Internal

Description

IP routing table is a tree of AddrRange to search one of them on the longest match base. It is a kind of TRIE with one way branching removed. Both IPv4 and IPv6 are supported.

Synopsis

Documentation

class Addr a => Routable a where Source #

A class to contain IPv4 and IPv6.

Methods

intToTBit :: Int -> a Source #

The intToTBit function takes Int and returns an Routable address whose only n-th bit is set.

isZero :: a -> a -> Bool Source #

The isZero function takes an Routable address and an test bit Routable address and returns True is the bit is unset, otherwise returns False.

Instances

Instances details
Routable IPv6 Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Routable IPv4 Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

data IPRTable k a Source #

The Tree structure for IP routing table based on TRIE with one way branching removed. This is an abstract data type, so you cannot touch its inside. Please use insert or lookup, instead.

Constructors

Nil 
Node !(AddrRange k) !k !(Maybe a) !(IPRTable k a) !(IPRTable k a) 

Instances

Instances details
Functor (IPRTable k) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Methods

fmap :: (a -> b) -> IPRTable k a -> IPRTable k b #

(<$) :: a -> IPRTable k b -> IPRTable k a #

Foldable (IPRTable k) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Methods

fold :: Monoid m => IPRTable k m -> m #

foldMap :: Monoid m => (a -> m) -> IPRTable k a -> m #

foldMap' :: Monoid m => (a -> m) -> IPRTable k a -> m #

foldr :: (a -> b -> b) -> b -> IPRTable k a -> b #

foldr' :: (a -> b -> b) -> b -> IPRTable k a -> b #

foldl :: (b -> a -> b) -> b -> IPRTable k a -> b #

foldl' :: (b -> a -> b) -> b -> IPRTable k a -> b #

foldr1 :: (a -> a -> a) -> IPRTable k a -> a #

foldl1 :: (a -> a -> a) -> IPRTable k a -> a #

toList :: IPRTable k a -> [a] #

null :: IPRTable k a -> Bool #

length :: IPRTable k a -> Int #

elem :: Eq a => a -> IPRTable k a -> Bool #

maximum :: Ord a => IPRTable k a -> a #

minimum :: Ord a => IPRTable k a -> a #

sum :: Num a => IPRTable k a -> a #

product :: Num a => IPRTable k a -> a #

Traversable (IPRTable k) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Methods

traverse :: Applicative f => (a -> f b) -> IPRTable k a -> f (IPRTable k b) #

sequenceA :: Applicative f => IPRTable k (f a) -> f (IPRTable k a) #

mapM :: Monad m => (a -> m b) -> IPRTable k a -> m (IPRTable k b) #

sequence :: Monad m => IPRTable k (m a) -> m (IPRTable k a) #

Generic1 (IPRTable k :: Type -> Type) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Associated Types

type Rep1 (IPRTable k) :: k -> Type #

Methods

from1 :: forall (a :: k0). IPRTable k a -> Rep1 (IPRTable k) a #

to1 :: forall (a :: k0). Rep1 (IPRTable k) a -> IPRTable k a #

(Eq k, Eq a) => Eq (IPRTable k a) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Methods

(==) :: IPRTable k a -> IPRTable k a -> Bool #

(/=) :: IPRTable k a -> IPRTable k a -> Bool #

(Show k, Show a) => Show (IPRTable k a) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Methods

showsPrec :: Int -> IPRTable k a -> ShowS #

show :: IPRTable k a -> String #

showList :: [IPRTable k a] -> ShowS #

Generic (IPRTable k a) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Associated Types

type Rep (IPRTable k a) :: Type -> Type #

Methods

from :: IPRTable k a -> Rep (IPRTable k a) x #

to :: Rep (IPRTable k a) x -> IPRTable k a #

Routable k => Semigroup (IPRTable k a) Source #

Note that Semigroup and Monoid instances are right-biased. That is, if both arguments have the same key, the value from the right argument will be used. Since: 1.7.5

Instance details

Defined in Data.IP.RouteTable.Internal

Methods

(<>) :: IPRTable k a -> IPRTable k a -> IPRTable k a #

sconcat :: NonEmpty (IPRTable k a) -> IPRTable k a #

stimes :: Integral b => b -> IPRTable k a -> IPRTable k a #

Routable k => Monoid (IPRTable k a) Source #

Since: 1.7.5

Instance details

Defined in Data.IP.RouteTable.Internal

Methods

mempty :: IPRTable k a #

mappend :: IPRTable k a -> IPRTable k a -> IPRTable k a #

mconcat :: [IPRTable k a] -> IPRTable k a #

type Rep1 (IPRTable k :: Type -> Type) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

type Rep (IPRTable k a) Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

empty :: Routable k => IPRTable k a Source #

The empty function returns an empty IP routing table.

>>> (empty :: IPRTable IPv4 ()) == fromList []
True

insert :: Routable k => AddrRange k -> a -> IPRTable k a -> IPRTable k a Source #

The insert function inserts a value with a key of AddrRange to IPRTable and returns a new IPRTable.

>>> (insert ("127.0.0.1" :: AddrRange IPv4) () empty) == fromList [("127.0.0.1",())]
True

link :: Routable k => IPRTable k a -> IPRTable k a -> IPRTable k a Source #

isLeft :: Routable k => AddrRange k -> k -> Bool Source #

delete :: Routable k => AddrRange k -> IPRTable k a -> IPRTable k a Source #

The delete function deletes a value by a key of AddrRange from IPRTable and returns a new IPRTable.

>>> delete "127.0.0.1" (insert "127.0.0.1" () empty) == (empty :: IPRTable IPv4 ())
True

node :: Routable k => AddrRange k -> k -> Maybe a -> IPRTable k a -> IPRTable k a -> IPRTable k a Source #

lookup :: Routable k => AddrRange k -> IPRTable k a -> Maybe a Source #

The lookup function looks up IPRTable with a key of AddrRange. If a routing information in IPRTable matches the key, its value is returned.

>>> let v4 = ["133.4.0.0/16","133.5.0.0/16","133.5.16.0/24","133.5.23.0/24"] :: [AddrRange IPv4]
>>> let rt = fromList $ zip v4 v4
>>> lookup "127.0.0.1" rt
Nothing
>>> lookup "133.3.0.1" rt
Nothing
>>> lookup "133.4.0.0" rt
Just 133.4.0.0/16
>>> lookup "133.4.0.1" rt
Just 133.4.0.0/16
>>> lookup "133.5.16.0" rt
Just 133.5.16.0/24
>>> lookup "133.5.16.1" rt
Just 133.5.16.0/24

lookupKeyValue :: Routable k => AddrRange k -> IPRTable k a -> Maybe (AddrRange k, a) Source #

The lookupKeyValue function looks up IPRTable with a key of AddrRange. If a routing information in IPRTable matches the key, both key and value are returned.

>>> :set -XOverloadedStrings
>>> let rt = fromList ([("192.168.0.0/24", 1), ("10.10.0.0/16", 2)] :: [(AddrRange IPv4, Int)])
>>> lookupKeyValue "127.0.0.1" rt
Nothing
>>> lookupKeyValue "192.168.0.1" rt
Just (192.168.0.0/24,1)
>>> lookupKeyValue "10.10.0.1" rt
Just (10.10.0.0/16,2)

search :: Routable k => AddrRange k -> IPRTable k a -> Maybe (AddrRange k, a) -> Maybe (AddrRange k, a) Source #

lookupAll :: Routable k => AddrRange k -> IPRTable k a -> [(AddrRange k, a)] Source #

lookupAll is a version of lookup that returns all entries matching the given key, not just the longest match.

>>> :set -XOverloadedStrings
>>> let rt = fromList ([("192.168.0.0/24", 1), ("10.10.0.0/16", 2), ("10.0.0.0/8", 3)] :: [(AddrRange IPv4, Int)])
>>> lookupAll "127.0.0.1" rt
[]
>>> lookupAll "192.168.0.1" rt
[(192.168.0.0/24,1)]
>>> lookupAll "10.10.0.1" rt
[(10.10.0.0/16,2),(10.0.0.0/8,3)]

findMatch :: Alternative m => Routable k => AddrRange k -> IPRTable k a -> m (AddrRange k, a) Source #

The findMatch function looks up IPRTable with a key of AddrRange. If the key matches routing informations in IPRTable, they are returned.

>>> let v4 = ["133.4.0.0/16","133.5.0.0/16","133.5.16.0/24","133.5.23.0/24"] :: [AddrRange IPv4]
>>> let rt = fromList $ zip v4 $ repeat ()
>>> findMatch "133.4.0.0/15" rt :: [(AddrRange IPv4,())]
[(133.4.0.0/16,()),(133.5.0.0/16,()),(133.5.16.0/24,()),(133.5.23.0/24,())]

fromList :: Routable k => [(AddrRange k, a)] -> IPRTable k a Source #

The fromList function creates a new IP routing table from a list of a pair of IPrange and value.

toList :: Routable k => IPRTable k a -> [(AddrRange k, a)] Source #

The toList function creates a list of a pair of AddrRange and value from an IP routing table.

foldt :: (IPRTable k a -> b -> b) -> b -> IPRTable k a -> b Source #

foldlWithKey :: (b -> AddrRange k -> a -> b) -> b -> IPRTable k a -> b Source #

O(n). Fold the keys and values in the IPRTable using the given left-associative binary operator. This function is equivalent to Data.Map.foldlWithKey with necessary to IPRTable changes. Since: 1.7.5

foldrWithKey :: (AddrRange k -> a -> b -> b) -> b -> IPRTable k a -> b Source #

O(n). Fold the keys and values in the IPRTable using the given right-associative binary operator. This function is equivalent to Data.Map.foldrWithKey with necessary to IPRTable changes. Since: 1.7.5