Replace words / unwords, it's broken too
This commit is contained in:
parent
bb064eb0c7
commit
1e0114441b
2 changed files with 10 additions and 5 deletions
|
@ -1,4 +1,5 @@
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Codec.Compression.Zlib (compress, decompress)
|
import Codec.Compression.Zlib (compress, decompress)
|
||||||
|
@ -7,7 +8,7 @@ import qualified Data.ByteString.Char8 as BS (
|
||||||
length, readFile
|
length, readFile
|
||||||
)
|
)
|
||||||
import qualified Data.ByteString.Lazy.Char8 as Lazy (
|
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 qualified Data.Map as Map (insert, lookup)
|
||||||
import PDF (Document(..), parseDocument, render)
|
import PDF (Document(..), parseDocument, render)
|
||||||
|
@ -22,7 +23,7 @@ revealFlateEncodedText =
|
||||||
Lazy.toStrict . compress . revealText . decompress . Lazy.fromStrict
|
Lazy.toStrict . compress . revealText . decompress . Lazy.fromStrict
|
||||||
where
|
where
|
||||||
lines = Lazy.split '\n'
|
lines = Lazy.split '\n'
|
||||||
unlines = Lazy.intercalate $ Lazy.pack "\n"
|
unlines = Lazy.intercalate "\n"
|
||||||
revealText = unlines . fmap fill . lines
|
revealText = unlines . fmap fill . lines
|
||||||
fill = update $ const Fill
|
fill = update $ const Fill
|
||||||
|
|
||||||
|
|
|
@ -5,7 +5,8 @@ module PDF.TextRendering (
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.ByteString.Lazy.Char8 (ByteString)
|
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 =
|
data TextRendering =
|
||||||
Fill
|
Fill
|
||||||
|
@ -18,12 +19,15 @@ data TextRendering =
|
||||||
| AddPath
|
| AddPath
|
||||||
deriving (Enum, Show)
|
deriving (Enum, Show)
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
update :: (TextRendering -> TextRendering) -> ByteString -> ByteString
|
update :: (TextRendering -> TextRendering) -> ByteString -> ByteString
|
||||||
update f = BS.unwords . changeTextRendering . BS.words
|
update f = unwords . changeTextRendering . words
|
||||||
where
|
where
|
||||||
changeTextRendering :: [ByteString] -> [ByteString]
|
|
||||||
changeTextRendering l@[value, "Tr"] =
|
changeTextRendering l@[value, "Tr"] =
|
||||||
case BS.readInt value of
|
case BS.readInt value of
|
||||||
Just (n, _) -> [BS.pack . show . fromEnum . f $ toEnum n, "Tr"]
|
Just (n, _) -> [BS.pack . show . fromEnum . f $ toEnum n, "Tr"]
|
||||||
_ -> l
|
_ -> l
|
||||||
changeTextRendering l = l
|
changeTextRendering l = l
|
||||||
|
words = BS.split ' '
|
||||||
|
unwords = BS.intercalate " "
|
||||||
|
|
Loading…
Reference in a new issue