44--
55{-# LANGUAGE FlexibleInstances #-}
66{-# LANGUAGE DeriveFunctor #-}
7+ {-# LANGUAGE TypeApplications #-}
8+ {-# LANGUAGE ScopedTypeVariables #-}
79
810{-# OPTIONS_GHC -fno-warn-orphans #-}
911
@@ -32,6 +34,7 @@ import Control.Arrow ((***))
3234import Control.DeepSeq (NFData (.. ), deepseq )
3335import Control.Exception (bracket )
3436import Data.Char (isSpace )
37+ import Data.Coerce (coerce )
3538import Data.Text.Foreign (I8 )
3639import Data.Text.Lazy.Builder.RealFloat (FPFormat (.. ))
3740import Data.Word (Word8 , Word16 )
@@ -47,6 +50,9 @@ import qualified Data.Text.Internal.Lazy as TL
4750import qualified Data.Text.Internal.Lazy.Fusion as TLF
4851import qualified Data.Text.Lazy as TL
4952import qualified System.IO as IO
53+ import Control.Applicative (liftA2 , liftA3 )
54+ import Data.Bits (shiftR , shiftL , countLeadingZeros , finiteBitSize )
55+ import GHC.Num (integerLog2 , integerLogBase )
5056
5157genWord8 :: Gen Word8
5258genWord8 = chooseAny
@@ -79,42 +85,65 @@ newtype Sqrt a = Sqrt { unSqrt :: a }
7985 deriving (Eq , Show )
8086
8187instance Arbitrary a => Arbitrary (Sqrt a ) where
82- arbitrary = fmap Sqrt $ sized $ \ n -> resize (smallish n) arbitrary
83- where
84- smallish = round . (sqrt :: Double -> Double ) . fromIntegral . abs
85- shrink = map Sqrt . shrink . unSqrt
88+ arbitrary = coerce $ sized $ \ n -> resize (smallish n) $ arbitrary @ a
89+ where
90+ smallish = intSqrt . abs
91+ intSqrt :: Int -> Int
92+ intSqrt n =
93+ if n < 2
94+ then n
95+ else
96+ let b2 = shiftR (finiteBitSize n - countLeadingZeros n) 1 in
97+ shiftR (shiftL 1 b2 + shiftR n b2) 1
98+ shrink = coerce (shrink @ a )
8699
87100instance Arbitrary T. Text where
88- arbitrary = ( T. pack . getUnicodeString) `fmap` arbitrary
101+ arbitrary = T. pack <$> listOf arbitraryUnicodeChar -- without surrogates
89102 shrink = map T. pack . shrink . T. unpack
90103
91104instance Arbitrary TL. Text where
92- arbitrary = ( TL. fromChunks . map notEmpty . unSqrt) `fmap` arbitrary
105+ arbitrary = TL. fromChunks <$> coerce (arbitrary @ ( Sqrt [ NotEmpty T. Text ]))
93106 shrink = map TL. pack . shrink . TL. unpack
94107
95108newtype BigInt = Big Integer
96109 deriving (Eq , Show )
97110
98111instance Arbitrary BigInt where
99- arbitrary = choose (1 :: Int ,200 ) >>= \ e -> Big <$> choose (10 ^ (e- 1 ),10 ^ e)
100- shrink (Big a) = [Big (a `div` 2 ^ (l- e)) | e <- shrink l]
101- where l = truncate (log (fromIntegral a) / log 2 :: Double ) :: Integer
112+ arbitrary = do
113+ e <- choose @ Int (1 ,200 )
114+ coerce $ choose @ Integer (10 ^ (e- 1 ),10 ^ e)
115+
116+ shrink ba = [coerce (a `div` 2 ^ (l- e)) | e <- shrink l]
117+ where
118+ a :: Integer
119+ a = coerce ba
120+ l :: Word
121+ l = integerLogBase 2 a
102122
103123newtype NotEmpty a = NotEmpty { notEmpty :: a }
104- deriving (Eq , Ord , Show )
124+ deriving (Eq , Ord , Show )
125+
126+ toNotEmptyBy :: Functor m => ([Char ] -> a ) -> m (NonEmptyList Char ) -> m (NotEmpty a )
127+ toNotEmptyBy f = fmap (coerce f)
128+
129+ arbitraryNotEmptyBy :: ([Char ] -> a ) -> Gen (NotEmpty a )
130+ arbitraryNotEmptyBy f = toNotEmptyBy f arbitrary
131+
132+ shrinkNotEmptyBy :: ([Char ] -> a ) -> (a -> [Char ]) -> NotEmpty a -> [NotEmpty a ]
133+ shrinkNotEmptyBy g f =
134+ toNotEmptyBy g . shrink . coerce f
105135
106136instance Arbitrary (NotEmpty T. Text ) where
107- arbitrary = fmap (NotEmpty . T. pack . getNonEmpty) arbitrary
108- shrink = fmap (NotEmpty . T. pack . getNonEmpty)
109- . shrink . NonEmpty . T. unpack . notEmpty
137+ arbitrary = arbitraryNotEmptyBy T. pack
138+ shrink = shrinkNotEmptyBy T. pack T. unpack
110139
111140instance Arbitrary (NotEmpty TL. Text ) where
112- arbitrary = fmap ( NotEmpty . TL. pack . getNonEmpty) arbitrary
113- shrink = fmap ( NotEmpty . TL. pack . getNonEmpty)
114- . shrink . NonEmpty . TL. unpack . notEmpty
141+ arbitrary = arbitraryNotEmptyBy TL. pack
142+ shrink = shrinkNotEmptyBy TL. pack TL. unpack
143+
115144
116145data DecodeErr = Lenient | Ignore | Strict | Replace
117- deriving (Show , Eq , Bounded , Enum )
146+ deriving (Show , Eq , Bounded , Enum )
118147
119148genDecodeErr :: DecodeErr -> Gen T. OnDecodeError
120149genDecodeErr Lenient = return T. lenientDecode
@@ -167,71 +196,84 @@ eq a b s = a s =^= b s
167196-- What about with the RHS packed?
168197eqP :: (Eq a , Show a , Stringy s ) =>
169198 (String -> a ) -> (s -> a ) -> String -> Word8 -> Property
170- eqP f g s w = counterexample " orig" (f s =^= g t) .&&.
171- counterexample " mini" (f s =^= g mini) .&&.
172- counterexample " head" (f sa =^= g ta) .&&.
173- counterexample " tail" (f sb =^= g tb)
174- where t = packS s
175- mini = packSChunkSize 10 s
176- (sa,sb) = splitAt m s
177- (ta,tb) = splitAtS m t
178- l = length s
179- m | l == 0 = n
180- | otherwise = n `mod` l
181- n = fromIntegral w
199+ eqP f g s w =
200+ testCounterExample " orig" s t .&&.
201+ testCounterExample " mini" s mini .&&.
202+ testCounterExample " head" sa ta .&&.
203+ testCounterExample " tail" sb tb
204+ where
205+ testCounterExample txt a b = counterexample txt $ f a =^= g b
206+
207+ t = packS s
208+ mini = packSChunkSize 10 s
209+ (sa,sb) = splitAt m s
210+ (ta,tb) = splitAtS m t
211+
212+ m = if l == 0 then n else n `mod` l
213+ where
214+ l = length s
215+ n = fromIntegral w
182216
183217eqPSqrt :: (Eq a , Show a , Stringy s ) =>
184218 (String -> a ) -> (s -> a ) -> Sqrt String -> Word8 -> Property
185- eqPSqrt f g s = eqP f g (unSqrt s)
219+ eqPSqrt f g s = eqP f g $ coerce s
186220
187221instance Arbitrary FPFormat where
188222 arbitrary = arbitraryBoundedEnum
189223
190- newtype Precision a = Precision ( Maybe Int )
191- deriving (Eq , Show )
224+ newtype Precision a = Precision { unPrecision :: Maybe Int }
225+ deriving (Eq , Show )
192226
227+ -- Deprecated on 2021-10-05
193228precision :: a -> Precision a -> Maybe Int
194- precision _ (Precision prec) = prec
229+ precision _ = coerce
230+ {-# DEPRECATED precision "Use @coerce@ or @unPrecision@ with types instead." #-}
195231
196232arbitraryPrecision :: Int -> Gen (Precision a )
197- arbitraryPrecision maxDigits = Precision <$> do
198- n <- choose (- 1 ,maxDigits)
199- return $ if n == - 1
200- then Nothing
201- else Just n
233+ arbitraryPrecision maxDigits = do
234+ n <- choose (0 ,maxDigits)
235+ frequency
236+ [ (1 , pure $ coerce $ Nothing @ Int )
237+ , (n, pure $ coerce $ Just n)
238+ ]
202239
203240instance Arbitrary (Precision Float ) where
204241 arbitrary = arbitraryPrecision 11
205- shrink = map Precision . shrink . precision undefined
242+ shrink = coerce ( shrink @ ( Maybe Int ))
206243
207244instance Arbitrary (Precision Double ) where
208245 arbitrary = arbitraryPrecision 22
209- shrink = map Precision . shrink . precision undefined
246+ shrink = coerce ( shrink @ ( Maybe Int ))
210247
211248instance Arbitrary IO. Newline where
212- arbitrary = oneof [return IO. LF , return IO. CRLF ]
249+ arbitrary = oneof [pure IO. LF , pure IO. CRLF ]
213250
214251instance Arbitrary IO. NewlineMode where
215- arbitrary = IO. NewlineMode <$> arbitrary <*> arbitrary
252+ arbitrary =
253+ liftA2 IO. NewlineMode
254+ arbitrary
255+ arbitrary
216256
217257instance Arbitrary IO. BufferMode where
218- arbitrary = oneof [ return IO. NoBuffering ,
219- return IO. LineBuffering ,
220- return (IO. BlockBuffering Nothing ),
221- (IO. BlockBuffering . Just . (+ 1 ) . fromIntegral ) `fmap`
222- (arbitrary :: Gen Word16 ) ]
258+ arbitrary =
259+ oneof
260+ [ pure IO. NoBuffering
261+ , pure IO. LineBuffering
262+ , pure (IO. BlockBuffering Nothing )
263+ , IO. BlockBuffering . pure . succ . fromIntegral <$> arbitrary @ Word16
264+ ]
223265
224266-- This test harness is complex! What property are we checking?
225267--
226268-- Reading after writing a multi-line file should give the same
227269-- results as were written.
228270--
229271-- What do we vary while checking this property?
230- -- * The lines themselves, scrubbed to contain neither CR nor LF. (By
231- -- working with a list of lines, we ensure that the data will
232- -- sometimes contain line endings.)
233- -- * Newline translation mode.
234- -- * Buffering.
272+ -- * The lines themselves, scrubbed to contain neither CR nor LF. (By
273+ -- working with a list of lines, we ensure that the data will
274+ -- sometimes contain line endings.)
275+ -- * Newline translation mode.
276+ -- * Buffering.
235277write_read :: (NFData a , Eq a , Show a )
236278 => ([b ] -> a )
237279 -> ((Char -> Bool ) -> a -> b )
@@ -245,18 +287,25 @@ write_read _ _ _ _ (IO.NewlineMode IO.LF IO.CRLF) _ _ = discard
245287write_read unline filt writer reader nl buf ts = ioProperty $
246288 (=== t) <$> act
247289 where
248- t = unline . map (filt (not . (`elem` " \r\n " ))) $ ts
249-
250- act = withTempFile $ \ path h -> do
251- IO. hSetNewlineMode h nl
252- IO. hSetBuffering h buf
253- () <- writer h t
254- IO. hClose h
255- bracket (IO. openFile path IO. ReadMode ) IO. hClose $ \ h' -> do
256- IO. hSetNewlineMode h' nl
257- IO. hSetBuffering h' buf
258- r <- reader h'
259- r `deepseq` return r
290+ t = unline . map (filt (`notElem` " \r\n " )) $ ts
291+
292+ act =
293+ withTempFile roundTrip
294+ where
295+
296+ readBack h' = do
297+ IO. hSetNewlineMode h' nl
298+ IO. hSetBuffering h' buf
299+ r <- reader h'
300+ r `deepseq` pure r
301+
302+ roundTrip path h = do
303+ IO. hSetNewlineMode h nl
304+ IO. hSetBuffering h buf
305+ () <- writer h t
306+ IO. hClose h
307+
308+ IO. withFile path IO. ReadMode readBack
260309
261310-- Generate various Unicode space characters with high probability
262311arbitrarySpacyChar :: Gen Char
@@ -269,5 +318,5 @@ newtype SpacyString = SpacyString { getSpacyString :: String }
269318 deriving (Eq , Ord , Show , Read )
270319
271320instance Arbitrary SpacyString where
272- arbitrary = SpacyString `fmap` listOf arbitrarySpacyChar
273- shrink ( SpacyString xs) = SpacyString `fmap` shrink xs
321+ arbitrary = coerce $ listOf arbitrarySpacyChar
322+ shrink = coerce ( shrink @ [ Char ])
0 commit comments