@@ -34,16 +34,18 @@ module Tests.QuickCheckUtils
3434 ) where
3535
3636import Control.Arrow ((***) )
37- import Data.Bool ( bool )
37+ import Control.Monad ( when )
3838import Data.Char (isSpace )
39+ import Data.IORef (writeIORef )
3940import Data.Text.Foreign (I8 )
4041import Data.Text.Lazy.Builder.RealFloat (FPFormat (.. ))
4142import Data.Word (Word8 , Word16 )
42- import GHC.IO.Encoding.Types (TextEncoding (TextEncoding ,textEncodingName ))
43- import Test.QuickCheck (Arbitrary (.. ), arbitraryUnicodeChar , arbitraryBoundedEnum , getUnicodeString , arbitrarySizedIntegral , shrinkIntegral , Property , ioProperty , discard , counterexample , scale , (.&&.) , NonEmptyList (.. ), forAll , getPositive )
43+ import qualified GHC.IO.Buffer as GIO
44+ import qualified GHC.IO.Handle.Internals as GIO
45+ import qualified GHC.IO.Handle.Types as GIO
46+ import GHC.IO.Encoding.Types (TextEncoding (textEncodingName ))
47+ import Test.QuickCheck (Arbitrary (.. ), arbitraryUnicodeChar , arbitraryBoundedEnum , getUnicodeString , arbitrarySizedIntegral , shrinkIntegral , Property , ioProperty , counterexample , scale , (.&&.) , NonEmptyList (.. ), forAllShrink )
4448import Test.QuickCheck.Gen (Gen , choose , chooseAny , elements , frequency , listOf , oneof , resize , sized )
45- import Test.Tasty (TestTree , testGroup )
46- import Test.Tasty.QuickCheck (testProperty )
4749import Tests.Utils
4850import qualified Data.ByteString as B
4951import qualified Data.ByteString.Lazy as BL
@@ -248,39 +250,55 @@ instance Arbitrary IO.BufferMode where
248250-- sometimes contain line endings.)
249251-- * Newline translation mode.
250252-- * Buffering.
251- write_read :: forall a b c .
252- (Eq a , Show a , Show c , Arbitrary c )
253- => ([b ] -> a )
254- -> ((Char -> Bool ) -> b -> b )
253+ write_read :: forall a .
254+ (Eq a , Show a )
255+ => Gen a
256+ -> (a -> [a ])
257+ -> (a -> a ) -- ^ replace '\n' with '\r\n' (for multiline tests) or append '\r' (for single-line tests)
255258 -> (IO. Handle -> a -> IO () )
256259 -> (IO. Handle -> IO a )
257- -> (c -> [b ])
258- -> [TestTree ]
259- write_read unline filt writer reader modData
260- = encodings <&> \ enc@ TextEncoding {textEncodingName} -> testGroup textEncodingName
261- [ testProperty " NoBuffering" $ propTest enc (pure IO. NoBuffering )
262- , testProperty " LineBuffering" $ propTest enc (pure IO. LineBuffering )
263- , testProperty " BlockBuffering" $ propTest enc blockBuffering
264- ]
260+ -> Property
261+ write_read genTxt shrinkTxt expandNl writer reader
262+ = forAllShrink genEncoding shrinkEncoding propTest
265263 where
266- propTest :: TextEncoding -> Gen IO. BufferMode -> IO. NewlineMode -> c -> Property
267- propTest _ _ (IO. NewlineMode IO. LF IO. CRLF ) _ = discard
268- propTest enc genBufferMode nl d = forAll genBufferMode $ \ mode -> ioProperty $ withTempFile $ \ _ h -> do
269- let ts = modData d
270- t = unline . map (filt (not . (`elem` " \r\n " ))) $ ts
271- IO. hSetEncoding h enc
272- IO. hSetNewlineMode h nl
273- IO. hSetBuffering h mode
274- () <- writer h t
275- IO. hSeek h IO. AbsoluteSeek 0
276- r <- reader h
277- let isEq = r == t
278- seq isEq $ pure $ counterexample (show r ++ bool " /= " " == " isEq ++ show t) isEq
279-
280- encodings = [IO. utf8, IO. utf8_bom, IO. utf16, IO. utf16le, IO. utf16be, IO. utf32, IO. utf32le, IO. utf32be]
281-
282- blockBuffering :: Gen IO. BufferMode
283- blockBuffering = IO. BlockBuffering <$> fmap (fmap $ min 4 . getPositive) arbitrary
264+ propTest :: TextEncoding -> IO. BufferMode -> Property
265+ propTest enc mode = forAllShrink genTxt shrinkTxt $ \ txt -> ioProperty $ do
266+ file <- emptyTempFile
267+ let with nl k = IO. withFile file IO. ReadWriteMode $ \ h -> do
268+ IO. hSetEncoding h enc
269+ IO. hSetBuffering h mode
270+ IO. hSetNewlineMode h nl
271+ setSmallBuffer h
272+ k h
273+ -- Put a very small buffer in Handle to easily test boundary conditions in `writeBlocks`
274+ setSmallBuffer h = GIO. withHandle_ " setSmallBuffer" h $ \ h_ -> do
275+ buf <- GIO. newCharBuffer 9 GIO. WriteBuffer
276+ writeIORef (GIO. haCharBuffer h_) buf
277+ readExpecting h txt' msg = do
278+ out <- reader h
279+ when (txt' /= out) $ error (show txt' ++ " /= " ++ show out ++ msg)
280+ -- 'reader' may be 'hGetContents', which closes the handle
281+ -- So we reopen a new file every time.
282+
283+ -- Test with CRLF encoding
284+ with (IO. NewlineMode IO. CRLF IO. CRLF ) $ \ h -> do
285+ writer h txt
286+ IO. hSeek h IO. AbsoluteSeek 0
287+ readExpecting h txt " (at location 1)"
288+
289+ -- Re-read without CRLF decoding to check that we did encode CRLF correctly
290+ with (IO. NewlineMode IO. LF IO. LF ) $ \ h -> do
291+ readExpecting h (expandNl txt) " (at location 2)"
292+
293+ -- Test without CRLF encoding
294+ with (IO. NewlineMode IO. LF IO. LF ) $ \ h -> do
295+ IO. hSetFileSize h 0
296+ writer h txt
297+ IO. hSeek h IO. AbsoluteSeek 0
298+ readExpecting h txt " (at location 3)"
299+
300+ genEncoding = elements [IO. utf8, IO. utf8_bom, IO. utf16, IO. utf16le, IO. utf16be, IO. utf32, IO. utf32le, IO. utf32be]
301+ shrinkEncoding enc = if textEncodingName enc == textEncodingName IO. utf8 then [] else [IO. utf8]
284302
285303-- Generate various Unicode space characters with high probability
286304arbitrarySpacyChar :: Gen Char
@@ -301,7 +319,3 @@ newtype SkewedBool = Skewed { getSkewed :: Bool }
301319
302320instance Arbitrary SkewedBool where
303321 arbitrary = Skewed <$> frequency [(1 , pure False ), (5 , pure True )]
304-
305- (<&>) :: [a ] -> (a -> b ) -> [b ]
306- (<&>) = flip fmap
307-
0 commit comments