Skip to content

Commit 8b9f30e

Browse files
committed
Make displayList lazier
1 parent ba9d202 commit 8b9f30e

File tree

4 files changed

+26
-4
lines changed

4 files changed

+26
-4
lines changed

CHANGELOG.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,9 @@
11
# CHANGELOG
22

3+
## [Unreleased]
4+
5+
* Fix `displayList` by making it lazier (https://github.com/haskell-text/text-display/pull/27)
6+
37
## [v0.0.3.0] - 21/08/2022
48

59
This is an experimental release.

src/Data/Text/Display.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -94,11 +94,10 @@ class Display a where
9494
-- > → Custom `displayList`
9595
displayList :: [a] -> Builder
9696
displayList [] = "[]"
97-
displayList (x : xs) = displayList' xs ("[" <> displayBuilder x)
97+
displayList (x : xs) = "[" <> displayBuilder x <> foldMap go xs <> "]"
9898
where
99-
displayList' :: [a] -> Builder -> Builder
100-
displayList' [] acc = acc <> "]"
101-
displayList' (y : ys) acc = displayList' ys (acc <> "," <> displayBuilder y)
99+
go :: a -> Builder
100+
go y = "," <> displayBuilder y
102101

103102
-- | The method 'displayPrec' allows you to write instances that
104103
-- require nesting. The precedence parameter can be thought of as a

test/Main.hs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,11 +6,18 @@
66

77
module Main where
88

9+
import Control.DeepSeq
10+
import Control.Exception
11+
import Control.Monad
912
import Data.ByteString
1013
import Data.List.NonEmpty
1114
import qualified Data.List.NonEmpty as NE
15+
import Data.Maybe
1216
import qualified Data.Text as T
1317
import Data.Text.Arbitrary
18+
import qualified Data.Text.Lazy as TL
19+
import qualified Data.Text.Lazy.Builder as TB
20+
import System.Timeout
1421
import Test.Hspec
1522
import Test.Hspec.QuickCheck
1623
import 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+
3752
spec :: Spec
3853
spec = 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

text-display.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ test-suite text-display-test
5555
build-depends:
5656
, base
5757
, bytestring
58+
, deepseq
5859
, hspec
5960
, quickcheck-text
6061
, should-not-typecheck

0 commit comments

Comments
 (0)