diff options
Diffstat (limited to 'src/Network/BitTorrent/PeerWire')
-rw-r--r-- | src/Network/BitTorrent/PeerWire/Bitfield.hs | 102 |
1 files changed, 81 insertions, 21 deletions
diff --git a/src/Network/BitTorrent/PeerWire/Bitfield.hs b/src/Network/BitTorrent/PeerWire/Bitfield.hs index b375c1f5..2baeb516 100644 --- a/src/Network/BitTorrent/PeerWire/Bitfield.hs +++ b/src/Network/BitTorrent/PeerWire/Bitfield.hs | |||
@@ -11,6 +11,7 @@ | |||
11 | -- defined here as well. | 11 | -- defined here as well. |
12 | -- | 12 | -- |
13 | {-# LANGUAGE BangPatterns #-} | 13 | {-# LANGUAGE BangPatterns #-} |
14 | {-# LANGUAGE RankNTypes #-} | ||
14 | module Network.BitTorrent.PeerWire.Bitfield | 15 | module Network.BitTorrent.PeerWire.Bitfield |
15 | -- TODO: move to Data.Bitfield | 16 | -- TODO: move to Data.Bitfield |
16 | ( Bitfield(..) | 17 | ( Bitfield(..) |
@@ -26,7 +27,9 @@ module Network.BitTorrent.PeerWire.Bitfield | |||
26 | 27 | ||
27 | -- * Serialization | 28 | -- * Serialization |
28 | , getBitfield, putBitfield, bitfieldByteCount | 29 | , getBitfield, putBitfield, bitfieldByteCount |
29 | , aligned | 30 | |
31 | |||
32 | , aligned, alignLow, alignedZip | ||
30 | ) where | 33 | ) where |
31 | 34 | ||
32 | import Control.Applicative hiding (empty) | 35 | import Control.Applicative hiding (empty) |
@@ -80,8 +83,25 @@ bitfieldByteCount = B.length . bfBits | |||
80 | {-# INLINE bitfieldByteCount #-} | 83 | {-# INLINE bitfieldByteCount #-} |
81 | 84 | ||
82 | 85 | ||
86 | align :: Storable a => Ptr a -> (Ptr a, Int) | ||
87 | align p = tie (alignPtr p) undefined | ||
88 | where | ||
89 | tie :: Storable a => (Int -> Ptr a) -> a -> (Ptr a, Int) | ||
90 | tie f a = (f (alignment a), (alignment a)) | ||
91 | |||
92 | alignLow :: Ptr Word8 -> Ptr Word | ||
93 | alignLow ptr = | ||
94 | let alg = alignment (undefined :: Word) | ||
95 | aptr = alignPtr (castPtr ptr) alg :: Ptr Word | ||
96 | in | ||
97 | if ptr == castPtr aptr | ||
98 | then aptr | ||
99 | else castPtr ((castPtr aptr :: Ptr Word8) `advancePtr` negate alg) | ||
100 | |||
101 | isAlignedBy :: Storable a => Ptr a -> Int -> Bool | ||
102 | isAlignedBy ptr alg = alignPtr ptr alg == ptr | ||
83 | 103 | ||
84 | type Mem a = (Ptr a, Int) | 104 | type Mem a = (Ptr a, Int) |
85 | 105 | ||
86 | aligned :: Storable a => Mem Word8 -> (Mem Word8, Mem a, Mem Word8) | 106 | aligned :: Storable a => Mem Word8 -> (Mem Word8, Mem a, Mem Word8) |
87 | aligned (ptr, len) = | 107 | aligned (ptr, len) = |
@@ -97,36 +117,75 @@ aligned (ptr, len) = | |||
97 | in | 117 | in |
98 | ((lowPtr, lowLen), (midPtr, midLenA), (hghPtr, hghLen)) | 118 | ((lowPtr, lowLen), (midPtr, midLenA), (hghPtr, hghLen)) |
99 | where | 119 | where |
100 | align :: Storable a => Ptr a -> (Ptr a, Int) | ||
101 | align p = tie (alignPtr p) undefined | ||
102 | where | ||
103 | tie :: Storable a => (Int -> Ptr a) -> a -> (Ptr a, Int) | ||
104 | tie f a = (f (alignment a), (alignment a)) | ||
105 | {-# INLINE aligned #-} | 120 | {-# INLINE aligned #-} |
106 | 121 | ||
107 | zipWithBS :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString | 122 | type Mem3 a = (Ptr a, Ptr a, Ptr a, Int) |
108 | zipWithBS f a b = | 123 | |
124 | emptyMem3 :: Mem3 a | ||
125 | emptyMem3 = (nullPtr, nullPtr, nullPtr, 0) | ||
126 | |||
127 | -- assume resulting memory is aligned | ||
128 | alignedZip :: Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Int | ||
129 | -> (Mem3 Word, Mem3 Word8) | ||
130 | alignedZip aptr bptr cptr size = | ||
131 | let alg = alignment (undefined :: Word) in | ||
132 | if (aptr `isAlignedBy` alg) && (bptr `isAlignedBy` alg) | ||
133 | then | ||
134 | let asize = alignLow (nullPtr `plusPtr` size) `minusPtr` nullPtr | ||
135 | in | ||
136 | ( (castPtr aptr, castPtr bptr, castPtr cptr, asize `div` alg) | ||
137 | , ( aptr `advancePtr` asize | ||
138 | , bptr `advancePtr` asize | ||
139 | , cptr `advancePtr` asize | ||
140 | , (size - asize) | ||
141 | ) | ||
142 | ) | ||
143 | else (emptyMem3, (aptr, bptr, cptr, size)) | ||
144 | |||
145 | -- force specialization | ||
146 | zipWithBS :: (Word -> Word -> Word) | ||
147 | -> (Word8 -> Word8 -> Word8) | ||
148 | -> ByteString -> ByteString -> ByteString | ||
149 | zipWithBS f g a b = | ||
109 | let (afptr, aoff, asize) = B.toForeignPtr a | 150 | let (afptr, aoff, asize) = B.toForeignPtr a |
110 | (bfptr, boff, bsize) = B.toForeignPtr b | 151 | (bfptr, boff, bsize) = B.toForeignPtr b |
111 | size = min asize bsize in | 152 | size = min asize bsize in |
112 | B.unsafeCreate size $ \ptr -> do | 153 | B.unsafeCreate size $ \rptr -> do |
113 | withForeignPtr afptr $ \aptr -> do | 154 | withForeignPtr afptr $ \_aptr -> do |
114 | withForeignPtr bfptr $ \bptr -> | 155 | withForeignPtr bfptr $ \_bptr -> do |
115 | zipBytes (aptr `plusPtr` aoff) (bptr `plusPtr` boff) ptr size | 156 | let aptr = _aptr `advancePtr` aoff |
157 | let bptr = _bptr `advancePtr` boff | ||
158 | |||
159 | let (mid, hgh) = alignedZip aptr bptr rptr size | ||
160 | zipWords mid | ||
161 | zipBytes hgh | ||
116 | where | 162 | where |
117 | zipBytes :: Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Int -> IO () | 163 | zipBytes :: (Ptr Word8, Ptr Word8, Ptr Word8, Int) -> IO () |
118 | zipBytes aptr bptr rptr n = go 0 | 164 | zipBytes (aptr, bptr, rptr, n) = go 0 |
119 | where | 165 | where |
120 | go :: Int -> IO () | 166 | go :: Int -> IO () |
121 | go i | i < n = do -- TODO unfold | 167 | go i | i < n = do -- TODO unfold |
122 | av <- peekByteOff aptr i | 168 | av <- peekElemOff aptr i |
123 | bv <- peekByteOff bptr i | 169 | bv <- peekElemOff bptr i |
124 | pokeByteOff rptr i (f av bv) | 170 | pokeElemOff rptr i (g av bv) |
125 | go (succ i) | 171 | go (succ i) |
126 | | otherwise = return () | 172 | | otherwise = return () |
127 | 173 | ||
128 | zipWithBF :: (Word8 -> Word8 -> Word8) -> Bitfield -> Bitfield -> Bitfield | 174 | zipWords :: (Ptr Word, Ptr Word, Ptr Word, Int) -> IO () |
129 | zipWithBF f a b = MkBitfield $ zipWithBS f (bfBits a) (bfBits b) | 175 | zipWords (aptr, bptr, rptr, n) = go 0 |
176 | where | ||
177 | go :: Int -> IO () | ||
178 | go i | i < n = do -- TODO unfold | ||
179 | av <- peekElemOff aptr i | ||
180 | bv <- peekElemOff bptr i | ||
181 | pokeElemOff rptr i (f av bv) | ||
182 | go (succ i) | ||
183 | | otherwise = return () | ||
184 | |||
185 | |||
186 | |||
187 | zipWithBF :: (forall a. Bits a => a -> a -> a) -> Bitfield -> Bitfield -> Bitfield | ||
188 | zipWithBF f a b = MkBitfield $ zipWithBS f f (bfBits a) (bfBits b) | ||
130 | {-# INLINE zipWithBF #-} | 189 | {-# INLINE zipWithBF #-} |
131 | 190 | ||
132 | findSet :: ByteString -> Maybe Int | 191 | findSet :: ByteString -> Maybe Int |
@@ -169,6 +228,7 @@ findSet b = | |||
169 | | otherwise = Nothing | 228 | | otherwise = Nothing |
170 | 229 | ||
171 | 230 | ||
231 | |||
172 | union :: Bitfield -> Bitfield -> Bitfield | 232 | union :: Bitfield -> Bitfield -> Bitfield |
173 | union = zipWithBF (.|.) | 233 | union = zipWithBF (.|.) |
174 | {-# INLINE union #-} | 234 | {-# INLINE union #-} |
@@ -180,7 +240,7 @@ intersection = zipWithBF (.&.) | |||
180 | difference :: Bitfield -> Bitfield -> Bitfield | 240 | difference :: Bitfield -> Bitfield -> Bitfield |
181 | difference = zipWithBF diffWord8 | 241 | difference = zipWithBF diffWord8 |
182 | where | 242 | where |
183 | diffWord8 :: Word8 -> Word8 -> Word8 | 243 | diffWord8 :: Bits a => a -> a -> a |
184 | diffWord8 a b = a .&. (a `xor` b) | 244 | diffWord8 a b = a .&. (a `xor` b) |
185 | {-# INLINE diffWord8 #-} | 245 | {-# INLINE diffWord8 #-} |
186 | {-# INLINE difference #-} | 246 | {-# INLINE difference #-} |