Skip to content

Commit

Permalink
deepseq -> seq, improve BlockBuffering generator
Browse files Browse the repository at this point in the history
  • Loading branch information
BebeSparkelSparkel committed May 19, 2024
1 parent 5283a16 commit b1d29f0
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 9 deletions.
9 changes: 4 additions & 5 deletions tests/Tests/QuickCheckUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,14 +34,13 @@ module Tests.QuickCheckUtils
) where

import Control.Arrow ((***))
import Control.DeepSeq (deepseq)
import Data.Bool (bool)
import Data.Char (isSpace)
import Data.Text.Foreign (I8)
import Data.Text.Lazy.Builder.RealFloat (FPFormat(..))
import Data.Word (Word8, Word16)
import GHC.IO.Encoding.Types (TextEncoding(TextEncoding,textEncodingName))
import Test.QuickCheck (Arbitrary(..), arbitraryUnicodeChar, arbitraryBoundedEnum, getUnicodeString, arbitrarySizedIntegral, shrinkIntegral, Property, ioProperty, discard, counterexample, scale, (.&&.), NonEmptyList(..), suchThat, forAll, getPositive)
import Test.QuickCheck (Arbitrary(..), arbitraryUnicodeChar, arbitraryBoundedEnum, getUnicodeString, arbitrarySizedIntegral, shrinkIntegral, Property, ioProperty, discard, counterexample, scale, (.&&.), NonEmptyList(..), forAll, getPositive)
import Test.QuickCheck.Gen (Gen, choose, chooseAny, elements, frequency, listOf, oneof, resize, sized)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.QuickCheck (testProperty)
Expand Down Expand Up @@ -276,12 +275,12 @@ write_read unline filt writer reader modData
IO.hSeek h IO.AbsoluteSeek 0
r <- reader h
let isEq = r == t
deepseq isEq $ pure $ counterexample (show r ++ bool " /= " " == " isEq ++ show t) isEq
seq isEq $ pure $ counterexample (show r ++ bool " /= " " == " isEq ++ show t) isEq

encodings = [IO.utf8, IO.utf8_bom, IO.utf16, IO.utf16le, IO.utf16be, IO.utf32, IO.utf32le, IO.utf32be]

blockBuffering :: Gen IO.BufferMode
blockBuffering = IO.BlockBuffering <$> (fmap (fmap getPositive) arbitrary) `suchThat` maybe True (> 4)

blockBuffering = IO.BlockBuffering <$> fmap (fmap $ min 4 . getPositive) arbitrary

-- Generate various Unicode space characters with high probability
arbitrarySpacyChar :: Gen Char
Expand Down
8 changes: 4 additions & 4 deletions tests/Tests/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,10 @@ module Tests.Utils
) where

import Control.Exception (SomeException, bracket, bracket_, evaluate, try)
import Control.Monad (when)
import Control.Monad (when, unless)
import GHC.IO.Handle.Internals (withHandle)
import System.Directory (removeFile)
import System.IO (Handle, hClose, hFlush, hIsOpen, hIsWritable, openTempFile)
import System.IO (Handle, hClose, hFlush, hIsOpen, hIsClosed, hIsWritable, openTempFile)
import Test.QuickCheck (Property, ioProperty, property, (===), counterexample)

-- Ensure that two potentially bottom values (in the sense of crashing
Expand All @@ -34,8 +34,8 @@ withTempFile :: (FilePath -> Handle -> IO a) -> IO a
withTempFile = bracket (openTempFile "." "crashy.txt") cleanupTemp . uncurry
where
cleanupTemp (path,h) = do
open <- hIsOpen h
when open (hClose h)
closed <- hIsClosed h
unless closed $ hClose h
removeFile path

withRedirect :: Handle -> Handle -> IO a -> IO a
Expand Down

0 comments on commit b1d29f0

Please sign in to comment.