@@ -64,7 +64,6 @@ module Data.BitVector.LittleEndian
64
64
, dimension
65
65
, isZeroVector
66
66
, subRange
67
- , showNatural
68
67
) where
69
68
70
69
@@ -88,7 +87,7 @@ import GHC.Generics
88
87
import GHC.Integer.GMP.Internals
89
88
import GHC.Integer.Logarithms
90
89
import GHC.Natural
91
- import Test.QuickCheck (Arbitrary (.. ), CoArbitrary (.. ), NonNegative (.. ), suchThat , variant )
90
+ import Test.QuickCheck (Arbitrary (.. ), CoArbitrary (.. ), NonNegative (.. ), choose , suchThat , variant )
92
91
import TextShow (TextShow (showb ))
93
92
94
93
@@ -118,11 +117,50 @@ type instance MonoKey BitVector = Word
118
117
-- @since 0.1.0
119
118
instance Arbitrary BitVector where
120
119
120
+ -- Arbitrary instance distribution weighting:
121
+ -- - 2% = (maxBound :: Word)
122
+ -- - 2% = (maxBound :: Word) + 1
123
+ -- - 8% = all bits on
124
+ -- - 8% = all bits off
125
+ -- - 80% = any bit configuration
121
126
arbitrary = do
122
- dimVal <- getNonNegative <$> arbitrary
123
- let upperBound = shiftL 1 dimVal
124
- intVal <- (getNonNegative <$> arbitrary) `suchThat` (< upperBound)
125
- pure . BV (toEnum dimVal) $ intToNat intVal
127
+ -- 1/25 chance of generating the boundary value at which the natural number
128
+ -- must use different Natural constructors: NatS# & NatJ#
129
+ n <- choose (0 , 25 :: Word )
130
+ case n of
131
+ 0 -> boundaryValue
132
+ 1 -> allBitsOn
133
+ 2 -> allBitsOn
134
+ 3 -> allBitsOff
135
+ 4 -> allBitsOff
136
+ _ -> anyBitValue
137
+ where
138
+ allBitsOn = genBitVector $ Just True
139
+ allBitsOff = genBitVector $ Just False
140
+ anyBitValue = genBitVector $ Nothing
141
+
142
+ boundaryValue = do
143
+ let wrdVal = maxBound :: Word
144
+ let dimVal = toEnum $ popCount wrdVal
145
+ let numVal = wordToNatural wrdVal
146
+ -- 50/50 change to generate above or below the constructor boundary
147
+ underBoundary <- arbitrary
148
+ let (lowerBound, naturalVal)
149
+ | underBoundary = (dimVal , numVal )
150
+ | otherwise = (dimVal + 1 , numVal + 1 )
151
+ widthVal <- (getNonNegative <$> arbitrary) `suchThat` (>= lowerBound)
152
+ pure $ BV widthVal naturalVal
153
+
154
+ genBitVector spec = do
155
+ dimVal <- getNonNegative <$> arbitrary
156
+ let upperBound = shiftL 1 dimVal
157
+ -- 1/5 chance all bits on or all bits off
158
+ natVal <- case spec of
159
+ Just False -> pure $ intToNat 0
160
+ Just True -> pure . intToNat $ upperBound - 1
161
+ Nothing -> fmap intToNat $
162
+ (getNonNegative <$> arbitrary) `suchThat` (< upperBound)
163
+ pure $ BV (toEnum dimVal) natVal
126
164
127
165
128
166
-- |
@@ -158,14 +196,14 @@ instance Bits BitVector where
158
196
in BV w $ n .&. mask
159
197
160
198
{-# INLINE setBit #-}
161
- setBit bv@ (BV w n) i@ ( I # v)
199
+ setBit bv@ (BV w n) i
162
200
| i < 0 = bv
163
- | otherwise = BV (max w j) $ ( n `orNatural` (bitNatural v :: Natural ) :: Natural )
201
+ | otherwise = BV (max w j) $ n `setBit` i
164
202
where
165
203
! j = toEnum i + 1
166
204
167
205
{-# INLINE testBit #-}
168
- testBit (BV w n) i = i >= 0 && toEnum i < w && n `testBitNatural ` i
206
+ testBit (BV w n) i = i >= 0 && toEnum i < w && n `testBit ` i
169
207
170
208
bitSize (BV w _) = fromEnum w
171
209
@@ -1116,16 +1154,9 @@ toInt w
1116
1154
-- this function does not throw an exception when an negative valued 'Integer'
1117
1155
-- is supplied and is also compatible with base < 4.10.0.0.
1118
1156
{-# INLINE intToNat #-}
1157
+ -- {-# NOINLINE intToNat #-}
1119
1158
intToNat :: Integer -> Natural
1120
- intToNat (S # i# ) | I # i# >= 0 = NatS # (int2Word# i# )
1121
- intToNat (Jp # bn) = NatJ # bn
1122
- intToNat _ = NatS # (int2Word# 0 # )
1123
-
1124
-
1125
- -- |
1126
- -- Utility Function for printing the 'Natural' number constructor.
1127
- showNatural :: BitVector -> String
1128
- showNatural (BV w (NatS # v)) = unwords [" [" <> show w<> " ]" , " NatS#" , show (W # v)]
1129
- showNatural (BV w n@ (NatJ # _)) = unwords [" [" <> show w<> " ]" , " NatJ#" , show n]
1130
-
1131
-
1159
+ intToNat (S # i# ) | isTrue# (i# >=# 0 # ) = NatS # (int2Word# i# )
1160
+ intToNat (Jp # bn) | isTrue# (sizeofBigNat# bn ==# 1 # ) = NatS # (bigNatToWord bn)
1161
+ | otherwise = NatJ # bn
1162
+ intToNat _ = NatS # (int2Word# 0 # )
0 commit comments