summaryrefslogtreecommitdiff
path: root/src/Data/Word64Map.hs
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-10-12 05:41:09 -0400
committerjoe <joe@jerkface.net>2017-10-12 05:41:09 -0400
commit37a7fa4978f89072d9231bcc9bd0848bb52c676c (patch)
tree48a2a934e5da1c6754915d5ad27417f604cbfd04 /src/Data/Word64Map.hs
parent3024b35b05d7f520666af20ced8d1f3080837bb2 (diff)
WIP Onion routing.
Diffstat (limited to 'src/Data/Word64Map.hs')
-rw-r--r--src/Data/Word64Map.hs62
1 files changed, 62 insertions, 0 deletions
diff --git a/src/Data/Word64Map.hs b/src/Data/Word64Map.hs
new file mode 100644
index 00000000..9e93c8c8
--- /dev/null
+++ b/src/Data/Word64Map.hs
@@ -0,0 +1,62 @@
1{-# LANGUAGE RankNTypes #-}
2{-# LANGUAGE ScopedTypeVariables #-}
3{-# LANGUAGE UnboxedTuples #-}
4module Data.Word64Map where
5
6import Data.Bits
7import qualified Data.IntMap as IntMap
8 ;import Data.IntMap (IntMap)
9import Data.Typeable
10import Data.Word
11
12-- | Since 'Int' may be 32 or 64 bits, this function is provided as a
13-- convenience to test if an integral type, such as 'Data.Word.Word64', can be
14-- safely transformed into an 'Int' for use with 'IntMap'.
15--
16-- Returns 'True' if the proxied type can be losslessly converted to 'Int' using
17-- 'fromIntegral'.
18fitsInInt :: forall proxy word. (Bounded word, Integral word) => proxy word -> Bool
19fitsInInt proxy = (original == casted)
20 where
21 original = div maxBound 2 :: word
22 casted = fromIntegral (fromIntegral original :: Int) :: word
23
24newtype Word64Map a = Word64Map (IntMap (IntMap a))
25
26empty :: Word64Map a
27empty = Word64Map IntMap.empty
28
29-- Warning: This function assumes an 'Int' is either 64 or 32 bits.
30keyFrom64 :: Word64 -> (# Int,Int #)
31keyFrom64 w8 =
32 if fitsInInt (Proxy :: Proxy Word64)
33 then (# fromIntegral w8 , 0 #)
34 else (# fromIntegral (w8 `shiftR` 32), fromIntegral w8 #)
35{-# INLINE keyFrom64 #-}
36
37lookup :: Word64 -> Word64Map b -> Maybe b
38lookup w8 (Word64Map m) | (# hi,lo #) <- keyFrom64 w8 = do
39 m' <- IntMap.lookup hi m
40 IntMap.lookup lo m'
41{-# INLINE lookup #-}
42
43insert :: Word64 -> b -> Word64Map b -> Word64Map b
44insert w8 b (Word64Map m) | (# hi,lo #) <- keyFrom64 w8
45 = Word64Map $ IntMap.alter (Just . maybe (IntMap.singleton lo b)
46 (IntMap.insert lo b))
47 hi
48 m
49{-# INLINE insert #-}
50
51delete :: Word64 -> Word64Map b -> Word64Map b
52delete w8 (Word64Map m) | (# hi,lo #) <- keyFrom64 w8
53 = Word64Map $ IntMap.alter (maybe Nothing
54 (\m' -> case IntMap.delete lo m' of
55 m'' | IntMap.null m'' -> Nothing
56 m'' -> Just m''))
57 hi
58 m
59{-# INLINE delete #-}
60
61
62