{-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -Wno-orphans #-} {-| Module: TestTemporary Description: Test that temporary files are unbuffered and binary. Copyright: © 2016 All rights reserved. License: GPL-3 Maintainer: Evan Cofsky <> Stability: experimental Portability: POSIX -} module TestTemporary where import Lawless import Test.Framework import Test.Framework.TH import Test.Framework.Providers.QuickCheck2 (testProperty) import Test.QuickCheck import Text import Temporary import qualified Data.ByteString as B import System.IO hiding (utf8) import Test.QuickCheck.Monadic import Data.Text.Encoding (encodeUtf8) instance Arbitrary Text where arbitrary = view packed <$> listOf1 arbitrary prop_CheckBuffering (line ∷ Text) = monadicIO $ do let l = encodeUtf8 line m ← run $ withTempHandle "testTemp" $ \h → do B.hPut h l hSeek h AbsoluteSeek 0 B.hGetContents h assert (l ≡ m) properties ∷ Test properties = $(testGroupGenerator)