[commit: packages/pretty] master: #32, add a test that rendering the prefix of an infinite document produces some result (a5c916a)
git at git.haskell.org
git at git.haskell.org
Thu Feb 2 19:15:23 UTC 2017
Repository : ssh://git@git.haskell.org/pretty
On branch : master
Link : http://git.haskell.org/packages/pretty.git/commitdiff/a5c916ae4fe90f2cfb65357aafc3b7673845f3d0
>---------------------------------------------------------------
commit a5c916ae4fe90f2cfb65357aafc3b7673845f3d0
Author: Neil Mitchell <ndmitchell at gmail.com>
Date: Thu Jun 2 13:15:32 2016 +0100
#32, add a test that rendering the prefix of an infinite document produces some result
>---------------------------------------------------------------
a5c916ae4fe90f2cfb65357aafc3b7673845f3d0
pretty.cabal | 1 +
tests/Test.hs | 2 ++
tests/UnitT32.hs | 9 +++++++++
3 files changed, 12 insertions(+)
diff --git a/pretty.cabal b/pretty.cabal
index 4bfef78..f3116eb 100644
--- a/pretty.cabal
+++ b/pretty.cabal
@@ -62,6 +62,7 @@ Test-Suite test-pretty
UnitLargeDoc
UnitPP1
UnitT3911
+ UnitT32
extensions: CPP, BangPatterns, DeriveGeneric
include-dirs: src/Text/PrettyPrint/Annotated
ghc-options: -rtsopts -with-rtsopts=-K2M
diff --git a/tests/Test.hs b/tests/Test.hs
index bbcd0f7..4d23ac0 100644
--- a/tests/Test.hs
+++ b/tests/Test.hs
@@ -18,6 +18,7 @@ import TestStructures
import UnitLargeDoc
import UnitPP1
import UnitT3911
+import UnitT32
import Control.Monad
import Data.Char (isSpace)
@@ -39,6 +40,7 @@ main = do
-- unit tests
testPP1
testT3911
+ testT32
testLargeDoc
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/tests/UnitT32.hs b/tests/UnitT32.hs
new file mode 100755
index 0000000..8c1eb85
--- /dev/null
+++ b/tests/UnitT32.hs
@@ -0,0 +1,9 @@
+-- Test from https://github.com/haskell/pretty/issues/32#issuecomment-223073337
+module UnitT32 where
+
+import Text.PrettyPrint.HughesPJ
+
+import TestUtils
+
+testT32 :: IO ()
+testT32 = simpleMatch "T3911" (replicate 10 'x') $ take 10 $ render $ hcat $ repeat $ text "x"
More information about the ghc-commits
mailing list