add som debug prints
This commit is contained in:
		
							parent
							
								
									f6481996d7
								
							
						
					
					
						commit
						edf66e1b51
					
				
					 4 changed files with 11 additions and 1 deletions
				
			
		| 
						 | 
				
			
			@ -35,6 +35,7 @@ main = do
 | 
			
		|||
        -- handle unsuccessful join
 | 
			
		||||
 | 
			
		||||
        putStrLn $ err <> " Error joining, start listening for incoming requests anyways"
 | 
			
		||||
        print =<< readTVarIO thisNode
 | 
			
		||||
        wait =<< async (fediMainThreads serverSock thisNode)
 | 
			
		||||
        -- TODO: periodic retry
 | 
			
		||||
           )
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -246,6 +246,7 @@ handleIncomingRequest :: LocalNodeStateSTM                     -- ^ the handling
 | 
			
		|||
                      -> SockAddr                           -- ^ source address of the request
 | 
			
		||||
                      -> IO ()
 | 
			
		||||
handleIncomingRequest nsSTM sendQ msgSet sourceAddr = do
 | 
			
		||||
    putStrLn $ "handling incoming request: " <> show msgSet
 | 
			
		||||
    ns <- readTVarIO nsSTM
 | 
			
		||||
    -- add nodestate to cache
 | 
			
		||||
    now <- getPOSIXTime
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -150,7 +150,6 @@ fediChordBootstrapJoin nsSTM (joinHost, joinPort) =
 | 
			
		|||
                           Just (FORWARD resultset) -> foldr' (addCacheEntryPure now) cacheAcc resultset
 | 
			
		||||
                              )
 | 
			
		||||
                           initCache bootstrapResponse
 | 
			
		||||
               putStrLn "initialised bootstrap cache"
 | 
			
		||||
               fediChordJoin bootstrapCache nsSTM
 | 
			
		||||
                                                   )
 | 
			
		||||
       `catch` (\e -> pure . Left $ "Error at bootstrap joining: " <> displayException (e :: IOException))
 | 
			
		||||
| 
						 | 
				
			
			@ -192,6 +191,7 @@ maxEntryAge = 600
 | 
			
		|||
-- | Periodically iterate through cache, clean up expired entries and verify unverified ones
 | 
			
		||||
cacheVerifyThread :: LocalNodeStateSTM -> IO ()
 | 
			
		||||
cacheVerifyThread nsSTM = forever $ do
 | 
			
		||||
    putStrLn "cache verify run: begin"
 | 
			
		||||
    -- get cache
 | 
			
		||||
    (ns, cache) <- atomically $ do
 | 
			
		||||
        ns <- readTVar nsSTM
 | 
			
		||||
| 
						 | 
				
			
			@ -239,10 +239,12 @@ cacheVerifyThread nsSTM = forever $ do
 | 
			
		|||
    let nodesToQuery targetID = case queryLocalCache latestNs latestCache (lNumBestNodes latestNs) targetID of
 | 
			
		||||
                                  FOUND node -> [node]
 | 
			
		||||
                                  FORWARD nodeSet -> remoteNode <$> Set.elems nodeSet
 | 
			
		||||
    print $ checkCacheSliceInvariants latestNs latestCache
 | 
			
		||||
    forM_ (checkCacheSliceInvariants latestNs latestCache) (\targetID ->
 | 
			
		||||
        forkIO $ sendQueryIdMessages targetID latestNs (Just (1 + jEntriesPerSlice latestNs)) (nodesToQuery targetID) >> pure () -- ask for 1 entry more than j because of querying the middle
 | 
			
		||||
                                                             )
 | 
			
		||||
    
 | 
			
		||||
    putStrLn "cache verify run: end"
 | 
			
		||||
    threadDelay $ 10^6 * round maxEntryAge `div` 20
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
| 
						 | 
				
			
			@ -309,6 +311,8 @@ stabiliseThread :: LocalNodeStateSTM -> IO ()
 | 
			
		|||
stabiliseThread nsSTM = forever $ do
 | 
			
		||||
    ns <- readTVarIO nsSTM
 | 
			
		||||
 | 
			
		||||
    putStrLn "stabilise run: begin"
 | 
			
		||||
 | 
			
		||||
    -- iterate through the same snapshot, collect potential new neighbours
 | 
			
		||||
    -- and nodes to be deleted, and modify these changes only at the end of
 | 
			
		||||
    -- each stabilise run.
 | 
			
		||||
| 
						 | 
				
			
			@ -356,6 +360,7 @@ stabiliseThread nsSTM = forever $ do
 | 
			
		|||
            writeTVar nsSTM $ addSuccessors [nextEntry] latestNs
 | 
			
		||||
                                                                     )
 | 
			
		||||
 | 
			
		||||
    putStrLn "stabilise run: end"
 | 
			
		||||
    -- TODO: make delay configurable
 | 
			
		||||
    threadDelay (60 * 10^6)
 | 
			
		||||
  where
 | 
			
		||||
| 
						 | 
				
			
			@ -420,6 +425,7 @@ sendThread sock sendQ = forever $ do
 | 
			
		|||
-- | Sets up and manages the main server threads of FediChord
 | 
			
		||||
fediMainThreads :: Socket -> LocalNodeStateSTM -> IO ()
 | 
			
		||||
fediMainThreads sock nsSTM = do
 | 
			
		||||
    (\x -> putStrLn $ "launching threads, ns: " <> show x) =<< readTVarIO nsSTM
 | 
			
		||||
    sendQ <- newTQueueIO
 | 
			
		||||
    recvQ <- newTQueueIO
 | 
			
		||||
    -- concurrently launch all handler threads, if one of them throws an exception
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -80,6 +80,8 @@ import qualified Network.ByteOrder             as NetworkBytes
 | 
			
		|||
 | 
			
		||||
import           Hash2Pub.Utils
 | 
			
		||||
 | 
			
		||||
import           Debug.Trace                   (trace)
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
-- define protocol constants
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue