Safe Haskell | None |
---|---|
Language | Haskell98 |
- type TcpHandle = Channel (Tcp ())
- type Tcp = Layer TcpState
- data TcpState = TcpState {}
- emptyTcpState :: TcpHandle -> IP4Handle -> POSIXTime -> TcpState
- self :: Tcp TcpHandle
- ip4Handle :: Tcp IP4Handle
- getHost :: Tcp Host
- setHost :: Host -> Tcp ()
- modifyHost :: (Host -> Host) -> Tcp ()
- resetTimeWait2MSL :: SocketId -> Tcp ()
- getTimeWait :: IP4 -> TcpHeader -> Tcp (Maybe (SocketId, TimeWaitSock))
- removeTimeWait :: SocketId -> Tcp ()
- getConnections :: Tcp Connections
- setConnections :: Connections -> Tcp ()
- lookupConnection :: SocketId -> Tcp (Maybe TcpSocket)
- getConnection :: SocketId -> Tcp TcpSocket
- setConnection :: SocketId -> TcpSocket -> Tcp ()
- addConnection :: SocketId -> TcpSocket -> Tcp ()
- modifyConnection :: SocketId -> (TcpSocket -> TcpSocket) -> Tcp ()
- remConnection :: SocketId -> Tcp ()
- sendSegment :: IP4 -> TcpHeader -> ByteString -> Tcp ()
- initialSeqNum :: Tcp TcpSeqNum
- addInitialSeqNum :: TcpSeqNum -> Tcp ()
- allocatePort :: Tcp TcpPort
- closePort :: TcpPort -> Tcp ()
- newtype Sock a = Sock {}
- type Escape r = TcpSocket -> Tcp (TcpSocket, Maybe r)
- type Next a r = TcpSocket -> a -> Tcp (TcpSocket, Maybe r)
- inTcp :: Tcp a -> Sock a
- escape :: Sock a
- runSock_ :: TcpSocket -> Sock a -> Tcp ()
- runSock' :: TcpSocket -> Sock a -> Tcp TcpSocket
- runSock :: TcpSocket -> Sock a -> Tcp (TcpSocket, Maybe a)
- eachConnection :: Sock () -> Tcp ()
- withConnection :: IP4 -> TcpHeader -> Sock a -> Tcp ()
- withConnection' :: IP4 -> TcpHeader -> Sock a -> Tcp () -> Tcp ()
- listeningConnection :: SocketId -> Sock a -> Tcp (Maybe a)
- establishedConnection :: SocketId -> Sock a -> Tcp ()
- getParent :: Sock (Maybe SocketId)
- inParent :: Sock a -> Sock (Maybe a)
- withChild :: TcpSocket -> Sock a -> Sock (Maybe a)
- getTcpSocket :: Sock TcpSocket
- setTcpSocket :: TcpSocket -> Sock ()
- getTcpTimers :: Sock TcpTimers
- modifyTcpSocket :: (TcpSocket -> (a, TcpSocket)) -> Sock a
- modifyTcpSocket_ :: (TcpSocket -> TcpSocket) -> Sock ()
- modifyTcpTimers :: (TcpTimers -> (a, TcpTimers)) -> Sock a
- modifyTcpTimers_ :: (TcpTimers -> TcpTimers) -> Sock ()
- setState :: ConnState -> Sock ()
- getState :: Sock ConnState
- whenState :: ConnState -> Sock () -> Sock ()
- whenStates :: [ConnState] -> Sock () -> Sock ()
- pushAcceptor :: Acceptor -> Sock ()
- popAcceptor :: Sock (Maybe Acceptor)
- notify :: Bool -> Sock ()
- outputS :: IO () -> Sock ()
- advanceRcvNxt :: TcpSeqNum -> Sock ()
- advanceSndNxt :: TcpSeqNum -> Sock ()
- remoteHost :: Sock IP4
- tcpOutput :: TcpHeader -> ByteString -> Sock ()
- shutdown :: Sock ()
- closeSocket :: Sock ()
Documentation
modifyHost :: (Host -> Host) -> Tcp () Source
resetTimeWait2MSL :: SocketId -> Tcp () Source
Reset the 2MSL timer on the socket in TimeWait.
getTimeWait :: IP4 -> TcpHeader -> Tcp (Maybe (SocketId, TimeWaitSock)) Source
removeTimeWait :: SocketId -> Tcp () Source
setConnections :: Connections -> Tcp () Source
lookupConnection :: SocketId -> Tcp (Maybe TcpSocket) Source
Lookup a connection, returning Nothing
if the connection doesn't exist.
getConnection :: SocketId -> Tcp TcpSocket Source
Retrieve a connection from the host. The computation fails if the connection doesn't exist.
setConnection :: SocketId -> TcpSocket -> Tcp () Source
Assign a connection to a socket id. If the TcpSocket is in TimeWait, this will do two things:
- Remove the corresponding key from the connections map
- Add the socket to the TimeWait map, using the current value of its 2MSL timer (which should be set when the TimeWait state is entered)
The purpose of this is to clean up the memory associated with the connection as soon as possible, and once it's in TimeWait, no data will flow on the socket.
addConnection :: SocketId -> TcpSocket -> Tcp () Source
Add a new connection to the host.
modifyConnection :: SocketId -> (TcpSocket -> TcpSocket) -> Tcp () Source
Modify an existing connection in the host.
remConnection :: SocketId -> Tcp () Source
Remove a connection from the host.
sendSegment :: IP4 -> TcpHeader -> ByteString -> Tcp () Source
Send out a tcp segment via the IP layer.
initialSeqNum :: Tcp TcpSeqNum Source
Get the initial sequence number.
addInitialSeqNum :: TcpSeqNum -> Tcp () Source
Increment the initial sequence number by a value.
allocatePort :: Tcp TcpPort Source
Allocate a new port for use.
Tcp operations in the context of a socket.
This implementation is a bit ridiculous, and when the eventual rewrite comes
this should be one of the first things to be reconsidered. The basic problem
is that if you rely on the finished
implementation for the Layer monad, you
exit from the socket context as well, losing any changes that have been made
locally. This gives the ability to simulate finished
, with the benefit of
only yielding from the Sock context, not the whole Tcp context.
runSock :: TcpSocket -> Sock a -> Tcp (TcpSocket, Maybe a) Source
Run the socket action, and increment its internal timestamp value.
eachConnection :: Sock () -> Tcp () Source
Iterate for each connection, rolling back to its previous state if the computation fails.
establishedConnection :: SocketId -> Sock a -> Tcp () Source
Run a socket operation in the context of the socket identified by the socket id.
XXX this should really be renamed, as it's not guarding on the state of the socket
getParent :: Sock (Maybe SocketId) Source
Get the parent id of the current socket, and fail if it doesn't exist.
inParent :: Sock a -> Sock (Maybe a) Source
Run an action in the context of the socket's parent. Returns Nothing
if
the connection has no parent.
setTcpSocket :: TcpSocket -> Sock () Source
modifyTcpSocket :: (TcpSocket -> (a, TcpSocket)) -> Sock a Source
modifyTcpSocket_ :: (TcpSocket -> TcpSocket) -> Sock () Source
modifyTcpTimers :: (TcpTimers -> (a, TcpTimers)) -> Sock a Source
modifyTcpTimers_ :: (TcpTimers -> TcpTimers) -> Sock () Source
whenStates :: [ConnState] -> Sock () -> Sock () Source
pushAcceptor :: Acceptor -> Sock () Source
popAcceptor :: Sock (Maybe Acceptor) Source
Pop off an acceptor.
notify :: Bool -> Sock () Source
Send a notification back to a waiting process that the socket has been
established, or that it has failed. It's assumed that this will only be
called from the context of a user socket, so when the parameter is False
,
the user close field will be set to true.
advanceRcvNxt :: TcpSeqNum -> Sock () Source
advanceSndNxt :: TcpSeqNum -> Sock () Source
remoteHost :: Sock IP4 Source
tcpOutput :: TcpHeader -> ByteString -> Sock () Source
Send a TCP segment in the context of a socket.
closeSocket :: Sock () Source
Set the socket state to closed, and unblock any waiting processes.