summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Announcer.hs21
-rw-r--r--examples/dhtd.hs14
-rw-r--r--todo.txt4
3 files changed, 31 insertions, 8 deletions
diff --git a/Announcer.hs b/Announcer.hs
index a2c8bde9..da1adcee 100644
--- a/Announcer.hs
+++ b/Announcer.hs
@@ -1,10 +1,12 @@
1{-# LANGUAGE DeriveDataTypeable #-}
2{-# LANGUAGE DeriveGeneric #-}
1{-# LANGUAGE ExistentialQuantification #-} 3{-# LANGUAGE ExistentialQuantification #-}
2{-# LANGUAGE GeneralizedNewtypeDeriving #-} 4{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3{-# LANGUAGE LambdaCase #-} 5{-# LANGUAGE LambdaCase #-}
4{-# LANGUAGE NamedFieldPuns #-} 6{-# LANGUAGE NamedFieldPuns #-}
5{-# LANGUAGE NondecreasingIndentation #-} 7{-# LANGUAGE NondecreasingIndentation #-}
6module Announcer 8module Announcer
7 ( Announcer 9 ( Announcer(scheduled)
8 , AnnounceKey 10 , AnnounceKey
9 , packAnnounceKey 11 , packAnnounceKey
10 , unpackAnnounceKey 12 , unpackAnnounceKey
@@ -13,6 +15,7 @@ module Announcer
13 , stopAnnouncer 15 , stopAnnouncer
14 , schedule 16 , schedule
15 , cancel 17 , cancel
18 , itemStatusNum
16 ) where 19 ) where
17 20
18import qualified Data.MinMaxPSQ as MM 21import qualified Data.MinMaxPSQ as MM
@@ -31,6 +34,8 @@ import Data.Hashable
31import Data.Maybe 34import Data.Maybe
32import Data.Ord 35import Data.Ord
33import Data.Time.Clock.POSIX 36import Data.Time.Clock.POSIX
37import qualified GHC.Generics as Generics
38import Generic.Data.Internal.Meta as Lyxia
34 39
35newtype AnnounceKey = AnnounceKey ByteString 40newtype AnnounceKey = AnnounceKey ByteString
36 deriving (Hashable,Ord,Eq) 41 deriving (Hashable,Ord,Eq)
@@ -38,16 +43,24 @@ newtype AnnounceKey = AnnounceKey ByteString
38packAnnounceKey :: Announcer -> String -> STM AnnounceKey 43packAnnounceKey :: Announcer -> String -> STM AnnounceKey
39packAnnounceKey _ = return . AnnounceKey . Char8.pack 44packAnnounceKey _ = return . AnnounceKey . Char8.pack
40 45
41unpackAnnounceKey :: AnnounceKey -> AnnounceKey -> STM String 46unpackAnnounceKey :: Announcer -> AnnounceKey -> STM String
42unpackAnnounceKey _ (AnnounceKey bs) = return $ Char8.unpack bs 47unpackAnnounceKey _ (AnnounceKey bs) = return $ Char8.unpack bs
43 48
44data ScheduledItem 49data ScheduledItem
45 = StopAnnouncer 50 = DeleteAnnouncement
46 | NewAnnouncement (STM (IO ())) (IO ()) (IO ()) POSIXTime 51 | NewAnnouncement (STM (IO ())) (IO ()) (IO ()) POSIXTime
47 | SearchFinished (IO ()) (IO ()) POSIXTime 52 | SearchFinished (IO ()) (IO ()) POSIXTime
48 | Announce (STM (IO ())) (IO ()) POSIXTime 53 | Announce (STM (IO ())) (IO ()) POSIXTime
49 | SearchResult (STM (IO ())) 54 | SearchResult (STM (IO ()))
50 | DeleteAnnouncement 55 | StopAnnouncer
56 -- Can't use Data because STM and IO. :(
57 -- deriving Data {- itemStatusNum sch = constrIndex $ toConstr sch -}
58 -- Using Generic to accomplish the job.
59 deriving Generics.Generic
60
61
62itemStatusNum :: ScheduledItem -> Int
63itemStatusNum sch = Lyxia.conIdToInt $ Lyxia.conId sch
51 64
52data Announcer = Announcer 65data Announcer = Announcer
53 { scheduled :: TVar (PSQ' AnnounceKey POSIXTime ScheduledItem) 66 { scheduled :: TVar (PSQ' AnnounceKey POSIXTime ScheduledItem)
diff --git a/examples/dhtd.hs b/examples/dhtd.hs
index 3e48e4bb..0439ed7e 100644
--- a/examples/dhtd.hs
+++ b/examples/dhtd.hs
@@ -769,6 +769,17 @@ clientSession s@Session{..} sock cnum h = do
769 -- 769 --
770 -- a +friend <jid> <text> 770 -- a +friend <jid> <text>
771 -- a +dhtkey <key> 771 -- a +dhtkey <key>
772 ("a", "") -> cmd0 $ do
773 now <- getPOSIXTime
774 rs <- atomically $ do
775 as <- readTVar (scheduled $ announcer)
776 forM (PSQ.toList as) $ \(k,ptm,item) -> do
777 kstr <- unpackAnnounceKey announcer k
778 return [ show (ptm - now)
779 , show (itemStatusNum item)
780 , kstr
781 ]
782 hPutClient h $ showColumns rs
772 ("a", s) | Just DHT{..} <- Map.lookup netname dhts 783 ("a", s) | Just DHT{..} <- Map.lookup netname dhts
773 , not (null s) 784 , not (null s)
774 -> cmd0 $ do 785 -> cmd0 $ do
@@ -805,6 +816,7 @@ clientSession s@Session{..} sock cnum h = do
805 reportit target = case op of 816 reportit target = case op of
806 '+' -> hPutClient h $ "Announcing at " ++ target ++ "." 817 '+' -> hPutClient h $ "Announcing at " ++ target ++ "."
807 '-' -> hPutClient h $ "Canceling " ++ target ++ "." 818 '-' -> hPutClient h $ "Canceling " ++ target ++ "."
819 -- mameth is for typical kademlia announce.
808 mameth = do 820 mameth = do
809 DHTAnnouncable { announceSendData 821 DHTAnnouncable { announceSendData
810 , announceParseData 822 , announceParseData
@@ -824,6 +836,8 @@ clientSession s@Session{..} sock cnum h = do
824 announceInterval) 836 announceInterval)
825 dta 837 dta
826 reportit $ show $ announceTarget dta 838 reportit $ show $ announceTarget dta
839 -- lmeth is for atypical announce messages such as
840 -- Tox dht-key and friend-request messages.
827 lmeth :: Maybe (IO ()) 841 lmeth :: Maybe (IO ())
828 lmeth = do 842 lmeth = do
829 DHTAnnouncable { announceSendData 843 DHTAnnouncable { announceSendData
diff --git a/todo.txt b/todo.txt
index 70af1142..10dc26cf 100644
--- a/todo.txt
+++ b/todo.txt
@@ -1,15 +1,11 @@
1xmpp: handle tox-friends in roster. 1xmpp: handle tox-friends in roster.
2 2
3xmpp: load tox user key from ~/.presence/<pubkey>.tox/secret
4
5tox: Add fallback trials to cookie response in case response is from another address than request. 3tox: Add fallback trials to cookie response in case response is from another address than request.
6 4
7ui: Online help. 5ui: Online help.
8 6
9ui: Explicit routing table node deletion. "forget" command. 7ui: Explicit routing table node deletion. "forget" command.
10 8
11ui: a - with no arguments would list the currently active recuring publications.
12
13kademlia: Change refresh algorithm to refresh farther away buckets before closer ones. 9kademlia: Change refresh algorithm to refresh farther away buckets before closer ones.
14 10
15kademlia: Remove (without replacement) stale routing nodes at some point. 11kademlia: Remove (without replacement) stale routing nodes at some point.