summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorSam T <pxqr.sta@gmail.com>2013-05-20 14:24:48 +0400
committerSam T <pxqr.sta@gmail.com>2013-05-20 14:24:48 +0400
commit36e8b49ede81619067645e7fff1bf28e0bb5b16b (patch)
tree33d06c20baed10e9dae627f96db68f87a675bfa2 /src
parente3da90564140f7140cfa3128d4b340e696fd5b47 (diff)
~ Fetch mutable bitfield module from cobit package.
Diffstat (limited to 'src')
-rw-r--r--src/Data/Bitfield/Mutable.hs186
1 files changed, 186 insertions, 0 deletions
diff --git a/src/Data/Bitfield/Mutable.hs b/src/Data/Bitfield/Mutable.hs
new file mode 100644
index 00000000..5de84dc8
--- /dev/null
+++ b/src/Data/Bitfield/Mutable.hs
@@ -0,0 +1,186 @@
1-- TODO: update documentation
2-- |
3-- Copyright : (c) Sam T. 2013
4-- License : MIT
5-- Maintainer : pxqr.sta@gmail.com
6-- Stability : experimental
7-- Portability : portable
8--
9--
10-- Set of integers with atomic modification. Internally IntSet
11-- represented as array of tightly packed bits.
12--
13-- Note that:
14--
15-- * Insertion, deletion are atomic, waitfree and failfree.
16--
17-- * You can avoid copying in conversion if you don't care about
18-- referencial transparency or sure that after conversion bitfields
19-- never modified.
20--
21--
22{-# OPTIONS -fno-warn-unused-do-bind #-}
23module Data.Bitfield.Mutable
24 ( IntSet
25
26 -- * Construction
27 , empty, full
28
29 -- * Query
30-- , lookup, member, notMember
31-- , size
32 , maxSize
33
34 -- * Modification
35-- , insert, delete
36
37 -- * Conversion
38 , fromByteString, toByteString
39
40 -- * Unsafe operations
41 -- ** Construction
42 , create, releaseIntSet
43
44 -- ** Modification
45 , insertUnsafe, deleteUnsafe
46
47 -- ** Query
48 , lookupUnsafe
49
50 -- ** Conversion
51 , fromByteStringUnsafe, toByteStringUnsafe
52
53 ) where
54
55import Control.Applicative hiding (empty)
56import Data.Bits.Atomic
57import Data.ByteString (ByteString)
58import qualified Data.ByteString as B
59import qualified Data.ByteString.Internal as B
60import Foreign
61
62
63-- | Basically 'BitSet' is a wrapper on the 'ForeignPtr'.
64data IntSet = IntSet {
65 sBasePtr :: {-# UNPACK #-} !(ForeignPtr Word8)
66 , sOffset :: {-# UNPACK #-} !Int
67 , sByteSize :: {-# UNPACK #-} !Int
68 , sMaxSize :: {-# UNPACK #-} !Int
69 } deriving Show
70
71
72maxSize :: IntSet -> Int
73maxSize = sMaxSize
74
75
76create :: Int -> (Int -> Ptr Word8 -> IO a) -> IO IntSet
77create n f = do
78 let byteSize = sizeInBytes n
79 fptr <- mallocForeignPtrBytes byteSize
80 withForeignPtr fptr (f byteSize)
81 return (IntSet fptr 0 byteSize n)
82
83-- | Create a 'IntSet' with a given size in /bits/.
84empty :: Int -> IO IntSet
85empty n = create n $ \bn ptr ->
86 B.memset ptr 0 (fromIntegral bn)
87
88full :: Int -> IO IntSet
89full n = create n $ \bn ptr ->
90 B.memset ptr (error "IntSet.full") (fromIntegral bn)
91
92
93-- | Should be used to free scarce resources immediately.
94--
95-- WARNING: After this call 'BitField' should not be used.
96-- Also you can avoid using it at all if resource is not too scarce.
97--
98releaseIntSet :: IntSet -> IO ()
99releaseIntSet = finalizeForeignPtr . sBasePtr
100
101-- | Set nth bit in the given BifField to 1.
102--
103-- UNSAFE: no bound checking.
104--
105insertUnsafe :: Int -> IntSet -> IO ()
106insertUnsafe i s =
107 withByte s i $ \ptr -> do
108 fetchAndOr ptr (bit (bitLoc i))
109 return ()
110{-# INLINE insertUnsafe #-}
111
112
113deleteUnsafe :: Int -> IntSet -> IO ()
114deleteUnsafe i s =
115 withByte s i $ \ptr -> do
116 fetchAndAnd ptr (complement (bit (bitLoc i)))
117 return ()
118{-# INLINE deleteUnsafe #-}
119
120-- | Get nth bit in the given BitField.
121--
122-- UNSAFE: no bound checking.
123--
124lookupUnsafe :: Int -> IntSet -> IO Bool
125lookupUnsafe n s = withByte s n $ \ptr -> (`testBit` bitLoc n) <$> peek ptr
126{-# INLINE lookupUnsafe #-}
127
128fromByteString :: Int -> ByteString -> IntSet
129fromByteString n = fromByteStringUnsafe n . B.copy
130{-# INLINE fromByteString #-}
131
132toByteString :: IntSet -> ByteString
133toByteString = B.copy . toByteStringUnsafe
134{-# INLINE toByteString #-}
135
136-- | Convert a 'BitField' to the 'ByteString' /without/ copying,
137-- so we can write it to a socket or a file for exsample.
138--
139-- WARNING: Note that using the resulting 'ByteString' might (and even should)
140-- BREAK REFERENCIAL TRANSPARENCY since we can change bits using 'setBitN'
141-- after the conversion. Use this function wisely and if and only if
142-- you understand the consequences, otherwise the really BAD THINGS WILL HAPPEN
143-- or use safe version instead.
144--
145toByteStringUnsafe :: IntSet -> ByteString
146toByteStringUnsafe = B.fromForeignPtr <$> sBasePtr <*> pure 0 <*> sByteSize
147
148
149-- | Convert a 'ByteString' to 'BitField' /without/ copying,
150-- so we can read it from a file or a socket.
151--
152-- WARNING: Please see 'toByteString' doc, the same apply to this function.
153--
154fromByteStringUnsafe :: Int -> ByteString -> IntSet
155fromByteStringUnsafe n (B.PS fptr a b) = IntSet fptr a b n
156
157baseSize :: (Bits a, Integral a) =>
158 a -- ^ Base, should be power of two.
159 -> a -- ^ Size.
160 -> a -- ^ Size in base.
161baseSize base n = (n `div` base) + fromIntegral (fromEnum ((n .&. 0x7) > 0))
162{-# SPECIALIZE baseSize :: Int -> Int -> Int #-}
163{-# SPECIALIZE baseSize :: Word64 -> Word64 -> Word64 #-}
164
165-------------------------------- internal --------------------------------------
166sizeInBytes :: Int -- ^ Length in bits.
167 -> Int -- ^ Length in bytes aligned by size of word.
168sizeInBytes = baseSize 8
169{-# INLINE sizeInBytes #-}
170
171-- TODO: see if shifts and bitwise ands are faster
172-- and make portable version if not
173byteLoc :: Int -> Int
174byteLoc i = i `div` 8 * sizeOf (error "byteLoc" :: Word8)
175{-# INLINE bitLoc #-}
176
177bitLoc :: Int -> Int
178bitLoc i = i `mod` 8 * sizeOf (error "bitLoc" :: Word8)
179{-# INLINE byteLoc #-}
180
181withByte :: IntSet -> Int -> (Ptr Word8 -> IO a) -> IO a
182withByte s n action = do
183 let offset = sOffset s + byteLoc n
184 withForeignPtr (sBasePtr s) $ \ptr ->
185 action (ptr `advancePtr` offset)
186{-# INLINE withByte #-} \ No newline at end of file