summaryrefslogtreecommitdiff
path: root/src/Data/BEncode
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-09-29 06:01:06 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-09-29 06:01:06 +0400
commit573487ff0d758e1c500c26bc1e8b90dd155eb97b (patch)
tree9e177fe4a599e1d12ad921e0ca7c8b39e1c7e26d /src/Data/BEncode
parente0ad240589038f9cc61a43844067ad021c0a903f (diff)
Introduce BDictMap
Diffstat (limited to 'src/Data/BEncode')
-rw-r--r--src/Data/BEncode/BDict.hs90
1 files changed, 90 insertions, 0 deletions
diff --git a/src/Data/BEncode/BDict.hs b/src/Data/BEncode/BDict.hs
new file mode 100644
index 0000000..c674b21
--- /dev/null
+++ b/src/Data/BEncode/BDict.hs
@@ -0,0 +1,90 @@
1module Data.BEncode.BDict
2 ( BKey
3 , BDictMap
4
5 -- * Construction
6 , Data.BEncode.BDict.empty
7 , Data.BEncode.BDict.singleton
8
9 -- * Query
10 , Data.BEncode.BDict.lookup
11
12 -- * Combine
13 , Data.BEncode.BDict.union
14
15 -- * Transformations
16 , Data.BEncode.BDict.map
17
18 -- * Conversion
19 , Data.BEncode.BDict.fromAscList
20 , Data.BEncode.BDict.toAscList
21 ) where
22
23import Control.DeepSeq
24import Data.ByteString as BS
25import Data.Monoid
26
27
28type BKey = ByteString
29
30-- STRICTNESS NOTE: the BKey is always evaluated since we either use a
31-- literal or compare before insert to the dict
32--
33-- LAYOUT NOTE: we don't use [StrictPair BKey a] since it introduce
34-- one more constructor per cell
35--
36
37-- | BDictMap is list of key value pairs sorted by keys.
38data BDictMap a
39 = Cons !BKey a (BDictMap a)
40 | Nil
41 deriving (Show, Read, Eq, Ord)
42
43instance NFData a => NFData (BDictMap a) where
44 rnf Nil = ()
45 rnf (Cons _ v xs)= rnf v `seq` rnf xs
46
47instance Functor BDictMap where
48 fmap = Data.BEncode.BDict.map
49 {-# INLINE fmap #-}
50
51--instance Foldable BDictMap where
52
53instance Monoid (BDictMap a) where
54 mempty = Data.BEncode.BDict.empty
55 mappend = Data.BEncode.BDict.union
56
57empty :: BDictMap a
58empty = Nil
59{-# INLINE empty #-}
60
61singleton :: BKey -> a -> BDictMap a
62singleton k v = Cons k v Nil
63{-# INLINE singleton #-}
64
65lookup :: BKey -> BDictMap a -> Maybe a
66lookup x = go
67 where
68 go Nil = Nothing
69 go (Cons k v xs)
70 | k == x = Just v
71 | otherwise = go xs
72{-# INLINE lookup #-}
73
74union :: BDictMap a -> BDictMap a -> BDictMap a
75union = undefined
76
77map :: (a -> b) -> BDictMap a -> BDictMap b
78map f = go
79 where
80 go Nil = Nil
81 go (Cons k v xs) = Cons k (f v) (go xs)
82{-# INLINE map #-}
83
84fromAscList :: [(BKey, a)] -> BDictMap a
85fromAscList [] = Nil
86fromAscList ((k, v) : xs) = Cons k v (fromAscList xs)
87
88toAscList :: BDictMap a -> [(BKey, a)]
89toAscList Nil = []
90toAscList (Cons k v xs) = (k, v) : toAscList xs \ No newline at end of file