Replace words / unwords, it's broken too

This commit is contained in:
Tissevert 2019-05-24 10:22:43 +02:00
parent bb064eb0c7
commit 1e0114441b
2 changed files with 10 additions and 5 deletions

View File

@ -1,4 +1,5 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Codec.Compression.Zlib (compress, decompress)
@ -7,7 +8,7 @@ import qualified Data.ByteString.Char8 as BS (
length, readFile
)
import qualified Data.ByteString.Lazy.Char8 as Lazy (
fromStrict, intercalate, pack, split, toStrict, writeFile
fromStrict, intercalate, split, toStrict, writeFile
)
import qualified Data.Map as Map (insert, lookup)
import PDF (Document(..), parseDocument, render)
@ -22,7 +23,7 @@ revealFlateEncodedText =
Lazy.toStrict . compress . revealText . decompress . Lazy.fromStrict
where
lines = Lazy.split '\n'
unlines = Lazy.intercalate $ Lazy.pack "\n"
unlines = Lazy.intercalate "\n"
revealText = unlines . fmap fill . lines
fill = update $ const Fill

View File

@ -5,7 +5,8 @@ module PDF.TextRendering (
) where
import Data.ByteString.Lazy.Char8 (ByteString)
import qualified Data.ByteString.Lazy.Char8 as BS (pack, readInt, unwords, words)
import qualified Data.ByteString.Lazy.Char8 as BS (intercalate, pack, readInt, split)
import Prelude hiding (unwords, words)
data TextRendering =
Fill
@ -18,12 +19,15 @@ data TextRendering =
| AddPath
deriving (Enum, Show)
update :: (TextRendering -> TextRendering) -> ByteString -> ByteString
update f = BS.unwords . changeTextRendering . BS.words
update f = unwords . changeTextRendering . words
where
changeTextRendering :: [ByteString] -> [ByteString]
changeTextRendering l@[value, "Tr"] =
case BS.readInt value of
Just (n, _) -> [BS.pack . show . fromEnum . f $ toEnum n, "Tr"]
_ -> l
changeTextRendering l = l
words = BS.split ' '
unwords = BS.intercalate " "