diff options
-rw-r--r-- | Mainline.hs | 2 | ||||
-rw-r--r-- | Tox.hs | 38 | ||||
-rwxr-xr-x | c | 3 | ||||
-rw-r--r-- | examples/dhtd.hs | 32 |
4 files changed, 67 insertions, 8 deletions
diff --git a/Mainline.hs b/Mainline.hs index 4ce4f4da..28025d59 100644 --- a/Mainline.hs +++ b/Mainline.hs | |||
@@ -608,6 +608,7 @@ newClient addr = do | |||
608 | forM_ ns $ \n -> do | 608 | forM_ ns $ \n -> do |
609 | hPutStrLn stderr $ "Change IP, ping: "++show n | 609 | hPutStrLn stderr $ "Change IP, ping: "++show n |
610 | ping outgoingClient n | 610 | ping outgoingClient n |
611 | -- TODO: trigger bootstrap ipv4 | ||
611 | again | 612 | again |
612 | fork $ fix $ \again -> do | 613 | fork $ fix $ \again -> do |
613 | myThreadId >>= flip labelThread "addr6" | 614 | myThreadId >>= flip labelThread "addr6" |
@@ -616,6 +617,7 @@ newClient addr = do | |||
616 | forM_ ns $ \n -> do | 617 | forM_ ns $ \n -> do |
617 | hPutStrLn stderr $ "Change IP, ping: "++show n | 618 | hPutStrLn stderr $ "Change IP, ping: "++show n |
618 | ping outgoingClient n | 619 | ping outgoingClient n |
620 | -- TODO: trigger bootstrap ipv6 | ||
619 | again | 621 | again |
620 | 622 | ||
621 | refresh_thread4 <- forkPollForRefresh | 623 | refresh_thread4 <- forkPollForRefresh |
@@ -10,6 +10,7 @@ | |||
10 | {-# LANGUAGE TupleSections #-} | 10 | {-# LANGUAGE TupleSections #-} |
11 | module Tox where | 11 | module Tox where |
12 | 12 | ||
13 | import Control.Applicative | ||
13 | import Control.Arrow | 14 | import Control.Arrow |
14 | import Control.Concurrent (MVar) | 15 | import Control.Concurrent (MVar) |
15 | import Control.Concurrent.STM | 16 | import Control.Concurrent.STM |
@@ -58,6 +59,10 @@ import Data.Time.Clock.POSIX (POSIXTime) | |||
58 | import Global6 | 59 | import Global6 |
59 | import Data.Ord | 60 | import Data.Ord |
60 | import System.IO | 61 | import System.IO |
62 | import qualified Data.Aeson as JSON | ||
63 | ;import Data.Aeson (FromJSON, ToJSON, (.=)) | ||
64 | import Control.Monad | ||
65 | import Text.Read | ||
61 | 66 | ||
62 | newtype NodeId = NodeId ByteString | 67 | newtype NodeId = NodeId ByteString |
63 | deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable) | 68 | deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable) |
@@ -89,6 +94,36 @@ data NodeInfo = NodeInfo | |||
89 | } | 94 | } |
90 | deriving (Eq,Ord) | 95 | deriving (Eq,Ord) |
91 | 96 | ||
97 | instance ToJSON NodeInfo where | ||
98 | toJSON (NodeInfo nid (IPv4 ip) port) | ||
99 | = JSON.object [ "public_key" .= show nid | ||
100 | , "ipv4" .= show ip | ||
101 | , "port" .= (fromIntegral port :: Int) | ||
102 | ] | ||
103 | toJSON (NodeInfo nid (IPv6 ip6) port) | ||
104 | | Just ip <- un4map ip6 | ||
105 | = JSON.object [ "public_key" .= show nid | ||
106 | , "ipv4" .= show ip | ||
107 | , "port" .= (fromIntegral port :: Int) | ||
108 | ] | ||
109 | | otherwise | ||
110 | = JSON.object [ "node-id" .= show nid | ||
111 | , "ipv6" .= show ip6 | ||
112 | , "port" .= (fromIntegral port :: Int) | ||
113 | ] | ||
114 | instance FromJSON NodeInfo where | ||
115 | parseJSON (JSON.Object v) = do | ||
116 | nidstr <- v JSON..: "public_key" | ||
117 | ip6str <- v JSON..:? "ipv6" | ||
118 | ip4str <- v JSON..:? "ipv4" | ||
119 | portnum <- v JSON..: "port" | ||
120 | ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe) | ||
121 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) | ||
122 | let (bs,_) = Base16.decode (C8.pack nidstr) | ||
123 | guard (B.length bs == 32) | ||
124 | return $ NodeInfo (NodeId bs) ip (fromIntegral (portnum :: Word16)) | ||
125 | |||
126 | |||
92 | instance S.Serialize NodeInfo where | 127 | instance S.Serialize NodeInfo where |
93 | get = do | 128 | get = do |
94 | nid <- S.get | 129 | nid <- S.get |
@@ -569,3 +604,6 @@ gen g = let (bs, g') = randomBytesGenerate 24 g | |||
569 | Right w = S.runGet S.getWord64be ws | 604 | Right w = S.runGet S.getWord64be ws |
570 | in ( TransactionId (Nonce8 w) (Nonce24 bs), g'' ) | 605 | in ( TransactionId (Nonce8 w) (Nonce24 bs), g'' ) |
571 | 606 | ||
607 | |||
608 | ping :: ToxClient -> NodeInfo -> IO Bool | ||
609 | ping = error "todo ping" | ||
@@ -1,4 +1,5 @@ | |||
1 | #!/bin/sh | 1 | #!/bin/sh |
2 | defs="-DBENCODE_AESON -DTHREAD_DEBUG" | 2 | defs="-DBENCODE_AESON -DTHREAD_DEBUG" |
3 | hide="-hide-package crypto-random -hide-package crypto-api -hide-package crypto-numbers -hide-package cryptohash -hide-package prettyclass" | 3 | hide="-hide-package crypto-random -hide-package crypto-api -hide-package crypto-numbers -hide-package cryptohash -hide-package prettyclass" |
4 | ghc -freverse-errors $hide -isrc -XOverloadedStrings -XRecordWildCards $defs "$@" | 4 | cbits="cbits/*.c" |
5 | ghc -freverse-errors $hide -isrc -XOverloadedStrings -XRecordWildCards $defs $cbits "$@" | ||
diff --git a/examples/dhtd.hs b/examples/dhtd.hs index ef225f0c..a1b8d665 100644 --- a/examples/dhtd.hs +++ b/examples/dhtd.hs | |||
@@ -49,6 +49,7 @@ import Network.QueryResponse | |||
49 | import Network.StreamServer | 49 | import Network.StreamServer |
50 | import Kademlia | 50 | import Kademlia |
51 | import qualified Mainline | 51 | import qualified Mainline |
52 | import qualified Tox | ||
52 | import Network.DHT.Routing as R | 53 | import Network.DHT.Routing as R |
53 | import Data.Aeson as J (ToJSON, FromJSON) | 54 | import Data.Aeson as J (ToJSON, FromJSON) |
54 | import qualified Data.Aeson as J | 55 | import qualified Data.Aeson as J |
@@ -280,7 +281,7 @@ clientSession s@Session{..} sock cnum h = do | |||
280 | pid <- getProcessID | 281 | pid <- getProcessID |
281 | hPutClient h (show pid) | 282 | hPutClient h (show pid) |
282 | ("external-ip", _) -> cmd0 $ do | 283 | ("external-ip", _) -> cmd0 $ do |
283 | unlines . map (either show show . Mainline.either4or6) <$> externalAddresses | 284 | unlines . map (either show show . either4or6) <$> externalAddresses |
284 | >>= hPutClient h | 285 | >>= hPutClient h |
285 | #ifdef THREAD_DEBUG | 286 | #ifdef THREAD_DEBUG |
286 | ("threads", _) -> cmd0 $ do | 287 | ("threads", _) -> cmd0 $ do |
@@ -470,10 +471,16 @@ main = do | |||
470 | 471 | ||
471 | quitBt <- forkListener bt | 472 | quitBt <- forkListener bt |
472 | 473 | ||
473 | tox <- return $ error "TODO: Tox.newClient" | 474 | let toxport = succ $ fromMaybe 33445 (fromIntegral <$> sockAddrPort addr) |
474 | quitTox <- return $ return () -- TODO: forkListener tox | 475 | addrTox <- getBindAddress (show toxport) True |
476 | (tox,toxR) <- Tox.newClient addrTox | ||
477 | |||
478 | -- TODO: load saved tox nodes. | ||
479 | |||
480 | quitTox <- forkListener tox | ||
475 | 481 | ||
476 | mainlineSearches <- atomically $ newTVar Map.empty | 482 | mainlineSearches <- atomically $ newTVar Map.empty |
483 | toxSearches <- atomically $ newTVar Map.empty | ||
477 | 484 | ||
478 | let mainlineDHT bkts = DHT | 485 | let mainlineDHT bkts = DHT |
479 | { dhtBuckets = bkts btR | 486 | { dhtBuckets = bkts btR |
@@ -482,13 +489,13 @@ main = do | |||
482 | [ ("node", DHTQuery (Mainline.nodeSearch bt) | 489 | [ ("node", DHTQuery (Mainline.nodeSearch bt) |
483 | (\ni -> fmap Mainline.unwrapNodes | 490 | (\ni -> fmap Mainline.unwrapNodes |
484 | . Mainline.findNodeH btR ni | 491 | . Mainline.findNodeH btR ni |
485 | . flip Mainline.FindNode (Just Mainline.Want_Both)) | 492 | . flip Mainline.FindNode (Just Want_Both)) |
486 | show | 493 | show |
487 | (const Nothing)) | 494 | (const Nothing)) |
488 | , ("peer", DHTQuery (Mainline.peerSearch bt) | 495 | , ("peer", DHTQuery (Mainline.peerSearch bt) |
489 | (\ni -> fmap Mainline.unwrapPeers | 496 | (\ni -> fmap Mainline.unwrapPeers |
490 | . Mainline.getPeersH btR swarms ni | 497 | . Mainline.getPeersH btR swarms ni |
491 | . flip Mainline.GetPeers (Just Mainline.Want_Both) | 498 | . flip Mainline.GetPeers (Just Want_Both) |
492 | . (read . show)) -- TODO: InfoHash -> NodeId | 499 | . (read . show)) -- TODO: InfoHash -> NodeId |
493 | (show . pPrint) | 500 | (show . pPrint) |
494 | (Just . show)) | 501 | (Just . show)) |
@@ -496,9 +503,20 @@ main = do | |||
496 | , dhtParseId = readEither :: String -> Either String Mainline.NodeId | 503 | , dhtParseId = readEither :: String -> Either String Mainline.NodeId |
497 | , dhtSearches = mainlineSearches | 504 | , dhtSearches = mainlineSearches |
498 | } | 505 | } |
506 | toxDHT bkts = DHT | ||
507 | { dhtBuckets = bkts toxR | ||
508 | , dhtPing = Tox.ping tox | ||
509 | , dhtQuery = Map.fromList | ||
510 | [ -- "node" | ||
511 | ] | ||
512 | , dhtParseId = readEither :: String -> Either String Tox.NodeId | ||
513 | , dhtSearches = toxSearches | ||
514 | } | ||
499 | dhts = Map.fromList | 515 | dhts = Map.fromList |
500 | [ ("bt4", mainlineDHT Mainline.routing4) | 516 | [ ("bt4", mainlineDHT Mainline.routing4) |
501 | , ("bt6", mainlineDHT Mainline.routing6) | 517 | , ("bt6", mainlineDHT Mainline.routing6) |
518 | , ("tox4", toxDHT Tox.routing4) | ||
519 | , ("tox6", toxDHT Tox.routing6) | ||
502 | ] | 520 | ] |
503 | 521 | ||
504 | waitForSignal <- do | 522 | waitForSignal <- do |
@@ -521,7 +539,7 @@ main = do | |||
521 | let bkts4 = Mainline.routing4 btR | 539 | let bkts4 = Mainline.routing4 btR |
522 | btSaved4 <- loadNodes "bt4" :: IO [Mainline.NodeInfo] | 540 | btSaved4 <- loadNodes "bt4" :: IO [Mainline.NodeInfo] |
523 | putStrLn $ "Loaded "++show (length btSaved4)++" nodes for bt4." | 541 | putStrLn $ "Loaded "++show (length btSaved4)++" nodes for bt4." |
524 | fallbackNodes4 <- Mainline.bootstrapNodes Mainline.Want_IP4 | 542 | fallbackNodes4 <- Mainline.bootstrapNodes Want_IP4 |
525 | fork $ do | 543 | fork $ do |
526 | myThreadId >>= flip labelThread "bootstrap.Mainline4" | 544 | myThreadId >>= flip labelThread "bootstrap.Mainline4" |
527 | bootstrap (Mainline.nodeSearch bt) bkts4 (Mainline.ping bt) btSaved4 fallbackNodes4 | 545 | bootstrap (Mainline.nodeSearch bt) bkts4 (Mainline.ping bt) btSaved4 fallbackNodes4 |
@@ -530,7 +548,7 @@ main = do | |||
530 | btSaved6 <- loadNodes "bt6" | 548 | btSaved6 <- loadNodes "bt6" |
531 | putStrLn $ "Loaded "++show (length btSaved6)++" nodes for bt6." | 549 | putStrLn $ "Loaded "++show (length btSaved6)++" nodes for bt6." |
532 | let bkts6 = Mainline.routing6 btR | 550 | let bkts6 = Mainline.routing6 btR |
533 | fallbackNodes6 <- Mainline.bootstrapNodes Mainline.Want_IP6 | 551 | fallbackNodes6 <- Mainline.bootstrapNodes Want_IP6 |
534 | fork $ do | 552 | fork $ do |
535 | myThreadId >>= flip labelThread "bootstrap.Mainline6" | 553 | myThreadId >>= flip labelThread "bootstrap.Mainline6" |
536 | bootstrap (Mainline.nodeSearch bt) bkts6 (Mainline.ping bt) btSaved6 fallbackNodes6 | 554 | bootstrap (Mainline.nodeSearch bt) bkts6 (Mainline.ping bt) btSaved6 fallbackNodes6 |