{-# LANGUAGE TemplateHaskell, OverloadedStrings #-} {-# 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 Path import Text import Text.IO import IO hiding (hGetLine, hPutStrLn) import Arbitrary() import Test.Framework import Test.Framework.TH import Test.Framework.Providers.QuickCheck2 (testProperty) import Test.QuickCheck import Test.QuickCheck.Monadic import Line default (Text) prop_CheckBuffering ∷ Line → Property prop_CheckBuffering (Line l) = monadicIO $ do m ← run $ do binaryTemporaryFile (absDir "/tmp") (relFile "testTemp") $ \tf → do let h = tf ^. tfHandle withOffset h 0 $ \_ → hPutStrLn h l hGetLine h assert (l ≡ m) properties ∷ Test properties = $(testGroupGenerator)