Use strict instead of lazy sum.
sum is lazy; replace with `foldl' (+) 0` to avoid stack overflow in Text.Pandoc.Pretty with very long strings. Closes #5401.
This commit is contained in:
parent
b87a3efb93
commit
7fa5fbed9e
2 changed files with 5 additions and 5 deletions
|
@ -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
|
||||
|
@ -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"
|
||||
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
@ -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])
|
||||
|
|
Loading…
Add table
Reference in a new issue