File: MVector.hs

package info (click to toggle)
haskell-bitvec 1.1.5.0-4
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 332 kB
  • sloc: haskell: 3,408; ansic: 397; makefile: 5
file content (277 lines) | stat: -rw-r--r-- 8,421 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
{-# LANGUAGE CPP #-}

#ifndef BITVEC_THREADSAFE
module Tests.MVector (mvectorTests) where
#else
module Tests.MVectorTS (mvectorTests) where
#endif

import Support

import Control.Exception
import Control.Monad.ST
#ifndef BITVEC_THREADSAFE
import Data.Bit
#else
import Data.Bit.ThreadSafe
#endif
import Data.Bits
import qualified Data.Vector.Generic as V
import qualified Data.Vector.Generic.Mutable as MG
import qualified Data.Vector.Generic.New as N
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Unboxed.Mutable as M
import Test.Tasty
import Test.Tasty.QuickCheck

#ifdef MIN_VERSION_quickcheck_classes
import Data.Proxy
import Test.QuickCheck.Classes
#endif

mvectorTests :: TestTree
mvectorTests = testGroup "Data.Vector.Unboxed.Mutable.Bit"
  [ testGroup "Data.Vector.Unboxed.Mutable functions"
    [ tenTimesLess $
      testProperty "slice" prop_slice_def
    , testProperty "grow"  prop_grow_def
    ]
  , testGroup "Read/write Words"
    [ tenTimesLess $
      testProperty "castFromWords"  prop_castFromWords_def
    , testProperty "cloneToWords"   prop_cloneToWords_def
    , tenTimesLess $
      testProperty "castToWords_1"  prop_castToWords_1
    , tenTimesLess $
      testProperty "castToWords_2"  prop_castToWords_2
    ]
#ifdef MIN_VERSION_quickcheck_classes
  , lawsToTest' $ muvectorLaws (Proxy :: Proxy Bit)
#endif
  , testProperty "basicInitialize 1" case_write_init_read1
  , testProperty "basicInitialize 2" case_write_init_read2
  , testProperty "basicInitialize 3" case_write_init_read3
  , testProperty "basicInitialize 4" case_write_init_read4
  , testProperty "basicSet 1"        case_write_set_read1
  , testProperty "basicSet 2"        case_write_set_read2
  , testProperty "basicSet 3"        case_write_set_read3
  , testProperty "basicSet 4"        case_write_set_read4
  , testProperty "basicSet 5"        case_set_read1
  , testProperty "basicSet 6"        case_set_read2
  , testProperty "basicSet 7"        case_set_read3
  , testProperty "basicSet 8"        case_set_read4
  , testProperty "basicUnsafeCopy1"  case_write_copy_read1
  , testProperty "basicUnsafeCopy2"  case_write_copy_read2
  , testProperty "basicUnsafeCopy3"  case_write_copy_read3
  , testProperty "basicUnsafeCopy4"  case_write_copy_read4
  , testProperty "basicUnsafeCopy5"  case_write_copy_read5
  , tenTimesLess $
    testProperty "flipBit" prop_flipBit
  , testProperty "new negative"       prop_new_neg
  , testProperty "replicate negative" prop_replicate_neg
  ]

prop_flipBit :: U.Vector Bit -> NonNegative Int -> Property
prop_flipBit xs (NonNegative k) = U.length xs > 0 ==> ys === ys'
  where
    k'  = k `mod` U.length xs
    ys  = U.modify (\v -> M.modify v complement k') xs
    ys' = U.modify (\v -> flipBit v k') xs

case_write_init_read1 :: Property
case_write_init_read1 = (=== Bit True) $ runST $ do
  arr <- M.new 2
  M.write arr 0 (Bit True)
  MG.basicInitialize (M.slice 1 1 arr)
  M.read arr 0

case_write_init_read2 :: Property
case_write_init_read2 = (=== Bit True) $ runST $ do
  arr <- M.new 2
  M.write arr 1 (Bit True)
  MG.basicInitialize (M.slice 0 1 arr)
  M.read arr 1

case_write_init_read3 :: Property
case_write_init_read3 =
  (=== (Bit True, Bit True)) $ runST $ do
    arr <- M.new 2
    M.write arr 0 (Bit True)
    M.write arr 1 (Bit True)
    MG.basicInitialize (M.slice 1 0 arr)
    (,) <$> M.read arr 0 <*> M.read arr 1

case_write_init_read4 :: Property
case_write_init_read4 =
  (=== (Bit True, Bit True)) $ runST $ do
    arr <- M.new 3
    M.write arr 0 (Bit True)
    M.write arr 2 (Bit True)
    MG.basicInitialize (M.slice 1 1 arr)
    (,) <$> M.read arr 0 <*> M.read arr 2

case_write_set_read1 :: Property
case_write_set_read1 = (=== Bit True) $ runST $ do
  arr <- M.new 2
  M.write arr 0 (Bit True)
  MG.basicSet (M.slice 1 1 arr) (Bit False)
  M.read arr 0

case_write_set_read2 :: Property
case_write_set_read2 = (=== Bit True) $ runST $ do
  arr <- M.new 2
  M.write arr 1 (Bit True)
  MG.basicSet (M.slice 0 1 arr) (Bit False)
  M.read arr 1

case_write_set_read3 :: Property
case_write_set_read3 =
  (=== (Bit True, Bit True)) $ runST $ do
    arr <- M.new 2
    M.write arr 0 (Bit True)
    M.write arr 1 (Bit True)
    MG.basicSet (M.slice 1 0 arr) (Bit False)
    (,) <$> M.read arr 0 <*> M.read arr 1

case_write_set_read4 :: Property
case_write_set_read4 =
  (=== (Bit True, Bit True)) $ runST $ do
    arr <- M.new 3
    M.write arr 0 (Bit True)
    M.write arr 2 (Bit True)
    MG.basicSet (M.slice 1 1 arr) (Bit False)
    (,) <$> M.read arr 0 <*> M.read arr 2

case_set_read1 :: Property
case_set_read1 = (=== Bit True) $ runST $ do
  arr <- M.new 1
  MG.basicSet arr (Bit True)
  M.read arr 0

case_set_read2 :: Property
case_set_read2 = (=== Bit True) $ runST $ do
  arr <- M.new 2
  MG.basicSet (M.slice 1 1 arr) (Bit True)
  M.read arr 1

case_set_read3 :: Property
case_set_read3 = (=== Bit True) $ runST $ do
  arr <- M.new 192
  MG.basicSet (M.slice 71 121 arr) (Bit True)
  M.read arr 145

case_set_read4 :: Property
case_set_read4 = (=== Bit True) $ runST $ do
  arr <- M.slice 27 38 <$> M.new 65
  MG.basicSet arr (Bit True)
  M.read arr 21

case_write_copy_read1 :: Property
case_write_copy_read1 = (=== Bit True) $ runST $ do
  src <- M.slice 37 28 <$> M.new 65
  M.write src 27 (Bit True)
  dst <- M.slice 37 28 <$> M.new 65
  M.copy dst src
  M.read dst 27

case_write_copy_read2 :: Property
case_write_copy_read2 = (=== Bit True) $ runST $ do
  src <- M.slice 32 33 <$> M.new 65
  M.write src 0 (Bit True)
  dst <- M.slice 32 33 <$> M.new 65
  M.copy dst src
  M.read dst 0

case_write_copy_read3 :: Property
case_write_copy_read3 = (=== Bit True) $ runST $ do
  src <- M.slice 1 1 <$> M.new 2
  M.write src 0 (Bit True)
  dst <- M.slice 1 1 <$> M.new 2
  M.copy dst src
  M.read dst 0

case_write_copy_read4 :: Property
case_write_copy_read4 = (=== Bit True) $ runST $ do
  src <- M.slice 12 52 <$> M.new 64
  M.write src 22 (Bit True)
  dst <- M.slice 12 52 <$> M.new 64
  M.copy dst src
  M.read dst 22

case_write_copy_read5 :: Property
case_write_copy_read5 = (=== Bit True) $ runST $ do
  src <- M.slice 48 80 <$> M.new 128
  M.write src 46 (Bit True)
  dst <- M.slice 48 80 <$> M.new 128
  M.copy dst src
  M.read dst 46

prop_slice_def
  :: NonNegative Int
  -> NonNegative Int
  -> N.New U.Vector Bit
  -> Property
prop_slice_def (NonNegative s) (NonNegative n) xs =
  l > 0 ==> runST $ do
    let xs' = V.new xs
    xs1 <- N.run xs
    xs2 <- V.unsafeFreeze (M.slice s' n' xs1)
    return (U.toList xs2 === sliceList s' n' (U.toList xs'))
  where
    l = V.length (V.new xs)
    s' = s `mod` l
    n' = n `mod` (l - s')

prop_grow_def :: U.Vector Bit -> NonNegative Int -> Bool
prop_grow_def xs (NonNegative m) = runST $ do
  let n = U.length xs
  v0  <- U.thaw xs
  v1  <- M.grow v0 m
  fv0 <- U.freeze v0
  fv1 <- U.freeze v1
  return (fv0 == U.take n fv1)

prop_castFromWords_def :: N.New U.Vector Word -> Property
prop_castFromWords_def ws =
  runST (N.run ws >>= pure . castFromWordsM >>= V.unsafeFreeze)
    === castFromWords (V.new ws)

prop_cloneToWords_def :: N.New U.Vector Bit -> Property
prop_cloneToWords_def xs =
  runST (N.run xs >>= cloneToWordsM >>= V.unsafeFreeze)
    === cloneToWords (V.new xs)

prop_castToWords_1 :: N.New U.Vector Word -> Property
prop_castToWords_1 xs = runST $ do
  vs <- N.run xs
  vs' <- cloneToWordsM (castFromWordsM vs)
  case castToWordsM (castFromWordsM vs) of
    Nothing -> pure $ property False
    Just vs'' -> do
      ws'  <- V.unsafeFreeze vs'
      ws'' <- V.unsafeFreeze vs''
      pure $ ws' === ws''

prop_castToWords_2 :: N.New U.Vector Bit -> Property
prop_castToWords_2 xs = runST $ do
  vs <- N.run xs
  case castToWordsM vs of
    Nothing  -> pure $ property True
    Just ws -> do
      ws' <- V.unsafeFreeze (castFromWordsM ws)
      ws'' <- V.unsafeFreeze vs
      pure $ ws' === ws''

prop_replicate_neg :: Positive Int -> Bit -> Property
prop_replicate_neg (Positive n) x = ioProperty $ do
  ret <- try (evaluate (runST $ MG.basicUnsafeReplicate (-n) x >>= U.unsafeFreeze))
  pure $ property $ case ret of
    Left ErrorCallWithLocation{} -> True
    _ -> False

prop_new_neg :: Positive Int -> Property
prop_new_neg (Positive n) = ioProperty $ do
  ret <- try (evaluate (runST $ MG.basicUnsafeNew (-n) >>= U.unsafeFreeze :: U.Vector Bit))
  pure $ property $ case ret of
    Left ErrorCallWithLocation{} -> True
    _ -> False