Skip to content

Commit

Permalink
Use strict instead of lazy sum.
Browse files Browse the repository at this point in the history
sum is lazy; replace with `foldl' (+) 0` to avoid stack
overflow in Text.Pandoc.Pretty with very long strings.

Closes #5401.
  • Loading branch information
jgm committed Mar 28, 2019
1 parent b87a3ef commit 7fa5fbe
Show file tree
Hide file tree
Showing 2 changed files with 5 additions and 5 deletions.
6 changes: 3 additions & 3 deletions src/Text/Pandoc/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,7 @@ import Control.Monad
import Control.Monad.State.Strict
import Data.Char (isSpace)
import Data.Foldable (toList)
import Data.List (intersperse)
import Data.List (intersperse, foldl')
import Data.Sequence (Seq, ViewL (..), fromList, mapWithIndex, singleton, viewl,
(<|))
import qualified Data.Sequence as Seq
Expand Down Expand Up @@ -305,7 +305,7 @@ renderList (BreakingSpace : xs) = do
let xs' = dropWhile isBreakingSpace xs
let next = takeWhile isText xs'
st <- get
let off = sum $ map offsetOf next
let off = foldl' (+) 0 $ map offsetOf next
case lineLength st of
Just l | column st + 1 + off > l -> do
outp (-1) "\n"
Expand Down Expand Up @@ -540,4 +540,4 @@ charWidth c =
-- | Get real length of string, taking into account combining and double-wide
-- characters.
realLength :: String -> Int
realLength = sum . map charWidth
realLength = foldl' (+) 0 . map charWidth
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Writers/Shared.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ import Data.Aeson (FromJSON (..), Result (..), ToJSON (..), Value (Object),
encode, fromJSON)
import Data.Char (chr, ord, isSpace, isDigit)
import qualified Data.HashMap.Strict as H
import Data.List (groupBy, intersperse, transpose)
import Data.List (groupBy, intersperse, transpose, foldl')
import qualified Data.Map as M
import Data.Maybe (isJust)
import qualified Data.Text as T
Expand Down Expand Up @@ -279,7 +279,7 @@ gridTable opts blocksToDoc headless aligns widths headers rows = do
-- handleGivenWidths
let handleZeroWidths = do
(widthsInChars', rawHeaders', rawRows') <- handleFullWidths
if sum widthsInChars' > writerColumns opts
if foldl' (+) 0 widthsInChars' > writerColumns opts
then -- use even widths
handleGivenWidths
(replicate numcols (1.0 / fromIntegral numcols) :: [Double])
Expand Down

0 comments on commit 7fa5fbe

Please sign in to comment.