diff options
author | joe <joe@jerkface.net> | 2017-01-27 04:34:32 -0500 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-01-27 04:34:32 -0500 |
commit | 77a317310d4f7929335fafe3cfbf53afd45faa82 (patch) | |
tree | 220e885dfc44af98998faee7660b9e9ef7363220 /src | |
parent | 6a239e20bbc7a84a74721d23587bbf1b8c20c704 (diff) |
Switched PSQueue to psqueues for strict spine.
Diffstat (limited to 'src')
-rw-r--r-- | src/Data/Wrapper/PSQ.hs | 41 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/ContactInfo.hs | 2 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Routing.hs | 17 |
3 files changed, 49 insertions, 11 deletions
diff --git a/src/Data/Wrapper/PSQ.hs b/src/Data/Wrapper/PSQ.hs new file mode 100644 index 00000000..e8fa2d98 --- /dev/null +++ b/src/Data/Wrapper/PSQ.hs | |||
@@ -0,0 +1,41 @@ | |||
1 | {-# LANGUAGE PatternSynonyms #-} | ||
2 | {-# LANGUAGE CPP #-} | ||
3 | module Data.Wrapper.PSQ | ||
4 | #if 0 | ||
5 | ( module Data.PSQueue ) where ; import Data.PSQueue | ||
6 | #else | ||
7 | ( module Data.Wrapper.PSQ , module OrdPSQ ) where | ||
8 | |||
9 | import Data.OrdPSQ as OrdPSQ hiding (insert, map, singleton, minView) | ||
10 | import qualified Data.OrdPSQ as OrdPSQ | ||
11 | |||
12 | type PSQ k p = OrdPSQ k p () | ||
13 | type Binding k p = (k,p,()) | ||
14 | |||
15 | pattern (:->) :: k -> p -> Binding k p | ||
16 | pattern k :-> p <- (k,p,()) where k :-> p = (k,p,()) | ||
17 | |||
18 | key :: Binding k v -> k | ||
19 | key (k,p,v) = k | ||
20 | {-# INLINE key #-} | ||
21 | |||
22 | insert :: (Ord k, Ord p) => k -> p -> PSQ k p -> PSQ k p | ||
23 | insert k p q = OrdPSQ.insert k p () q | ||
24 | {-# INLINE insert #-} | ||
25 | |||
26 | insertWith :: (Ord k, Ord p) => (p -> p -> p) -> k -> p -> PSQ k p -> PSQ k p | ||
27 | insertWith f k p0 q = snd $ OrdPSQ.alter f' k q | ||
28 | where | ||
29 | f' (Just (p,())) = ((),Just (f p0 p, ())) | ||
30 | f' Nothing = ((),Nothing) | ||
31 | {-# INLINE insertWith #-} | ||
32 | |||
33 | singleton :: (Ord k, Ord p) => k -> p -> PSQ k p | ||
34 | singleton k p = OrdPSQ.singleton k p () | ||
35 | {-# INLINE singleton #-} | ||
36 | |||
37 | minView :: (Ord k, Ord p) => PSQ k p -> Maybe (Binding k p, PSQ k p) | ||
38 | minView q = fmap (\(k,p,(),q') -> (k :-> p, q')) $ OrdPSQ.minView q | ||
39 | {-# INLINE minView #-} | ||
40 | |||
41 | #endif | ||
diff --git a/src/Network/BitTorrent/DHT/ContactInfo.hs b/src/Network/BitTorrent/DHT/ContactInfo.hs index ea3b96f0..26bdeae9 100644 --- a/src/Network/BitTorrent/DHT/ContactInfo.hs +++ b/src/Network/BitTorrent/DHT/ContactInfo.hs | |||
@@ -12,7 +12,7 @@ import Data.List as L | |||
12 | import Data.Maybe | 12 | import Data.Maybe |
13 | import Data.HashMap.Strict as HM | 13 | import Data.HashMap.Strict as HM |
14 | import Data.Serialize | 14 | import Data.Serialize |
15 | import Data.PSQueue as PSQ | 15 | import Data.Wrapper.PSQ as PSQ |
16 | import Data.Time.Clock.POSIX | 16 | import Data.Time.Clock.POSIX |
17 | import Data.ByteString (ByteString) | 17 | import Data.ByteString (ByteString) |
18 | import Data.Word | 18 | import Data.Word |
diff --git a/src/Network/BitTorrent/DHT/Routing.hs b/src/Network/BitTorrent/DHT/Routing.hs index d64e415e..3c2e30aa 100644 --- a/src/Network/BitTorrent/DHT/Routing.hs +++ b/src/Network/BitTorrent/DHT/Routing.hs | |||
@@ -70,7 +70,7 @@ import Data.Functor.Identity | |||
70 | import Data.List as L hiding (insert) | 70 | import Data.List as L hiding (insert) |
71 | import Data.Maybe | 71 | import Data.Maybe |
72 | import Data.Monoid | 72 | import Data.Monoid |
73 | import Data.PSQueue as PSQ | 73 | import Data.Wrapper.PSQ as PSQ |
74 | import Data.Serialize as S hiding (Result, Done) | 74 | import Data.Serialize as S hiding (Result, Done) |
75 | import qualified Data.Sequence as Seq | 75 | import qualified Data.Sequence as Seq |
76 | import Data.Time | 76 | import Data.Time |
@@ -181,10 +181,6 @@ runRouting ping_node find_nodes timestamper = go | |||
181 | -- | Timestamp - last time this node is pinged. | 181 | -- | Timestamp - last time this node is pinged. |
182 | type NodeEntry ip = Binding (NodeInfo ip) Timestamp | 182 | type NodeEntry ip = Binding (NodeInfo ip) Timestamp |
183 | 183 | ||
184 | instance (Serialize k, Serialize v) => Serialize (Binding k v) where | ||
185 | get = (:->) <$> get <*> get | ||
186 | put (k :-> v) = put k >> put v | ||
187 | |||
188 | -- TODO instance Pretty where | 184 | -- TODO instance Pretty where |
189 | 185 | ||
190 | -- | Number of nodes in a bucket. | 186 | -- | Number of nodes in a bucket. |
@@ -239,12 +235,13 @@ data Bucket ip = Bucket { bktNodes :: PSQ (NodeInfo ip) Timestamp | |||
239 | , bktQ :: BucketQueue ip | 235 | , bktQ :: BucketQueue ip |
240 | } deriving (Show,Generic) | 236 | } deriving (Show,Generic) |
241 | 237 | ||
242 | instance (Eq ip, Serialize ip) => Serialize (Bucket ip) | 238 | instance (Eq ip, Serialize ip) => Serialize (Bucket ip) where |
239 | get = Bucket . psqFromPairList <$> get <*> pure (runIdentity $ emptyQueue bucketQ) | ||
240 | put = put . psqToPairList . bktNodes | ||
241 | |||
242 | psqFromPairList xs = PSQ.fromList $ map (\(a,b) -> a :-> b) xs | ||
243 | 243 | ||
244 | instance (Serialize k, Serialize v, Ord k, Ord v) | 244 | psqToPairList psq = map (\(a :-> b) -> (a,b)) $ PSQ.toList psq |
245 | => Serialize (PSQ k v) where | ||
246 | get = PSQ.fromList <$> get | ||
247 | put = put . PSQ.toList | ||
248 | 245 | ||
249 | -- | Update interval, in seconds. | 246 | -- | Update interval, in seconds. |
250 | delta :: NominalDiffTime | 247 | delta :: NominalDiffTime |