Compare commits

..

No commits in common. "0e6f126b3ba69f8211b7135bbdce3afdd0b63c2e" and "84bcd676ae76730c178b2885ae0aa91f4d774d70" have entirely different histories.

12 changed files with 235 additions and 267 deletions

View file

@ -1,8 +0,0 @@
- group: {name: generalise, enabled: true}
- warn: { name: Use DerivingStrategies }
- error: { lhs: return, rhs: pure }
- ignore: {name: "Avoid lambda using `infix`"}

View file

@ -23,7 +23,6 @@ in
haddock haddock
cabal-install cabal-install
hlint hlint
stylish-haskell
pkgs.python3Packages.asn1ate pkgs.python3Packages.asn1ate
]; ];
}; };

View file

@ -1,9 +1,9 @@
import Hash2Pub.FediChord
import Data.Map.Internal.Debug (showTree) import Data.Map.Internal.Debug (showTree)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Hash2Pub.FediChord
giebMalCache :: [Integer] -> Map.Map NodeID () giebMalCache :: [Integer] -> Map.Map NodeID ()
giebMalCache = Map.fromList . fmap (mkCacheEntry . fromInteger) giebMalCache = Map.fromList . map (mkCacheEntry . fromInteger)
where where
mkCacheEntry nodeid = (nodeid, ()) mkCacheEntry nodeid = (nodeid, ())
@ -22,7 +22,7 @@ edgeCase1 = do
putStrLn "\nWhile (NodeID 2^255+2^254+3) > (NodeID 2^254 + 14) …" putStrLn "\nWhile (NodeID 2^255+2^254+3) > (NodeID 2^254 + 14) …"
print $ toNodeID (2^255+2^254+3) > toNodeID (2^254+14) print $ toNodeID (2^255+2^254+3) > toNodeID (2^254+14)
putStrLn "… and 2^255+2^254+3 is an element of the map…" putStrLn "… and 2^255+2^254+3 is an element of the map…"
print $ Map.member (fromInteger (2^255+2^254+3)) testOverlap print $ Map.member (fromInteger 2^255+2^254+3) testOverlap
putStrLn "… looking for an element larger than 2^254 + 14 doesn't yield any." putStrLn "… looking for an element larger than 2^254 + 14 doesn't yield any."
print $ nidLookupGT testOverlap (2^254+14) print $ nidLookupGT testOverlap (2^254+14)
putStrLn "\nThat's the tree of the map:" putStrLn "\nThat's the tree of the map:"

View file

@ -2,18 +2,18 @@
module Hash2Pub.ASN1Coding where module Hash2Pub.ASN1Coding where
import Control.Exception (displayException) import Data.ASN1.Encoding -- asn1-encoding package
import Data.ASN1.BinaryEncoding -- asn1-encoding package import Data.ASN1.BinaryEncoding
import Data.ASN1.Encoding import Data.ASN1.Error()
import Data.ASN1.Error () import Data.ASN1.Types -- asn1-types package
import Data.ASN1.Parse import Data.ASN1.Parse
import Data.ASN1.Types import Data.Maybe (fromMaybe, mapMaybe, isNothing)
import Data.Bifunctor (first) import Data.Time.Clock.POSIX()
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, isNothing, mapMaybe)
import qualified Data.Set as Set import qualified Data.Set as Set
import Data.Time.Clock.POSIX () import qualified Data.Map.Strict as Map
import Data.Bifunctor (first)
import Control.Exception (displayException)
import Safe import Safe
import Hash2Pub.FediChord import Hash2Pub.FediChord
@ -110,7 +110,7 @@ serialiseMessage maxBytesLength msg =
payloadParts i = zip [1..] . splitPayload i <$> actionPayload payloadParts i = zip [1..] . splitPayload i <$> actionPayload
actionPayload = payload msg actionPayload = payload msg
encodedMsgs i = Map.map encodeMsg $ messageParts i encodedMsgs i = Map.map encodeMsg $ messageParts i
maxMsgLength = maximum . fmap BS.length . Map.elems maxMsgLength = maximum . map BS.length . Map.elems
-- | encode a 'FediChordMessage' to a bytestring without further modification -- | encode a 'FediChordMessage' to a bytestring without further modification
encodeMsg :: FediChordMessage -> BS.ByteString encodeMsg :: FediChordMessage -> BS.ByteString
@ -130,21 +130,21 @@ encodePayload LeaveResponsePayload = [Null]
encodePayload payload'@LeaveRequestPayload{} = encodePayload payload'@LeaveRequestPayload{} =
Start Sequence Start Sequence
: Start Sequence : Start Sequence
: fmap (IntVal . getNodeID) (leaveSuccessors payload') : map (IntVal . getNodeID) (leaveSuccessors payload')
<> [End Sequence ++ [End Sequence
, Start Sequence] , Start Sequence]
<> fmap (IntVal . getNodeID) (leavePredecessors payload') ++ map (IntVal . getNodeID) (leavePredecessors payload')
<> [End Sequence ++ [End Sequence
, End Sequence] , End Sequence]
-- currently StabiliseResponsePayload and LeaveRequestPayload are equal -- currently StabiliseResponsePayload and LeaveRequestPayload are equal
encodePayload payload'@StabiliseResponsePayload{} = encodePayload payload'@StabiliseResponsePayload{} =
Start Sequence Start Sequence
: Start Sequence : Start Sequence
: fmap (IntVal . getNodeID) (stabiliseSuccessors payload') : map (IntVal . getNodeID) (stabiliseSuccessors payload')
<> [End Sequence ++ [End Sequence
, Start Sequence] , Start Sequence]
<> fmap (IntVal . getNodeID) (stabilisePredecessors payload') ++ map (IntVal . getNodeID) (stabilisePredecessors payload')
<> [End Sequence ++ [End Sequence
, End Sequence] , End Sequence]
encodePayload payload'@StabiliseRequestPayload = [Null] encodePayload payload'@StabiliseRequestPayload = [Null]
encodePayload payload'@QueryIDResponsePayload{} = encodePayload payload'@QueryIDResponsePayload{} =
@ -154,12 +154,12 @@ encodePayload payload'@QueryIDResponsePayload{} =
Start Sequence Start Sequence
: encodeQueryResult resp : encodeQueryResult resp
: case resp of : case resp of
FOUND ns -> encodeNodeState ns FOUND ns -> encodeNodeState $ ns
FORWARD entrySet -> FORWARD entrySet ->
Start Sequence Start Sequence
: (concatMap encodeCacheEntry . Set.elems $ entrySet) : (concatMap encodeCacheEntry . Set.elems $ entrySet)
<> [End Sequence] ++ [End Sequence]
<> [End Sequence] ++ [End Sequence]
encodePayload payload'@QueryIDRequestPayload{} = [ encodePayload payload'@QueryIDRequestPayload{} = [
Start Sequence Start Sequence
, IntVal . getNodeID $ queryTargetID payload' , IntVal . getNodeID $ queryTargetID payload'
@ -170,21 +170,21 @@ encodePayload payload'@QueryIDRequestPayload{} = [
encodePayload payload'@JoinResponsePayload{} = encodePayload payload'@JoinResponsePayload{} =
Start Sequence Start Sequence
: Start Sequence : Start Sequence
: fmap (IntVal . getNodeID) (joinSuccessors payload') : map (IntVal . getNodeID) (joinSuccessors payload')
<> [End Sequence ++ [End Sequence
, Start Sequence] , Start Sequence]
<> fmap (IntVal . getNodeID) (joinPredecessors payload') ++ map (IntVal . getNodeID) (joinPredecessors payload')
<> [End Sequence ++ [End Sequence
, Start Sequence] , Start Sequence]
<> concatMap encodeCacheEntry (joinCache payload') ++ concatMap encodeCacheEntry (joinCache payload')
<> [End Sequence ++ [End Sequence
, End Sequence] , End Sequence]
encodePayload payload'@JoinRequestPayload{} = [Null] encodePayload payload'@JoinRequestPayload{} = [Null]
encodePayload PingRequestPayload{} = [Null] encodePayload PingRequestPayload{} = [Null]
encodePayload payload'@PingResponsePayload{} = encodePayload payload'@PingResponsePayload{} =
Start Sequence Start Sequence
: concatMap encodeNodeState (pingNodeStates payload') : concatMap encodeNodeState (pingNodeStates payload')
<> [End Sequence] ++ [End Sequence]
encodeNodeState :: NodeState -> [ASN1] encodeNodeState :: NodeState -> [ASN1]
encodeNodeState ns = [ encodeNodeState ns = [
@ -203,7 +203,7 @@ encodeCacheEntry (RemoteCacheEntry ns timestamp) =
Start Sequence Start Sequence
: encodeNodeState ns : encodeNodeState ns
-- ToDo: possibly optimise this by using dlists -- ToDo: possibly optimise this by using dlists
<> [ ++ [
IntVal . fromIntegral . fromEnum $ timestamp IntVal . fromIntegral . fromEnum $ timestamp
, End Sequence] , End Sequence]
encodeCacheEntry _ = [] encodeCacheEntry _ = []
@ -221,11 +221,11 @@ encodeMessage
: (Enumerated . fromIntegral . fromEnum $ action) : (Enumerated . fromIntegral . fromEnum $ action)
: IntVal requestID : IntVal requestID
: encodeNodeState sender : encodeNodeState sender
<> [ ++ [
IntVal parts IntVal parts
, IntVal part ] , IntVal part ]
<> maybe [] encodePayload requestPayload ++ maybe [] encodePayload requestPayload
<> [End Sequence] ++ [End Sequence]
encodeMessage encodeMessage
(Response responseTo senderID parts part action responsePayload) = [ (Response responseTo senderID parts part action responsePayload) = [
Start Sequence Start Sequence
@ -234,8 +234,8 @@ encodeMessage
, IntVal parts , IntVal parts
, IntVal part , IntVal part
, Enumerated . fromIntegral . fromEnum $ action] , Enumerated . fromIntegral . fromEnum $ action]
<> maybe [] encodePayload responsePayload ++ maybe [] encodePayload responsePayload
<> [End Sequence] ++ [End Sequence]
-- ===== parser combinators ===== -- ===== parser combinators =====
@ -243,21 +243,21 @@ parseMessage :: ParseASN1 FediChordMessage
parseMessage = do parseMessage = do
begin <- getNext begin <- getNext
case begin of case begin of
Start Sequence -> pure () Start Sequence -> return ()
x -> throwParseError $ "unexpected ASN.1 element " <> show x x -> throwParseError $ "unexpected ASN.1 element " ++ show x
-- request and response messages are distiguishable by their structure, -- request and response messages are distiguishable by their structure,
-- see ASN.1 schema -- see ASN.1 schema
firstElem <- getNext firstElem <- getNext
message <- case firstElem of message <- case firstElem of
Enumerated a -> parseRequest . toEnum . fromIntegral $ a Enumerated a -> parseRequest . toEnum . fromIntegral $ a
IntVal i -> parseResponse i IntVal i -> parseResponse i
other -> throwParseError $ "unexpected first ASN1 element: " <> show other other -> throwParseError $ "unexpected first ASN1 element: " ++ show other
-- consume sequence end -- consume sequence end
end <- getNext end <- getNext
case end of case end of
End Sequence -> pure () End Sequence -> return ()
x -> throwParseError $ "unexpected ASN.1 element " <> show x x -> throwParseError $ "unexpected ASN.1 element " ++ show x
pure message return message
@ -268,14 +268,14 @@ parseRequest action = do
parts <- parseInteger parts <- parseInteger
part <- parseInteger part <- parseInteger
hasPayload <- hasNext hasPayload <- hasNext
payload <- if not hasPayload then pure Nothing else Just <$> case action of payload <- if not hasPayload then return Nothing else Just <$> case action of
QueryID -> parseQueryIDRequest QueryID -> parseQueryIDRequest
Join -> parseJoinRequest Join -> parseJoinRequest
Leave -> parseLeaveRequest Leave -> parseLeaveRequest
Stabilise -> parseStabiliseRequest Stabilise -> parseStabiliseRequest
Ping -> parsePingRequest Ping -> parsePingRequest
pure $ Request requestID sender parts part action payload return $ Request requestID sender parts part action payload
parseResponse :: Integer -> ParseASN1 FediChordMessage parseResponse :: Integer -> ParseASN1 FediChordMessage
parseResponse responseTo = do parseResponse responseTo = do
@ -284,49 +284,49 @@ parseResponse responseTo = do
part <- parseInteger part <- parseInteger
action <- parseEnum :: ParseASN1 Action action <- parseEnum :: ParseASN1 Action
hasPayload <- hasNext hasPayload <- hasNext
payload <- if not hasPayload then pure Nothing else Just <$> case action of payload <- if not hasPayload then return Nothing else Just <$> case action of
QueryID -> parseQueryIDResponse QueryID -> parseQueryIDResponse
Join -> parseJoinResponse Join -> parseJoinResponse
Leave -> parseLeaveResponse Leave -> parseLeaveResponse
Stabilise -> parseStabiliseResponse Stabilise -> parseStabiliseResponse
Ping -> parsePingResponse Ping -> parsePingResponse
pure $ Response responseTo senderID parts part action payload return $ Response responseTo senderID parts part action payload
parseInteger :: ParseASN1 Integer parseInteger :: ParseASN1 Integer
parseInteger = do parseInteger = do
i <- getNext i <- getNext
case i of case i of
IntVal parsed -> pure parsed IntVal parsed -> return parsed
x -> throwParseError $ "Expected IntVal but got " <> show x x -> throwParseError $ "Expected IntVal but got " ++ show x
parseEnum :: Enum a => ParseASN1 a parseEnum :: Enum a => ParseASN1 a
parseEnum = do parseEnum = do
e <- getNext e <- getNext
case e of case e of
Enumerated en -> pure $ toEnum . fromIntegral $ en Enumerated en -> return $ toEnum . fromIntegral $ en
x -> throwParseError $ "Expected Enumerated but got " <> show x x -> throwParseError $ "Expected Enumerated but got " ++ show x
parseString :: ParseASN1 String parseString :: ParseASN1 String
parseString = do parseString = do
s <- getNext s <- getNext
case s of case s of
ASN1String toBeParsed -> maybe (throwParseError "string parsing failed") pure $ asn1CharacterToString toBeParsed ASN1String toBeParsed -> maybe (throwParseError "string parsing failed") return $ asn1CharacterToString toBeParsed
x -> throwParseError $ "Expected a ASN1String but got " <> show x x -> throwParseError $ "Expected a ASN1String but got " ++ show x
parseOctets :: ParseASN1 BS.ByteString parseOctets :: ParseASN1 BS.ByteString
parseOctets = do parseOctets = do
os <- getNext os <- getNext
case os of case os of
OctetString bs -> pure bs OctetString bs -> return bs
x -> throwParseError $ "Expected an OctetString but got " <> show x x -> throwParseError $ "Expected an OctetString but got " ++ show x
parseNull :: ParseASN1 () parseNull :: ParseASN1 ()
parseNull = do parseNull = do
n <- getNext n <- getNext
case n of case n of
Null -> pure () Null -> return ()
x -> throwParseError $ "Expected Null but got " <> show x x -> throwParseError $ "Expected Null but got " ++ show x
parseNodeState :: ParseASN1 NodeState parseNodeState :: ParseASN1 NodeState
parseNodeState = onNextContainer Sequence $ do parseNodeState = onNextContainer Sequence $ do
@ -336,7 +336,7 @@ parseNodeState = onNextContainer Sequence $ do
dhtPort' <- fromInteger <$> parseInteger dhtPort' <- fromInteger <$> parseInteger
apPort' <- fromInteger <$> parseInteger apPort' <- fromInteger <$> parseInteger
vServer' <- parseInteger vServer' <- parseInteger
pure NodeState { return NodeState {
nid = nid' nid = nid'
, domain = domain' , domain = domain'
, dhtPort = dhtPort' , dhtPort = dhtPort'
@ -351,7 +351,7 @@ parseCacheEntry :: ParseASN1 RemoteCacheEntry
parseCacheEntry = onNextContainer Sequence $ do parseCacheEntry = onNextContainer Sequence $ do
node <- parseNodeState node <- parseNodeState
timestamp <- toEnum . fromIntegral <$> parseInteger timestamp <- toEnum . fromIntegral <$> parseInteger
pure $ RemoteCacheEntry node timestamp return $ RemoteCacheEntry node timestamp
parseNodeCache :: ParseASN1 [RemoteCacheEntry] parseNodeCache :: ParseASN1 [RemoteCacheEntry]
parseNodeCache = onNextContainer Sequence $ getMany parseCacheEntry parseNodeCache = onNextContainer Sequence $ getMany parseCacheEntry
@ -359,14 +359,14 @@ parseNodeCache = onNextContainer Sequence $ getMany parseCacheEntry
parseJoinRequest :: ParseASN1 ActionPayload parseJoinRequest :: ParseASN1 ActionPayload
parseJoinRequest = do parseJoinRequest = do
parseNull parseNull
pure JoinRequestPayload return JoinRequestPayload
parseJoinResponse :: ParseASN1 ActionPayload parseJoinResponse :: ParseASN1 ActionPayload
parseJoinResponse = onNextContainer Sequence $ do parseJoinResponse = onNextContainer Sequence $ do
succ' <- fmap fromInteger <$> onNextContainer Sequence (getMany parseInteger) succ' <- map fromInteger <$> onNextContainer Sequence (getMany parseInteger)
pred' <- fmap fromInteger <$> onNextContainer Sequence (getMany parseInteger) pred' <- map fromInteger <$> onNextContainer Sequence (getMany parseInteger)
cache <- parseNodeCache cache <- parseNodeCache
pure $ JoinResponsePayload { return $ JoinResponsePayload {
joinSuccessors = succ' joinSuccessors = succ'
, joinPredecessors = pred' , joinPredecessors = pred'
, joinCache = cache , joinCache = cache
@ -376,7 +376,7 @@ parseQueryIDRequest :: ParseASN1 ActionPayload
parseQueryIDRequest = onNextContainer Sequence $ do parseQueryIDRequest = onNextContainer Sequence $ do
targetID <- fromInteger <$> parseInteger targetID <- fromInteger <$> parseInteger
lBestNodes <- parseInteger lBestNodes <- parseInteger
pure $ QueryIDRequestPayload { return $ QueryIDRequestPayload {
queryTargetID = targetID queryTargetID = targetID
, queryLBestNodes = lBestNodes , queryLBestNodes = lBestNodes
} }
@ -388,29 +388,29 @@ parseQueryIDResponse = onNextContainer Sequence $ do
0 -> FOUND <$> parseNodeState 0 -> FOUND <$> parseNodeState
1 -> FORWARD . Set.fromList <$> parseNodeCache 1 -> FORWARD . Set.fromList <$> parseNodeCache
_ -> throwParseError "invalid QueryIDResponse type" _ -> throwParseError "invalid QueryIDResponse type"
pure $ QueryIDResponsePayload { return $ QueryIDResponsePayload {
queryResult = result queryResult = result
} }
parseStabiliseRequest :: ParseASN1 ActionPayload parseStabiliseRequest :: ParseASN1 ActionPayload
parseStabiliseRequest = do parseStabiliseRequest = do
parseNull parseNull
pure StabiliseRequestPayload return StabiliseRequestPayload
parseStabiliseResponse :: ParseASN1 ActionPayload parseStabiliseResponse :: ParseASN1 ActionPayload
parseStabiliseResponse = onNextContainer Sequence $ do parseStabiliseResponse = onNextContainer Sequence $ do
succ' <- fmap fromInteger <$> onNextContainer Sequence (getMany parseInteger) succ' <- map fromInteger <$> onNextContainer Sequence (getMany parseInteger)
pred' <- fmap fromInteger <$> onNextContainer Sequence (getMany parseInteger) pred' <- map fromInteger <$> onNextContainer Sequence (getMany parseInteger)
pure $ StabiliseResponsePayload { return $ StabiliseResponsePayload {
stabiliseSuccessors = succ' stabiliseSuccessors = succ'
, stabilisePredecessors = pred' , stabilisePredecessors = pred'
} }
parseLeaveRequest :: ParseASN1 ActionPayload parseLeaveRequest :: ParseASN1 ActionPayload
parseLeaveRequest = onNextContainer Sequence $ do parseLeaveRequest = onNextContainer Sequence $ do
succ' <- fmap fromInteger <$> onNextContainer Sequence (getMany parseInteger) succ' <- map fromInteger <$> onNextContainer Sequence (getMany parseInteger)
pred' <- fmap fromInteger <$> onNextContainer Sequence (getMany parseInteger) pred' <- map fromInteger <$> onNextContainer Sequence (getMany parseInteger)
pure $ LeaveRequestPayload { return $ LeaveRequestPayload {
leaveSuccessors = succ' leaveSuccessors = succ'
, leavePredecessors = pred' , leavePredecessors = pred'
} }
@ -418,16 +418,16 @@ parseLeaveRequest = onNextContainer Sequence $ do
parseLeaveResponse :: ParseASN1 ActionPayload parseLeaveResponse :: ParseASN1 ActionPayload
parseLeaveResponse = do parseLeaveResponse = do
parseNull parseNull
pure LeaveResponsePayload return LeaveResponsePayload
parsePingRequest :: ParseASN1 ActionPayload parsePingRequest :: ParseASN1 ActionPayload
parsePingRequest = do parsePingRequest = do
parseNull parseNull
pure PingRequestPayload return PingRequestPayload
parsePingResponse :: ParseASN1 ActionPayload parsePingResponse :: ParseASN1 ActionPayload
parsePingResponse = onNextContainer Sequence $ do parsePingResponse = onNextContainer Sequence $ do
handledNodes <- getMany parseNodeState handledNodes <- getMany parseNodeState
pure $ PingResponsePayload { return $ PingResponsePayload {
pingNodeStates = handledNodes pingNodeStates = handledNodes
} }

View file

@ -1,3 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
module Hash2Pub.DHTProtocol module Hash2Pub.DHTProtocol
( QueryResponse (..) ( QueryResponse (..)
, queryLocalCache , queryLocalCache
@ -15,26 +17,36 @@ module Hash2Pub.DHTProtocol
) )
where where
import Data.Maybe (maybe, fromMaybe)
import qualified Data.Set as Set
import qualified Data.Map as Map
import qualified Data.ByteString as BS
import Data.Time.Clock.POSIX
import Network.Socket hiding (send, sendTo, recv, recvFrom)
import Network.Socket.ByteString
import System.Timeout
import Control.Monad.State.Strict
import Control.Concurrent.STM import Control.Concurrent.STM
import Control.Concurrent.STM.TQueue import Control.Concurrent.STM.TQueue
import Control.Concurrent.STM.TBQueue import Control.Concurrent.STM.TBQueue
import qualified Data.ByteString as BS
import qualified Data.Map as Map import Hash2Pub.FediChord
import Data.Maybe (fromMaybe, maybe) ( NodeID
import qualified Data.Set as Set , NodeState (..)
import Data.Time.Clock.POSIX , getSuccessors
import Network.Socket hiding (recv, recvFrom, send, sendTo) , putSuccessors
import Network.Socket.ByteString , getPredecessors
import System.Timeout , putPredecessors
, cacheGetNodeStateUnvalidated
, NodeCache
, CacheEntry(..)
, cacheLookup
, cacheLookupSucc
, cacheLookupPred
, localCompare
)
import Hash2Pub.ASN1Coding import Hash2Pub.ASN1Coding
import Hash2Pub.FediChord (CacheEntry (..), NodeCache, NodeID,
NodeState (..),
cacheGetNodeStateUnvalidated,
cacheLookup, cacheLookupPred,
cacheLookupSucc, getPredecessors,
getSuccessors, localCompare,
putPredecessors, putSuccessors)
import Hash2Pub.ProtocolTypes import Hash2Pub.ProtocolTypes
import Debug.Trace (trace) import Debug.Trace (trace)
@ -79,7 +91,7 @@ addCacheEntry :: RemoteCacheEntry -- ^ a remote cache entry received from netw
-> IO NodeCache -- ^ new node cache with the element inserted -> IO NodeCache -- ^ new node cache with the element inserted
addCacheEntry entry cache = do addCacheEntry entry cache = do
now <- getPOSIXTime now <- getPOSIXTime
pure $ addCacheEntryPure now entry cache return $ addCacheEntryPure now entry cache
-- | pure version of 'addCacheEntry' with current time explicitly specified as argument -- | pure version of 'addCacheEntry' with current time explicitly specified as argument
addCacheEntryPure :: POSIXTime -- ^ current time addCacheEntryPure :: POSIXTime -- ^ current time
@ -169,9 +181,9 @@ sendRequestTo timeout attempts msg sock = do
attempts :: Int -- ^ number of retries *i* attempts :: Int -- ^ number of retries *i*
-> IO (Maybe a) -- ^ action to retry -> IO (Maybe a) -- ^ action to retry
-> IO (Maybe a) -- ^ result after at most *i* retries -> IO (Maybe a) -- ^ result after at most *i* retries
attempts 0 _ = pure Nothing attempts 0 _ = return Nothing
attempts i action = do attempts i action = do
actionResult <- action actionResult <- action
case actionResult of case actionResult of
Nothing -> attempts (i-1) action Nothing -> attempts (i-1) action
Just res -> pure $ Just res Just res -> return $ Just res

View file

@ -1,6 +1,4 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE GeneralizedNewtypeDeriving, DataKinds, OverloadedStrings #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{- | {- |
Module : FediChord Module : FediChord
Description : An opinionated implementation of the EpiChord DHT by Leong et al. Description : An opinionated implementation of the EpiChord DHT by Leong et al.
@ -47,26 +45,25 @@ module Hash2Pub.FediChord (
, cacheWriter , cacheWriter
) where ) where
import Control.Exception
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, isJust, mapMaybe)
import Data.Time.Clock.POSIX
import Network.Socket import Network.Socket
import Data.Time.Clock.POSIX
import Control.Exception
import Data.Maybe (isJust, fromMaybe, mapMaybe)
-- for hashing and ID conversion -- for hashing and ID conversion
import Crypto.Hash
import Data.Word
import qualified Data.ByteString as BS
import qualified Data.ByteString.UTF8 as BSU
import qualified Data.ByteArray as BA
import qualified Network.ByteOrder as NetworkBytes
import Data.IP (IPv6, fromHostAddress6, toHostAddress6)
import Data.IORef
import Control.Concurrent.STM import Control.Concurrent.STM
import Control.Concurrent.STM.TQueue import Control.Concurrent.STM.TQueue
import Control.Monad (forever) import Control.Monad (forever)
import Crypto.Hash import Data.Typeable (Typeable(..), typeOf)
import qualified Data.ByteArray as BA
import qualified Data.ByteString as BS
import qualified Data.ByteString.UTF8 as BSU
import Data.IORef
import Data.IP (IPv6, fromHostAddress6,
toHostAddress6)
import Data.Typeable (Typeable (..), typeOf)
import Data.Word
import qualified Network.ByteOrder as NetworkBytes
import Hash2Pub.Utils import Hash2Pub.Utils
@ -283,12 +280,12 @@ lookupWrapper :: (NodeID -> NodeCache -> Maybe (NodeID, CacheEntry)) -> (NodeID
lookupWrapper f fRepeat direction key cache = lookupWrapper f fRepeat direction key cache =
case f key cache of case f key cache of
-- the proxy entry found holds a -- the proxy entry found holds a
Just (_, ProxyEntry _ (Just entry@NodeEntry{})) -> Just entry Just (_, (ProxyEntry _ (Just entry@NodeEntry{}))) -> Just entry
-- proxy entry holds another proxy entry, this should not happen -- proxy entry holds another proxy entry, this should not happen
Just (_, ProxyEntry _ (Just (ProxyEntry _ _))) -> Nothing Just (_, (ProxyEntry _ (Just (ProxyEntry _ _)))) -> Nothing
-- proxy entry without own entry is a pointer on where to continue -- proxy entry without own entry is a pointer on where to continue
-- if lookup direction is the same as pointer direction: follow pointer -- if lookup direction is the same as pointer direction: follow pointer
Just (foundKey, ProxyEntry (pointerID, pointerDirection) Nothing) -> Just (foundKey, (ProxyEntry (pointerID, pointerDirection) Nothing)) ->
let newKey = if pointerDirection == direction let newKey = if pointerDirection == direction
then pointerID then pointerID
else foundKey + (fromInteger . toInteger . fromEnum $ direction) else foundKey + (fromInteger . toInteger . fromEnum $ direction)
@ -325,17 +322,17 @@ cacheLookupPred = lookupWrapper Map.lookupLT Map.lookupLE Backwards
cacheGetNodeStateUnvalidated :: CacheEntry -> NodeState cacheGetNodeStateUnvalidated :: CacheEntry -> NodeState
cacheGetNodeStateUnvalidated (NodeEntry _ nState _) = nState cacheGetNodeStateUnvalidated (NodeEntry _ nState _) = nState
cacheGetNodeStateUnvalidated (ProxyEntry _ (Just entry)) = cacheGetNodeStateUnvalidated entry cacheGetNodeStateUnvalidated (ProxyEntry _ (Just entry)) = cacheGetNodeStateUnvalidated entry
cacheGetNodeStateUnvalidated _ = error "trying to pure empty node state, please report a bug" cacheGetNodeStateUnvalidated _ = error "trying to return empty node state, please report a bug"
-- | converts a 'HostAddress6' IP address to a big-endian strict ByteString -- | converts a 'HostAddress6' IP address to a big-endian strict ByteString
ipAddrAsBS :: HostAddress6 -> BS.ByteString ipAddrAsBS :: HostAddress6 -> BS.ByteString
ipAddrAsBS (a, b, c, d) = mconcat $ fmap NetworkBytes.bytestring32 [a, b, c, d] ipAddrAsBS (a, b, c, d) = mconcat $ map NetworkBytes.bytestring32 [a, b, c, d]
-- | converts a ByteString in big endian order to an IPv6 address 'HostAddress6' -- | converts a ByteString in big endian order to an IPv6 address 'HostAddress6'
bsAsIpAddr :: BS.ByteString -> HostAddress6 bsAsIpAddr :: BS.ByteString -> HostAddress6
bsAsIpAddr bytes = (a,b,c,d) bsAsIpAddr bytes = (a,b,c,d)
where where
a:b:c:d:_ = fmap NetworkBytes.word32 . chunkBytes 4 $ bytes a:b:c:d:_ = map NetworkBytes.word32 . chunkBytes 4 $ bytes
-- | generates a 256 bit long NodeID using SHAKE128, represented as ByteString -- | generates a 256 bit long NodeID using SHAKE128, represented as ByteString
@ -347,7 +344,7 @@ genNodeIDBS ip nodeDomain vserver =
hashIpaddrUpper `BS.append` hashID nodeDomain' `BS.append` hashIpaddLower hashIpaddrUpper `BS.append` hashID nodeDomain' `BS.append` hashIpaddLower
where where
vsBS = BS.pack [vserver] -- attention: only works for vserver IDs up to 255 vsBS = BS.pack [vserver] -- attention: only works for vserver IDs up to 255
ipaddrNet = BS.take 8 (ipAddrAsBS ip) `BS.append` vsBS ipaddrNet = (BS.take 8 $ ipAddrAsBS ip) `BS.append` vsBS
nodeDomain' = BSU.fromString nodeDomain `BS.append` vsBS nodeDomain' = BSU.fromString nodeDomain `BS.append` vsBS
hashID bstr = BS.pack . BA.unpack $ (hash bstr :: Digest (SHAKE128 128)) hashID bstr = BS.pack . BA.unpack $ (hash bstr :: Digest (SHAKE128 128))
(hashIpaddrUpper, hashIpaddLower) = BS.splitAt 64 $ hashID ipaddrNet (hashIpaddrUpper, hashIpaddLower) = BS.splitAt 64 $ hashID ipaddrNet
@ -394,7 +391,7 @@ byteStringToUInteger bs = sum $ parsedBytes 0 bs
--checkCacheSlices :: NodeState -> IO [()] --checkCacheSlices :: NodeState -> IO [()]
--checkCacheSlices state = case getNodeCache state of --checkCacheSlices state = case getNodeCache state of
-- -- don't do anything on nodes without a cache -- -- don't do anything on nodes without a cache
-- Nothing -> pure [()] -- Nothing -> return [()]
-- Just cache' -> checkSlice jEntries (nid state) startBound lastSucc =<< readIORef cache' -- Just cache' -> checkSlice jEntries (nid state) startBound lastSucc =<< readIORef cache'
-- -- TODO: do the same for predecessors -- -- TODO: do the same for predecessors
-- where -- where
@ -418,10 +415,10 @@ byteStringToUInteger bs = sum $ parsedBytes 0 bs
-- -- TODO: replace empty IO actions with actual lookups to middle of slice -- -- TODO: replace empty IO actions with actual lookups to middle of slice
-- -- TODO: validate ID before adding to cache -- -- TODO: validate ID before adding to cache
-- case Map.lookupLT upperBound cache of -- case Map.lookupLT upperBound cache of
-- Nothing -> pure () : checkSlice j ownID lowerBound (Just lastSuccNode) cache -- Nothing -> return () : checkSlice j ownID lowerBound (Just lastSuccNode) cache
-- Just (matchID, _) -> -- Just (matchID, _) ->
-- if -- if
-- matchID <= lowerBound then pure () : checkSlice j ownID lowerBound (Just lastSuccNode) cache -- matchID <= lowerBound then return () : checkSlice j ownID lowerBound (Just lastSuccNode) cache
-- else -- else
-- checkSlice j ownID lowerBound (Just lastSuccNode) cache -- checkSlice j ownID lowerBound (Just lastSuccNode) cache
@ -442,7 +439,7 @@ fediChordInit :: FediChordConf -> IO (Socket, NodeState)
fediChordInit conf = do fediChordInit conf = do
initialState <- nodeStateInit conf initialState <- nodeStateInit conf
serverSock <- mkServerSocket (ipAddr initialState) (dhtPort initialState) serverSock <- mkServerSocket (ipAddr initialState) (dhtPort initialState)
pure (serverSock, initialState) return (serverSock, initialState)
-- | initialises the 'NodeState' for this local node. -- | initialises the 'NodeState' for this local node.
-- Separated from 'fediChordInit' to be usable in tests. -- Separated from 'fediChordInit' to be usable in tests.
@ -470,7 +467,7 @@ nodeStateInit conf = do
, pNumParallelQueries = 2 , pNumParallelQueries = 2
, jEntriesPerSlice = 2 , jEntriesPerSlice = 2
} }
pure initialState return initialState
--fediChordJoin :: NodeState -- ^ the local 'NodeState' --fediChordJoin :: NodeState -- ^ the local 'NodeState'
-- -> (String, PortNumber) -- ^ domain and port of a bootstrapping node -- -> (String, PortNumber) -- ^ domain and port of a bootstrapping node
@ -489,13 +486,13 @@ cacheWriter :: NodeState -> IO ()
cacheWriter ns = do cacheWriter ns = do
let writeQueue' = getCacheWriteQueue ns let writeQueue' = getCacheWriteQueue ns
case writeQueue' of case writeQueue' of
Nothing -> pure () Nothing -> return ()
Just writeQueue -> forever $ do Just writeQueue -> forever $ do
f <- atomically $ readTQueue writeQueue f <- atomically $ readTQueue writeQueue
let let
refModifier :: NodeCache -> (NodeCache, ()) refModifier :: NodeCache -> (NodeCache, ())
refModifier nc = (f nc, ()) refModifier nc = (f nc, ())
maybe (pure ()) ( maybe (return ()) (
\ref -> atomicModifyIORef' ref refModifier \ref -> atomicModifyIORef' ref refModifier
) $ getNodeCacheRef ns ) $ getNodeCacheRef ns
@ -521,7 +518,7 @@ mkServerSocket ip port = do
sock <- socket AF_INET6 Datagram defaultProtocol sock <- socket AF_INET6 Datagram defaultProtocol
setSocketOption sock IPv6Only 1 setSocketOption sock IPv6Only 1
bind sock sockAddr bind sock sockAddr
pure sock return sock
-- | create a UDP datagram socket, connected to a destination. -- | create a UDP datagram socket, connected to a destination.
-- The socket gets an arbitrary free local port assigned. -- The socket gets an arbitrary free local port assigned.
@ -532,4 +529,4 @@ mkSendSocket dest destPort = do
destAddr <- addrAddress <$> resolve (Just dest) (Just destPort) destAddr <- addrAddress <$> resolve (Just dest) (Just destPort)
sendSock <- socket AF_INET6 Datagram defaultProtocol sendSock <- socket AF_INET6 Datagram defaultProtocol
setSocketOption sendSock IPv6Only 1 setSocketOption sendSock IPv6Only 1
pure sendSock return sendSock

View file

@ -1,8 +1,8 @@
module Main where module Main where
import Control.Concurrent
import Data.IP (IPv6, toHostAddress6)
import System.Environment import System.Environment
import Data.IP (IPv6, toHostAddress6) -- iproute, just for IPv6 string parsing
import Control.Concurrent
import Hash2Pub.FediChord import Hash2Pub.FediChord
@ -20,12 +20,12 @@ main = do
-- idea: list of bootstrapping nodes, try joining within a timeout -- idea: list of bootstrapping nodes, try joining within a timeout
-- stop main thread from terminating during development -- stop main thread from terminating during development
getChar getChar
pure () return ()
readConfig :: IO FediChordConf readConfig :: IO FediChordConf
readConfig = do readConfig = do
confDomainString : ipString : portString : _ <- getArgs confDomainString : ipString : portString : _ <- getArgs
pure $ FediChordConf { return $ FediChordConf {
confDomain = confDomainString confDomain = confDomainString
, confIP = toHostAddress6 . read $ ipString , confIP = toHostAddress6 . read $ ipString
, confDhtPort = read portString , confDhtPort = read portString

View file

@ -1,11 +1,11 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Main where module Main where
import qualified Data.ASN1.Encoding as ASN1 -- asn1-encoding package
import qualified Data.ASN1.BinaryEncoding as ASN1 import qualified Data.ASN1.BinaryEncoding as ASN1
import qualified Data.ASN1.Encoding as ASN1
import qualified Data.ASN1.Error as ASN1 import qualified Data.ASN1.Error as ASN1
import qualified Data.ASN1.Types as ASN1 -- asn1-types package
import qualified Data.ASN1.Parse as ASN1P import qualified Data.ASN1.Parse as ASN1P
import qualified Data.ASN1.Types as ASN1
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Debug.Trace (trace) import Debug.Trace (trace)
@ -14,7 +14,7 @@ import Debug.Trace (trace)
-- encoding values as ASN.1 types is done using Data.ASN1.Prim -- encoding values as ASN.1 types is done using Data.ASN1.Prim
someASN1 :: [ASN1.ASN1] someASN1 :: [ASN1.ASN1]
someASN1 = ASN1.Start ASN1.Sequence : ASN1.ASN1String (ASN1.asn1CharacterString ASN1.Visible domain) : ASN1.ASN1String (ASN1.asn1CharacterString ASN1.UTF8 unicode) : fmap ASN1.IntVal xs <> [ASN1.End ASN1.Sequence] someASN1 = ASN1.Start ASN1.Sequence : ASN1.ASN1String (ASN1.asn1CharacterString ASN1.Visible domain) : ASN1.ASN1String (ASN1.asn1CharacterString ASN1.UTF8 unicode) : map ASN1.IntVal xs ++ [ASN1.End ASN1.Sequence]
where where
domain = "domains.are.ascii.on.ly" domain = "domains.are.ascii.on.ly"
unicode = "Hähä, but unicode string!" unicode = "Hähä, but unicode string!"
@ -27,12 +27,12 @@ derToAsn1 :: BS.ByteString -> Either ASN1.ASN1Error [ASN1.ASN1]
derToAsn1 = ASN1.decodeASN1' ASN1.DER derToAsn1 = ASN1.decodeASN1' ASN1.DER
getUnicodeField :: [ASN1.ASN1] -> String getUnicodeField :: [ASN1.ASN1] -> String
getUnicodeField (ASN1.Start ASN1.Sequence : _ : ASN1.ASN1String strASN1 : _) = fromMaybe "" $ ASN1.asn1CharacterToString strASN1 getUnicodeField ((ASN1.Start ASN1.Sequence) : _ : (ASN1.ASN1String strASN1) : _) = fromMaybe "" $ ASN1.asn1CharacterToString strASN1
testParser :: ASN1P.ParseASN1 String testParser :: ASN1P.ParseASN1 String
testParser = do testParser = do
foo <- ASN1P.onNextContainer ASN1.Sequence getAll foo <- ASN1P.onNextContainer ASN1.Sequence getAll
pure $ show foo return $ show foo
getAll :: ASN1P.ParseASN1 [ASN1.ASN1] getAll :: ASN1P.ParseASN1 [ASN1.ASN1]
getAll = ASN1P.getMany ASN1P.getNext getAll = ASN1P.getMany ASN1P.getNext

View file

@ -1,32 +0,0 @@
#!/usr/bin/env bash
set -euo pipefail
function ls-source-files {
git ls-files "app/*.hs" "src/*.hs" "test/*.hs"
}
function check-git-status {
[ "$(git status -s '*.hs' | wc -l)" == "0" ]
}
function stylish {
stylish-haskell -i $(ls-source-files)
}
if check-git-status
then
echo "Running stylish-haskell..."
stylish
echo "Done."
if check-git-status
then
echo "OK, impeccable style."
else
echo "KO! Lack of style on those files:"
git status -sb
exit 1
fi
else
echo "git status not clean, aborting"
fi

View file

@ -1,20 +1,20 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module FediChordSpec where module FediChordSpec where
import Control.Exception
import Data.ASN1.Parse (runParseASN1)
import qualified Data.ByteString as BS
import Data.IORef
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust)
import qualified Data.Set as Set
import Data.Time.Clock.POSIX
import Network.Socket
import Test.Hspec import Test.Hspec
import Control.Exception
import Network.Socket
import Data.Maybe (fromJust)
import qualified Data.Map.Strict as Map
import qualified Data.ByteString as BS
import qualified Data.Set as Set
import Data.ASN1.Parse (runParseASN1)
import Data.Time.Clock.POSIX
import Data.IORef
import Hash2Pub.ASN1Coding
import Hash2Pub.DHTProtocol
import Hash2Pub.FediChord import Hash2Pub.FediChord
import Hash2Pub.DHTProtocol
import Hash2Pub.ASN1Coding
spec :: Spec spec :: Spec
spec = do spec = do
@ -123,7 +123,7 @@ spec = do
nid1 = toNodeID 2^(23::Integer)+1 nid1 = toNodeID 2^(23::Integer)+1
node1 = do node1 = do
eln <- exampleLocalNode -- is at 2^23.00000017198264 = 8388609 eln <- exampleLocalNode -- is at 2^23.00000017198264 = 8388609
pure $ putPredecessors [nid4] $ eln {nid = nid1} return $ putPredecessors [nid4] $ eln {nid = nid1}
nid2 = toNodeID 2^(230::Integer)+12 nid2 = toNodeID 2^(230::Integer)+12
node2 = exampleNodeState { nid = nid2} node2 = exampleNodeState { nid = nid2}
nid3 = toNodeID 2^(25::Integer)+10 nid3 = toNodeID 2^(25::Integer)+10
@ -156,7 +156,7 @@ spec = do
describe "Messages can be encoded to and decoded from ASN.1" $ do describe "Messages can be encoded to and decoded from ASN.1" $ do
-- define test messages -- define test messages
let let
someNodeIDs = fmap fromInteger [3..12] someNodeIDs = map fromInteger [3..12]
qidReqPayload = QueryIDRequestPayload { qidReqPayload = QueryIDRequestPayload {
queryTargetID = nid exampleNodeState queryTargetID = nid exampleNodeState
, queryLBestNodes = 3 , queryLBestNodes = 3

View file

@ -1,8 +1,8 @@
module Main (main) where module Main (main) where
import qualified FediChordSpec
import Test.Hspec import Test.Hspec
import qualified FediChordSpec
main :: IO () main :: IO ()
main = hspec $ main = hspec $ do
describe "FediChord tests" FediChordSpec.spec describe "FediChord tests" FediChordSpec.spec