@@ -79,13 +79,13 @@ instance Arbitrary BL.ByteString where
7979-- | For tests that have O(n^2) running times or input sizes, resize
8080-- their inputs to the square root of the originals.
8181newtype Sqrt a = Sqrt { unSqrt :: a }
82- deriving (Eq , Show )
82+ deriving (Eq , Show )
8383
8484instance 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
8686 where
8787 smallish = round . (sqrt :: Double -> Double ) . fromIntegral . abs
88- shrink = map Sqrt . shrink . unSqrt
88+ shrink = coerce ( shrink @ a )
8989
9090instance Arbitrary T. Text where
9191 arbitrary = T. pack <$> listOf arbitraryUnicodeChar -- without surrogates
@@ -96,17 +96,20 @@ instance Arbitrary TL.Text where
9696 shrink = map TL. pack . shrink . TL. unpack
9797
9898newtype BigInt = Big Integer
99- deriving (Eq , Show )
99+ deriving (Eq , Show )
100100
101101instance Arbitrary BigInt where
102102 arbitrary = do
103103 e <- choose (1 :: Int ,200 )
104- Big <$> choose (10 ^ (e- 1 ),10 ^ e)
104+ coerce $ choose @ Integer (10 ^ (e- 1 ),10 ^ e)
105105 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
107109
108110newtype NotEmpty a = NotEmpty { notEmpty :: a }
109- deriving (Eq , Ord , Show )
111+ deriving (Eq , Ord , Show )
112+
110113
111114instance Arbitrary (NotEmpty T. Text ) where
112115 arbitrary = fmap (NotEmpty . T. pack . getNonEmpty) arbitrary
@@ -119,16 +122,17 @@ instance Arbitrary (NotEmpty TL.Text) where
119122 . shrink . NonEmpty . TL. unpack . notEmpty
120123
121124data DecodeErr = Lenient | Ignore | Strict | Replace
122- deriving (Show , Eq , Bounded , Enum )
125+ deriving (Show , Eq , Bounded , Enum )
123126
124127genDecodeErr :: DecodeErr -> Gen T. OnDecodeError
125128genDecodeErr Lenient = return T. lenientDecode
126129genDecodeErr Ignore = return T. ignore
127130genDecodeErr 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+ ]
132136
133137instance Arbitrary DecodeErr where
134138 arbitrary = arbitraryBoundedEnum
@@ -193,25 +197,26 @@ instance Arbitrary FPFormat where
193197 arbitrary = arbitraryBoundedEnum
194198
195199newtype Precision a = Precision (Maybe Int )
196- deriving (Eq , Show )
200+ deriving (Eq , Show )
197201
198202precision :: a -> Precision a -> Maybe Int
199203precision _ (Precision prec) = prec
200204
201205arbitraryPrecision :: Int -> Gen (Precision a )
202- arbitraryPrecision maxDigits = Precision <$> do
206+ arbitraryPrecision maxDigits = do
203207 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
207212
208213instance Arbitrary (Precision Float ) where
209214 arbitrary = arbitraryPrecision 11
210- shrink = map Precision . shrink . precision undefined
215+ shrink = coerce . shrink . precision undefined
211216
212217instance Arbitrary (Precision Double ) where
213218 arbitrary = arbitraryPrecision 22
214- shrink = map Precision . shrink . precision undefined
219+ shrink = coerce . shrink . precision undefined
215220
216221instance Arbitrary IO. Newline where
217222 arbitrary = oneof [return IO. LF , return IO. CRLF ]
@@ -274,5 +279,5 @@ newtype SpacyString = SpacyString { getSpacyString :: String }
274279 deriving (Eq , Ord , Show , Read )
275280
276281instance 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