Skip to content

Commit

Permalink
Merge pull request #35 from ndmitchell/master
Browse files Browse the repository at this point in the history
Remove harmful $! forcing in beside
  • Loading branch information
dterei committed Jun 2, 2016
2 parents f904ff7 + a5c916a commit ba5a4da
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 1 deletion.
1 change: 1 addition & 0 deletions pretty.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion src/Text/PrettyPrint/Annotated/HughesPJ.hs
Original file line number Diff line number Diff line change
Expand Up @@ -695,7 +695,7 @@ beside p@(Beside p1 g1 q1) g2 q2
| otherwise = beside (reduceDoc p) g2 q2
beside p@(Above{}) g q = let !d = reduceDoc p in beside d g q
beside (NilAbove p) g q = nilAbove_ $! beside p g q
beside (TextBeside t p) g q = TextBeside t $! rest
beside (TextBeside t p) g q = TextBeside t rest
where
rest = case p of
Empty -> nilBeside g q
Expand Down
2 changes: 2 additions & 0 deletions tests/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import TestStructures
import UnitLargeDoc
import UnitPP1
import UnitT3911
import UnitT32

import Control.Monad
import Data.Char (isSpace)
Expand All @@ -39,6 +40,7 @@ main = do
-- unit tests
testPP1
testT3911
testT32
testLargeDoc

-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Expand Down
9 changes: 9 additions & 0 deletions tests/UnitT32.hs
Original file line number Diff line number Diff line change
@@ -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"

0 comments on commit ba5a4da

Please sign in to comment.