summaryrefslogtreecommitdiff
path: root/dht/src/Hans
diff options
context:
space:
mode:
authorJames Crayne <jim.crayne@gmail.com>2019-09-28 13:43:29 -0400
committerJoe Crayne <joe@jerkface.net>2020-01-01 19:27:53 -0500
commit11987749fc6e6d3e53ea737d46d5ab13a16faeb8 (patch)
tree5716463275c2d3e902889db619908ded2a73971c /dht/src/Hans
parentadd2c76bced51fde5e9917e7449ef52be70faf87 (diff)
Factor out some new libraries
word64-map: Data.Word64Map network-addr: Network.Address tox-crypto: Crypto.Tox lifted-concurrent: Control.Concurrent.Lifted.Instrument Control.Concurrent.Async.Lifted.Instrument psq-wrap: Data.Wrapper.PSQInt Data.Wrapper.PSQ minmax-psq: Data.MinMaxPSQ tasks: Control.Concurrent.Tasks kad: Network.Kademlia Network.Kademlia.Bootstrap Network.Kademlia.Routing Network.Kademlia.CommonAPI Network.Kademlia.Persistence Network.Kademlia.Search
Diffstat (limited to 'dht/src/Hans')
-rw-r--r--dht/src/Hans/Checksum.hs136
1 files changed, 136 insertions, 0 deletions
diff --git a/dht/src/Hans/Checksum.hs b/dht/src/Hans/Checksum.hs
new file mode 100644
index 00000000..7afc93c7
--- /dev/null
+++ b/dht/src/Hans/Checksum.hs
@@ -0,0 +1,136 @@
1{-# LANGUAGE RecordWildCards #-}
2{-# LANGUAGE BangPatterns #-}
3
4-- BANNERSTART
5-- - Copyright 2006-2008, Galois, Inc.
6-- - This software is distributed under a standard, three-clause BSD license.
7-- - Please see the file LICENSE, distributed with this software, for specific
8-- - terms and conditions.
9-- Author: Adam Wick <awick@galois.com>
10-- BANNEREND
11-- |A module providing checksum computations to other parts of Hans. The
12-- checksum here is the standard Internet 16-bit checksum (the one's
13-- complement of the one's complement sum of the data).
14
15module Hans.Checksum(
16 -- * Checksums
17 computeChecksum,
18 Checksum(..),
19 PartialChecksum(),
20 emptyPartialChecksum,
21 finalizeChecksum,
22 stepChecksum,
23
24 Pair8(..),
25 ) where
26
27import Data.Bits (Bits(shiftL,shiftR,complement,clearBit,(.&.)))
28import Data.List (foldl')
29import Data.Word (Word8,Word16,Word32)
30import qualified Data.ByteString as S
31import qualified Data.ByteString.Lazy as L
32import qualified Data.ByteString.Short as Sh
33import qualified Data.ByteString.Unsafe as S
34
35
36data PartialChecksum = PartialChecksum { pcAccum :: {-# UNPACK #-} !Word32
37 , pcCarry :: !(Maybe Word8)
38 } deriving (Eq,Show)
39
40emptyPartialChecksum :: PartialChecksum
41emptyPartialChecksum = PartialChecksum
42 { pcAccum = 0
43 , pcCarry = Nothing
44 }
45
46finalizeChecksum :: PartialChecksum -> Word16
47finalizeChecksum pc = complement (fromIntegral (fold32 (fold32 result)))
48 where
49 fold32 :: Word32 -> Word32
50 fold32 x = (x .&. 0xFFFF) + (x `shiftR` 16)
51
52 result = case pcCarry pc of
53 Nothing -> pcAccum pc
54 Just prev -> stepChecksum (pcAccum pc) prev 0
55{-# INLINE finalizeChecksum #-}
56
57
58computeChecksum :: Checksum a => a -> Word16
59computeChecksum a = finalizeChecksum (extendChecksum a emptyPartialChecksum)
60{-# INLINE computeChecksum #-}
61
62-- | Incremental checksum computation interface.
63class Checksum a where
64 extendChecksum :: a -> PartialChecksum -> PartialChecksum
65
66
67data Pair8 = Pair8 !Word8 !Word8
68
69instance Checksum Pair8 where
70 extendChecksum (Pair8 hi lo) = \ PartialChecksum { .. } ->
71 case pcCarry of
72 Nothing -> PartialChecksum { pcAccum = stepChecksum pcAccum hi lo
73 , pcCarry = Nothing }
74 Just c -> PartialChecksum { pcAccum = stepChecksum pcAccum c hi
75 , pcCarry = Just lo }
76 {-# INLINE extendChecksum #-}
77
78instance Checksum Word16 where
79 extendChecksum w = \pc -> extendChecksum (Pair8 hi lo) pc
80 where
81 lo = fromIntegral w
82 hi = fromIntegral (w `shiftR` 8)
83 {-# INLINE extendChecksum #-}
84
85instance Checksum Word32 where
86 extendChecksum w = \pc ->
87 extendChecksum (fromIntegral w :: Word16) $
88 extendChecksum (fromIntegral (w `shiftR` 16) :: Word16) pc
89 {-# INLINE extendChecksum #-}
90
91instance Checksum a => Checksum [a] where
92 extendChecksum as = \pc -> foldl' (flip extendChecksum) pc as
93 {-# INLINE extendChecksum #-}
94
95instance Checksum L.ByteString where
96 extendChecksum lbs = \pc -> extendChecksum (L.toChunks lbs) pc
97 {-# INLINE extendChecksum #-}
98
99-- XXX this could be faster if we could mirror the structure of the instance for
100-- S.ByteString
101instance Checksum Sh.ShortByteString where
102 extendChecksum shb = \ pc -> extendChecksum (Sh.fromShort shb) pc
103
104
105instance Checksum S.ByteString where
106 extendChecksum b pc
107 | S.null b = pc
108 | otherwise = case pcCarry pc of
109 Nothing -> result
110 Just prev -> extendChecksum (S.tail b) PartialChecksum
111 { pcCarry = Nothing
112 , pcAccum = stepChecksum (pcAccum pc) prev (S.unsafeIndex b 0)
113 }
114 where
115
116 n' = S.length b
117 n = clearBit n' 0 -- aligned to two
118
119 result = PartialChecksum
120 { pcAccum = loop (pcAccum pc) 0
121 , pcCarry = carry
122 }
123
124 carry
125 | odd n' = Just $! S.unsafeIndex b n
126 | otherwise = Nothing
127
128 loop !acc off
129 | off < n = loop (stepChecksum acc hi lo) (off + 2)
130 | otherwise = acc
131 where hi = S.unsafeIndex b off
132 lo = S.unsafeIndex b (off+1)
133
134stepChecksum :: Word32 -> Word8 -> Word8 -> Word32
135stepChecksum acc hi lo = acc + fromIntegral hi `shiftL` 8 + fromIntegral lo
136{-# INLINE stepChecksum #-}