Compare commits

..

No commits in common. "big-Hufflepdf-refactoring" and "main" have entirely different histories.

3 changed files with 41 additions and 27 deletions

View File

@ -24,8 +24,7 @@ executable reveal
build-depends: base >=4.9.1 && <4.13 build-depends: base >=4.9.1 && <4.13
, bytestring , bytestring
, containers , containers
, mtl
, Hufflepdf >= 0.2.0 , Hufflepdf >= 0.2.0
, zlib
hs-source-dirs: src hs-source-dirs: src
ghc-options: -Wall -rtsopts
default-language: Haskell2010 default-language: Haskell2010

View File

@ -1,39 +1,54 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Main where module Main where
import Codec.Compression.Zlib (compress, decompress)
import Data.ByteString.Char8 (ByteString) import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS (readFile, split, intercalate) import qualified Data.ByteString.Char8 as BS (
import qualified Data.ByteString.Lazy.Char8 as Lazy (writeFile) length, readFile
import PDF (Layers(..), Document(..), UnifiedLayers(..), parseDocument, render) )
import PDF.Box (Index(..), Either_(..), at, atAll) import qualified Data.ByteString.Lazy.Char8 as Lazy (
import PDF.Layer (Layer, Objects(..)) fromStrict, intercalate, split, toStrict, writeFile
import PDF.Object.Navigation (StreamContent(..)) )
import qualified Data.Map as Map (insert, lookup)
import PDF (Document(..), parseDocument, render)
import PDF.Object (Content(..), DirectObject(..), Object(..), Name(..), Number(..))
import PDF.TextRendering (TextRendering(..), update) import PDF.TextRendering (TextRendering(..), update)
import Prelude hiding (lines, unlines) import Prelude hiding (lines, unlines)
import System.Environment (getArgs) import System.Environment (getArgs)
import System.IO (hPutStrLn, stderr) import System.IO (hPutStrLn, stderr)
revealText :: ByteString -> ByteString revealFlateEncodedText :: ByteString -> ByteString
revealText = unlines . fmap fill . lines revealFlateEncodedText =
Lazy.toStrict . compress . revealText . decompress . Lazy.fromStrict
where where
lines = BS.split '\n' lines = Lazy.split '\n'
unlines = Lazy.intercalate "\n"
revealText = unlines . fmap fill . lines
fill = update $ const Fill fill = update $ const Fill
unlines = BS.intercalate "\n"
revealLayer :: Monad m => Layer -> m Layer revealObject :: Object -> Object
revealLayer = revealObject obj@(Stream {header, streamContent}) =
atAll Objects case Map.lookup (Name "Filter") header of
.atAll (Either_ Clear) $ Just (NameObject (Name "FlateDecode")) ->
return . revealText let newStreamContent = revealFlateEncodedText streamContent in
let newLength = Number . fromIntegral $ BS.length newStreamContent in
Stream {
header = Map.insert (Name "Length") (NumberObject newLength) header
, streamContent = newStreamContent
}
_ -> obj
revealObject obj = obj
reveal :: Document -> IO Document revealContent :: Content -> Content
reveal = at UnifiedLayers $ revealLayer revealContent content = content {
objects = revealObject <$> (objects content)
}
revealFirst :: Document -> IO Document reveal :: Document -> Document
revealFirst = at Layers .at(Index 0) $ revealLayer reveal document = document {
updates = revealContent <$> (updates document)
deepReveal :: Document -> IO Document }
deepReveal = atAll Layers $ revealLayer
main :: IO () main :: IO ()
main = do main = do
@ -41,4 +56,4 @@ main = do
result <- parseDocument <$> BS.readFile inputPath result <- parseDocument <$> BS.readFile inputPath
case result of case result of
Left parseError -> hPutStrLn stderr $ show parseError Left parseError -> hPutStrLn stderr $ show parseError
Right doc -> Lazy.writeFile outputPath . render =<< reveal doc Right doc -> Lazy.writeFile outputPath . render $ reveal doc

View File

@ -4,8 +4,8 @@ module PDF.TextRendering (
, update , update
) where ) where
import Data.ByteString.Char8 (ByteString) import Data.ByteString.Lazy.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS (intercalate, pack, readInt, split) import qualified Data.ByteString.Lazy.Char8 as BS (intercalate, pack, readInt, split)
import Prelude hiding (unwords, words) import Prelude hiding (unwords, words)
data TextRendering = data TextRendering =