66
77module Main where
88
9+ import Control.DeepSeq
10+ import Control.Exception
11+ import Control.Monad
912import Data.ByteString
1013import Data.List.NonEmpty
1114import qualified Data.List.NonEmpty as NE
15+ import Data.Maybe
1216import qualified Data.Text as T
1317import Data.Text.Arbitrary
18+ import qualified Data.Text.Lazy as TL
19+ import qualified Data.Text.Lazy.Builder as TB
20+ import System.Timeout
1421import Test.Hspec
1522import Test.Hspec.QuickCheck
1623import Test.ShouldNotTypecheck (shouldNotTypecheck )
@@ -34,6 +41,14 @@ data OpaqueType = OpaqueType Int
3441 (Display )
3542 via (OpaqueInstance " <opaque>" OpaqueType )
3643
44+ -- | @v \`shouldEvaluateWithin\` n@ sets the expectation that evaluating @v@
45+ -- should take no longer than @n@ microseconds.
46+ shouldEvaluateWithin :: (HasCallStack , NFData a ) => a -> Int -> Expectation
47+ shouldEvaluateWithin a n = do
48+ res <- timeout n (evaluate $ force a)
49+ when (isNothing res) $ do
50+ expectationFailure (" evaluation timed out in " <> show n <> " microseconds" )
51+
3752spec :: Spec
3853spec = do
3954 describe " Display Tests:" $ do
@@ -51,6 +66,9 @@ spec = do
5166 it " Single-element List instance is equivalent to Show" $ do
5267 let list = [1 ] :: [Int ]
5368 T. unpack (display list) `shouldBe` show list
69+ it " List instance is streamed lazily" $ do
70+ let list = [1 .. ] :: [Int ]
71+ TL. take 20 (TB. toLazyText $ displayBuilder list) `shouldEvaluateWithin` 100000
5472 it " NonEmpty instance is equivalent to Show" $ do
5573 let ne = NE. fromList [1 .. 5 ] :: NonEmpty Int
5674 T. unpack (display ne) `shouldBe` show ne
0 commit comments