module Hans.Tcp.Timers where
import Hans.Config
import qualified Hans.HashTable as HT
import Hans.Lens
import Hans.Tcp.Tcb
import Hans.Tcp.Output
import Hans.Tcp.SendWindow
import Hans.Time (toUSeconds)
import Hans.Types
import Control.Concurrent (threadDelay)
import Control.Monad (when)
import Data.IORef (atomicModifyIORef')
import Data.Time.Clock (getCurrentTime,diffUTCTime)
tcpTimers :: NetworkStack -> IO ()
tcpTimers ns = loop True
where
loop runSlow =
do start <- getCurrentTime
HT.mapHashTableM_ (\_ -> updateActive ns runSlow) (view tcpActive ns)
end <- getCurrentTime
let delay = 0.250 diffUTCTime end start
when (delay > 0) (threadDelay (toUSeconds delay))
loop $! not runSlow
updateActive :: NetworkStack -> Bool -> Tcb -> IO ()
updateActive ns runSlow tcb@Tcb { .. } =
do
when runSlow $
do ts <- atomicModifyIORef' tcbTimers updateTimers
handleRTO ns tcb ts
handle2MSL ns tcb ts
shouldAck <- atomicModifyIORef' tcbNeedsDelayedAck (\ b -> (False,b))
when shouldAck (sendAck ns tcb)
handleRTO :: NetworkStack -> Tcb -> TcpTimers -> IO ()
handleRTO ns Tcb { .. } TcpTimers { .. }
| ttRetransmitValid && ttRetransmit <= 0 =
do mbSeg <- atomicModifyIORef' tcbSendWindow retransmitTimeout
case mbSeg of
Just (hdr,body) ->
do atomicModifyIORef' tcbTimers retryRetransmit
_ <- sendTcp ns tcbRouteInfo tcbRemote hdr body
return ()
Nothing ->
return ()
| otherwise =
return ()
handle2MSL :: NetworkStack -> Tcb -> TcpTimers -> IO ()
handle2MSL ns tcb@Tcb { .. } TcpTimers { .. }
| tt2MSL <= 0 =
if ttIdle >= ttMaxIdle
then closeActive ns tcb
else atomicModifyIORef' tcbTimers (reset2MSL (view config ns))
| otherwise =
return ()