summaryrefslogtreecommitdiff
path: root/Announcer.hs
blob: 4f4eba8f1a50fea0b5a4d2f528aa81207668805f (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
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
{-# LANGUAGE ExistentialQuantification  #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase                 #-}
{-# LANGUAGE NondecreasingIndentation   #-}
module Announcer
    ( Announcer
    , AnnounceKey
    , packAnnounceKey
    , unpackAnnounceKey
    , AnnounceMethod(..)
    , forkAnnouncer
    , stopAnnouncer
    , schedule
    , cancel
    ) where

import Data.Wrapper.PSQ as PSQ
import Network.Kademlia.Search
import InterruptibleDelay

import Control.Concurrent.Lifted.Instrument
import Control.Concurrent.STM
import Control.Monad
import Data.ByteString                      (ByteString)
import qualified Data.ByteString.Char8      as Char8
import Data.Function
import Data.Hashable
import Data.Maybe
import Data.Time.Clock.POSIX

newtype AnnounceKey = AnnounceKey ByteString
 deriving (Hashable,Ord,Eq)

packAnnounceKey :: Announcer -> String -> STM AnnounceKey
packAnnounceKey _ = return . AnnounceKey . Char8.pack

unpackAnnounceKey :: AnnounceKey -> AnnounceKey -> STM String
unpackAnnounceKey _ (AnnounceKey bs) = return $ Char8.unpack bs

data ScheduledItem
    = forall r. ScheduledItem (AnnounceMethod r)
    | StopAnnouncer

data Announcer = Announcer
    { scheduled       :: TVar (PSQ' AnnounceKey POSIXTime ScheduledItem)
    , announcerActive :: TVar Bool
    , interrutible    :: InterruptibleDelay
    }

scheduleImmediately :: Announcer -> ScheduledItem -> STM ()
scheduleImmediately announcer item
    = modifyTVar' (scheduled announcer) (PSQ.insert' (AnnounceKey "") item 0)

stopAnnouncer :: Announcer -> IO ()
stopAnnouncer announcer = do
    atomically $ scheduleImmediately announcer StopAnnouncer
    atomically $ readTVar (announcerActive announcer) >>= check . not

data AnnounceMethod r = forall nid ni addr r tok a. AnnounceMethod
    { aSearch  :: Search nid addr tok ni r
    , aPublish :: r -> tok -> Maybe ni -> IO (Maybe a)
    }

-- startDelay :: InterruptibleDelay -> Microseconds -> IO Bool
-- interruptDelay :: InterruptibleDelay -> IO ()

schedule :: Announcer -> AnnounceKey -> AnnounceMethod r -> r -> IO ()
schedule announcer _ _ _ = do
    -- fork the search
    -- add it to the priority queue of announce methods.
    interruptDelay (interrutible announcer)

cancel :: Announcer -> AnnounceKey -> AnnounceMethod r -> r -> IO ()
cancel announcer _ _ _ = do
    -- cancel search/announce
    interruptDelay (interrutible announcer)


forkAnnouncer :: IO Announcer
forkAnnouncer = do
    delay <- interruptibleDelay
    announcer <- atomically $ Announcer <$> newTVar PSQ.empty
                                        <*> newTVar True
                                        <*> pure delay
    fork $ announceThread announcer
    return announcer


announceThread :: Announcer -> IO ()
announceThread announcer = do
    myThreadId >>= flip labelThread "announcer"
    fix $ \loop -> do
    join $ atomically $ do
        item <- maybe retry return =<< findMin <$> readTVar (scheduled announcer)
        return $ do
        now <- getPOSIXTime
        -- Is it time to do something?
        if (prio item > now)
            then do -- Yes.  Dequeue and handle this event.
                 action <- atomically $ do
                     modifyTVar' (scheduled announcer)
                                 (PSQ.delete (key item))
                     performScheduledItem announcer item
                 -- Are we finished?
                 mapM_ (>> loop)  -- No? Okay, perform scheduled op and loop.
                       action
            else do -- No.  Wait a bit.
                 startDelay (interrutible announcer) (microseconds $ prio item - now)
                 loop
    -- We're done.  Let 'stopAnnouncer' know that it can stop blocking.
    atomically $ writeTVar (announcerActive announcer) False

performScheduledItem :: Announcer -> Binding' AnnounceKey POSIXTime ScheduledItem -> STM (Maybe (IO ()))
performScheduledItem announcer = \case

    (Binding _ StopAnnouncer _) ->  return Nothing

    -- announcement added:

    -- wait for time to announce or for search to finish.
    --
    -- time for periodic announce:
    --   (re-)announce to the current known set of storing-nodes.
    --   If the search is finished, restart the search.
    --
    -- search finished:
    --   if any of the current storing-nodes set have not been
    --   announced to, announce to them.
    --
    --
    -- announcement removed:
    --