git-annex/Assistant/Pairing/Network.hs

108 lines
3.6 KiB
Haskell
Raw Normal View History

2012-09-08 19:21:34 +00:00
{- git-annex assistant pairing network code
2012-09-11 01:55:59 +00:00
-
- All network traffic is sent over multicast UDP. For reliability,
- each message is repeated until acknowledged. This is done using a
- thread, that gets stopped before the next message is sent.
2012-09-08 19:21:34 +00:00
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.Pairing.Network where
2012-09-11 01:55:59 +00:00
import Assistant.Common
2012-09-08 19:21:34 +00:00
import Assistant.Pairing
2012-09-11 01:55:59 +00:00
import Assistant.DaemonStatus
2012-09-08 19:21:34 +00:00
import Utility.ThreadScheduler
2012-09-11 01:55:59 +00:00
import Utility.Verifiable
2012-09-08 19:21:34 +00:00
import Network.Multicast
import Network.Info
import Network.Socket
import Control.Exception (bracket)
import qualified Data.Map as M
2012-09-11 01:55:59 +00:00
import Control.Concurrent
2012-09-08 19:21:34 +00:00
{- This is an arbitrary port in the dynamic port range, that could
- conceivably be used for some other broadcast messages.
- If so, hope they ignore the garbage from us; we'll certianly
- ignore garbage from them. Wild wild west. -}
pairingPort :: PortNumber
pairingPort = 55556
{- This is the All Hosts multicast group, which should reach all hosts
- on the same network segment. -}
multicastAddress :: SomeAddr -> HostName
multicastAddress (IPv4Addr _) = "224.0.0.1"
multicastAddress (IPv6Addr _) = "ff02::1"
2012-09-11 01:55:59 +00:00
{- Multicasts a message repeatedly on all interfaces, with a 2 second
- delay between each transmission. The message is repeated forever
- unless a number of repeats is specified.
2012-09-08 19:21:34 +00:00
-
- The remoteHostAddress is set to the interface's IP address.
-
- Note that new sockets are opened each time. This is hardly efficient,
- but it allows new network interfaces to be used as they come up.
- On the other hand, the expensive DNS lookups are cached.
-}
2012-09-11 01:55:59 +00:00
multicastPairMsg :: Maybe Int -> Secret -> PairStage -> PairData -> IO ()
multicastPairMsg repeats secret stage pairdata = go M.empty repeats
2012-09-08 19:21:34 +00:00
where
2012-09-11 01:55:59 +00:00
go _ (Just 0) = noop
go cache n = do
2012-09-08 19:21:34 +00:00
addrs <- activeNetworkAddresses
let cache' = updatecache cache addrs
mapM_ (sendinterface cache') addrs
threadDelaySeconds (Seconds 2)
2012-09-11 01:55:59 +00:00
go cache' $ pred <$> n
2012-09-08 19:21:34 +00:00
sendinterface cache i = void $ catchMaybeIO $
withSocketsDo $ bracket
(multicastSender (multicastAddress i) pairingPort)
(sClose . fst)
(\(sock, addr) -> do
setInterface sock (showAddr i)
maybe noop (\s -> void $ sendTo sock s addr)
(M.lookup i cache)
)
updatecache cache [] = cache
updatecache cache (i:is)
| M.member i cache = updatecache cache is
| otherwise = updatecache (M.insert i (show $ mkmsg i) cache) is
2012-09-11 01:55:59 +00:00
mkmsg addr = PairMsg $
mkVerifiable (stage, pairdata, addr) secret
2012-09-08 19:21:34 +00:00
2012-09-11 01:55:59 +00:00
startSending :: DaemonStatusHandle -> PairingInProgress -> IO () -> IO ()
startSending dstatus pip sender = do
tid <- forkIO sender
let pip' = pip { inProgressThreadId = Just tid }
oldpip <- modifyDaemonStatus dstatus $
\s -> (s { pairingInProgress = Just pip' }, pairingInProgress s)
maybe noop stopold oldpip
2012-09-08 19:21:34 +00:00
where
2012-09-11 01:55:59 +00:00
stopold = maybe noop killThread . inProgressThreadId
stopSending :: DaemonStatusHandle -> PairingInProgress -> IO ()
stopSending dstatus pip = do
maybe noop killThread $ inProgressThreadId pip
modifyDaemonStatus_ dstatus $ \s -> s { pairingInProgress = Nothing }
2012-09-08 19:21:34 +00:00
class ToSomeAddr a where
toSomeAddr :: a -> SomeAddr
instance ToSomeAddr IPv4 where
toSomeAddr (IPv4 a) = IPv4Addr a
instance ToSomeAddr IPv6 where
toSomeAddr (IPv6 o1 o2 o3 o4) = IPv6Addr (o1, o2, o3, o4)
showAddr :: SomeAddr -> HostName
showAddr (IPv4Addr a) = show $ IPv4 a
showAddr (IPv6Addr (o1, o2, o3, o4)) = show $ IPv6 o1 o2 o3 o4
activeNetworkAddresses :: IO [SomeAddr]
activeNetworkAddresses = filter (not . all (`elem` "0.:") . showAddr)
. concat . map (\ni -> [toSomeAddr $ ipv4 ni, toSomeAddr $ ipv6 ni])
<$> getNetworkInterfaces