@@ -79,13 +79,13 @@ instance Arbitrary BL.ByteString where
79
79
-- | For tests that have O(n^2) running times or input sizes, resize
80
80
-- their inputs to the square root of the originals.
81
81
newtype Sqrt a = Sqrt { unSqrt :: a }
82
- deriving (Eq , Show )
82
+ deriving (Eq , Show )
83
83
84
84
instance Arbitrary a => Arbitrary (Sqrt a ) where
85
- arbitrary = fmap Sqrt $ sized $ \ n -> resize (smallish n) arbitrary
85
+ arbitrary = coerce $ sized $ \ n -> resize (smallish n) $ arbitrary @ a
86
86
where
87
87
smallish = round . (sqrt :: Double -> Double ) . fromIntegral . abs
88
- shrink = map Sqrt . shrink . unSqrt
88
+ shrink = coerce ( shrink @ a )
89
89
90
90
instance Arbitrary T. Text where
91
91
arbitrary = T. pack <$> listOf arbitraryUnicodeChar -- without surrogates
@@ -96,17 +96,20 @@ instance Arbitrary TL.Text where
96
96
shrink = map TL. pack . shrink . TL. unpack
97
97
98
98
newtype BigInt = Big Integer
99
- deriving (Eq , Show )
99
+ deriving (Eq , Show )
100
100
101
101
instance Arbitrary BigInt where
102
102
arbitrary = do
103
103
e <- choose (1 :: Int ,200 )
104
- Big <$> choose (10 ^ (e- 1 ),10 ^ e)
104
+ coerce $ choose @ Integer (10 ^ (e- 1 ),10 ^ e)
105
105
shrink (Big a) = [Big (a `div` 2 ^ (l- e)) | e <- shrink l]
106
- where l = truncate (logBase 2 (fromIntegral a) :: Double ) :: Integer
106
+ where
107
+ l :: Integer
108
+ l = truncate $ logBase @ Double 2 $ fromIntegral a
107
109
108
110
newtype NotEmpty a = NotEmpty { notEmpty :: a }
109
- deriving (Eq , Ord , Show )
111
+ deriving (Eq , Ord , Show )
112
+
110
113
111
114
instance Arbitrary (NotEmpty T. Text ) where
112
115
arbitrary = fmap (NotEmpty . T. pack . getNonEmpty) arbitrary
@@ -119,16 +122,17 @@ instance Arbitrary (NotEmpty TL.Text) where
119
122
. shrink . NonEmpty . TL. unpack . notEmpty
120
123
121
124
data DecodeErr = Lenient | Ignore | Strict | Replace
122
- deriving (Show , Eq , Bounded , Enum )
125
+ deriving (Show , Eq , Bounded , Enum )
123
126
124
127
genDecodeErr :: DecodeErr -> Gen T. OnDecodeError
125
128
genDecodeErr Lenient = return T. lenientDecode
126
129
genDecodeErr Ignore = return T. ignore
127
130
genDecodeErr Strict = return T. strictDecode
128
- genDecodeErr Replace = (\ c _ _ -> c) <$> frequency
129
- [ (1 , return Nothing )
130
- , (50 , Just <$> arbitraryUnicodeChar)
131
- ]
131
+ genDecodeErr Replace = (\ c _ _ -> c) <$>
132
+ frequency
133
+ [ (1 , return Nothing )
134
+ , (50 , pure <$> arbitraryUnicodeChar)
135
+ ]
132
136
133
137
instance Arbitrary DecodeErr where
134
138
arbitrary = arbitraryBoundedEnum
@@ -193,25 +197,26 @@ instance Arbitrary FPFormat where
193
197
arbitrary = arbitraryBoundedEnum
194
198
195
199
newtype Precision a = Precision (Maybe Int )
196
- deriving (Eq , Show )
200
+ deriving (Eq , Show )
197
201
198
202
precision :: a -> Precision a -> Maybe Int
199
203
precision _ (Precision prec) = prec
200
204
201
205
arbitraryPrecision :: Int -> Gen (Precision a )
202
- arbitraryPrecision maxDigits = Precision <$> do
206
+ arbitraryPrecision maxDigits = do
203
207
n <- choose (- 1 ,maxDigits)
204
- return $ if n == - 1
205
- then Nothing
206
- else Just n
208
+ pure $ coerce $
209
+ if n == - 1
210
+ then Nothing
211
+ else Just n
207
212
208
213
instance Arbitrary (Precision Float ) where
209
214
arbitrary = arbitraryPrecision 11
210
- shrink = map Precision . shrink . precision undefined
215
+ shrink = coerce . shrink . precision undefined
211
216
212
217
instance Arbitrary (Precision Double ) where
213
218
arbitrary = arbitraryPrecision 22
214
- shrink = map Precision . shrink . precision undefined
219
+ shrink = coerce . shrink . precision undefined
215
220
216
221
instance Arbitrary IO. Newline where
217
222
arbitrary = oneof [return IO. LF , return IO. CRLF ]
@@ -274,5 +279,5 @@ newtype SpacyString = SpacyString { getSpacyString :: String }
274
279
deriving (Eq , Ord , Show , Read )
275
280
276
281
instance Arbitrary SpacyString where
277
- arbitrary = SpacyString `fmap` listOf arbitrarySpacyChar
278
- shrink (SpacyString xs) = SpacyString `fmap` shrink xs
282
+ arbitrary = coerce $ listOf arbitrarySpacyChar
283
+ shrink (SpacyString xs) = coerce $ shrink xs
0 commit comments