summaryrefslogtreecommitdiff
path: root/dht/src/Network/Tox/Avahi.hs
blob: 2ca6515c5ae0b728330d867eec6065e7fffc80ef (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE CPP             #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns    #-}
module Network.Tox.Avahi
  ( module Network.Tox.Avahi
  , NodeInfo(..)
  , NodeId
  ) where

import Control.Applicative
import Data.Foldable
import Network.Address
import Network.BSD         (getHostName)
import Network.Tox.NodeId
import Text.Read

#if defined(VERSION_avahi)
import Network.Avahi
#else
data Service = Service
#endif


toxServiceName :: String
toxServiceName = "_tox_dht._udp"

toxServiceDomain :: String
toxServiceDomain = "local"

(<.>) :: String -> String -> String
a <.> b = a ++ "." ++ b

toxService :: String -> PortNumber -> NodeId -> (Maybe NodeId) -> Service
toxService hostname (fromIntegral -> port) dhtkey toxid =
  Service
#if defined(VERSION_avahi)
  {
    serviceProtocol = PROTO_UNSPEC,
    serviceName     = "Tox DHT @ " ++ hostname,
    serviceType     = toxServiceName,
    serviceDomain   = toxServiceDomain,
    serviceHost     = if null hostname then "" else hostname <.> toxServiceDomain,
    serviceAddress  = Nothing,
    servicePort     = port,
    serviceText     = maybe (show dhtkey) (show . ((,) dhtkey)) toxid
  }
#endif

announceToxServiceWithHostname :: String -> PortNumber -> NodeId -> (Maybe NodeId) -> IO ()
#if defined(VERSION_avahi)
announceToxServiceWithHostname  = (boobs.boobs) announce toxService
  where boobs = ((.).(.))
#else
announceToxServiceWithHostname _ _ _ _ = return ()
#endif

announceToxService :: PortNumber -> NodeId -> (Maybe NodeId) -> IO ()
announceToxService a b c = do
  h <- getHostName
  announceToxServiceWithHostname h a b c

queryToxService :: (NodeInfo -> Maybe NodeId -> IO ()) -> IO ()
queryToxService cb =
#if defined(VERSION_avahi)
  browse $
  BrowseQuery
  { lookupProtocol    = PROTO_UNSPEC
  , lookupServiceName = toxServiceName
  , lookupDomain      = toxServiceDomain
  , lookupCallback    = runCallback
  }
  where
    runCallback Service {..} = do
      let both :: Maybe (NodeId, NodeId)
          both = readMaybe serviceText
          nid  = (fst <$> both) <|> readMaybe serviceText
          addr = readMaybe =<< serviceAddress
          p    = fromIntegral servicePort
      forM_ nid $ \n -> forM_ addr $ \a -> cb (NodeInfo n a p) (snd <$> both)
#else
  return ()
#endif