Skip to content

Commit

Permalink
Clean up easy warnings.
Browse files Browse the repository at this point in the history
  • Loading branch information
dagit committed May 5, 2011
1 parent 6453ed7 commit b83beca
Show file tree
Hide file tree
Showing 4 changed files with 25 additions and 23 deletions.
1 change: 1 addition & 0 deletions Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ main :: IO ()
-- main = parseAndWriteFile "foo.pdf" "bar.pdf" -- no transformation done, just tests parse and print
main = watermarkFile "foo.pdf" "watermarked.pdf" watermarkPDF

watermarkPDF :: [Char]
watermarkPDF = "BT 100 50 Td /F1 12 Tf(Hello Watermark!) Tj ET"

buildAndWriteFile :: String -> Int -> IO ()
Expand Down
26 changes: 13 additions & 13 deletions Text/PDF/Document.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ module Text.PDF.Document where
import Data.Map as Map
import qualified Data.Traversable as T
import qualified Control.Monad.State as State
import Text.PDF.Types
import Text.PDF.Types hiding ( parent, dictMap )
import Text.PDF.Utils
-- import Text.PDF.Parser
import System.IO
Expand All @@ -35,7 +35,7 @@ newPage stream mbox rscDict = PDFPageParsed {

-- appendPage pageTree newPage returns a new Page Tree with newPage appended to the end
appendPage :: PDFObject -> PDFObject -> PDFObject
appendPage (PDFArray a) newPage = PDFArray (a ++ [newPage])
appendPage (PDFArray a) newPage' = PDFArray (a ++ [newPage'])
appendPage x y = (PDFArray [(PDFError "BadCallToAppendPage with:"), x, y])
-- eventually want to balance the tree of pages

Expand Down Expand Up @@ -72,7 +72,7 @@ unParsePage parsedPage = (PDFDict (fromList [
((PDFKey "CropBox"), boxToPDFObject (cropBox parsedPage))]))

unDigestDocument :: PDFDocumentParsed -> PDFTreeExploded
unDigestDocument inDoc@(PDFDocumentParsed parsedPageList {- globals -} ) = (catalogDictFromArray pageArray) where
unDigestDocument (PDFDocumentParsed parsedPageList {- globals -} ) = (catalogDictFromArray pageArray) where
(PDFArray pageArray) = PDFArray (Prelude.map unParsePage parsedPageList)

boxToPDFObject :: PDFBox -> PDFObject
Expand All @@ -86,7 +86,7 @@ showPDFObject (PDFString s) = "(" ++ (escapeString s) ++ ")"
showPDFObject (PDFSymbol s) = "/" ++ s

showPDFObject (PDFDict m) =
"<<" ++ (foldWithKey showKeyObject "" m) ++ " >>"
"<<" ++ (foldrWithKey showKeyObject "" m) ++ " >>"

showPDFObject (PDFFloat f) = (show f)
showPDFObject (PDFInt i) = (show i)
Expand Down Expand Up @@ -171,8 +171,7 @@ newPDFState = PDFState {
rsrcDict = PDFDict (fromList []),
fontsDict = PDFDict (fromList []),
pagesArray = []
} where
doc = (PDFObjectTreeFlattened PDFNull Map.empty )
}

-- todo: I like putting the media box as an arg to beginPage. HMMMM.
beginPage :: PDF ()
Expand Down Expand Up @@ -246,6 +245,7 @@ setFont name shortcut fontSize = do
globalProcSet :: PDFObject
globalProcSet = PDFArray [(PDFSymbol "PDF"), (PDFSymbol "Text") ]

globalPageBox :: PDFBox
globalPageBox = Quad 0 0 300 300

-- buildPageTree takes a PDFObjectTreeFlattened and an array of PDFObjects (which are page dicts)
Expand Down Expand Up @@ -291,7 +291,7 @@ traverseAndUnNest a = (enPointerify PDFNull) a

enPointerify :: PDFObject -> PDFObject -> UnNest PDFObject

enPointerify parent ia@(PDFArray objs) = do
enPointerify parent (PDFArray objs) = do
objs' <- mapM (enPointerify parent) objs -- could also use T.mapM here
case (length objs > 4) of
True -> do
Expand All @@ -310,7 +310,7 @@ enPointerify parent node@(PDFDict objs) = do
-- ok, this is wack: if I don't "enpointerify" streams, it's not a valid PDF.
-- I'm having a hard time finding where this should be true in the spec. Sigh. that's
-- a day of my life I'd like back. :-/
enPointerify parent str@(PDFStream s) = do
enPointerify _parent str@(PDFStream _) = do
reference str

enPointerify _parent o = return o
Expand Down Expand Up @@ -340,10 +340,10 @@ reference obj = do
return ref

clobberReference :: PDFObject -> PDFObject -> UnNest PDFObject
clobberReference object reference = do
clobberReference object ref = do
dict <- State.get
State.put (clobberObjectWithRef dict object reference)
return reference
State.put (clobberObjectWithRef dict object ref)
return ref

addDocObjectGetRef :: PDFObject -> PDFObjectTreeFlattened -> (PDFObject, PDFObjectTreeFlattened)
addDocObjectGetRef obj (PDFObjectTreeFlattened root oldMap) = (objRef, (PDFObjectTreeFlattened root newMap)) where
Expand All @@ -358,7 +358,7 @@ addObjectGetRef oldMap pdfobj = (newMap, newRef) where
objNum = (Map.size oldMap + 1)

clobberObjectWithRef :: PDFObjectMap -> PDFObject -> PDFObject -> PDFObjectMap
clobberObjectWithRef oldMap newObject (PDFReference n g) = Map.insert n newObject oldMap
clobberObjectWithRef oldMap newObject (PDFReference n _) = Map.insert n newObject oldMap
clobberObjectWithRef _ _ _ = error ("internal error: bad args to clobberObjectWithRef")

enpointerifyRoot :: PDFObjectTreeFlattened -> PDFObjectTreeFlattened
Expand All @@ -369,7 +369,7 @@ data ObjectIndices = ObjectIndices [Int] deriving (Show)

-- print the first line, and kick off printing the big "list of objects"
printFlatTree :: Handle -> PDFObjectTreeFlattened -> IO PDFObjectTreeFlattened
printFlatTree h d@(PDFObjectTreeFlattened id om) = do
printFlatTree h d@(PDFObjectTreeFlattened _ _) = do
let prefixLen = length header14
hPutStr h (header14)
let d' = enpointerifyRoot d
Expand Down
15 changes: 8 additions & 7 deletions Text/PDF/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,8 @@ import Data.Char as Char
import Data.Array as Array
-- import Data.Maybe

import Text.PDF.Types
import Text.PDF.Types hiding ( catalogDict )
import qualified Text.PDF.Types as T ( catalogDict )
import Text.PDF.Utils

-- import Debug.Trace
Expand All @@ -45,7 +46,7 @@ data PDFContents = PDFContents String deriving (Show)

parseContents :: PDFContents -> PDFObjectTreeFlattened
parseContents pdfContents = PDFObjectTreeFlattened {
catalogDict = catalogObj, -- the root, extracted from the catalog
T.catalogDict = catalogObj, -- the root, extracted from the catalog
objectList = parsedObjectMap -- objectNum -> PDFObject
} where
(xrefEntries, (PDFDict trailerDict)) = getXRefTable pdfContents
Expand All @@ -56,8 +57,8 @@ parseContents pdfContents = PDFObjectTreeFlattened {
Left err -> error ("malformed top-level PDF object: *** " ++ objStr ++ "ERR:" ++ (show err) ++ "***\n")
Right obj -> obj
catalogObj = case (Map.lookup (PDFKey "Root") trailerDict) of
Just rr@(PDFReference n g) -> (parsedObjectMap Map.! n)
Just rd@(PDFDict rdict) -> rd
Just (PDFReference n _) -> (parsedObjectMap Map.! n)
Just rd@(PDFDict _) -> rd
Just er -> error ("bad value for Root object in catalog dictionary" ++ (show er))
_ -> error ("no Root key/value in catalog dictionary: " ++ (show trailerDict))

Expand All @@ -81,7 +82,7 @@ recursivelyParse objectMap (PDFDict d) = (PDFDict (Map.map (recursivelyParse ob

-- trevor says "you could use an exception transformer" here.
recursivelyParse objectMap (PDFReference n _) = recursivelyParse objectMap (objectMap Map.! n)
recursivelyParse objectMap (PDFStream s) = (PDFStream s) -- though some funky PDFs could put the length as a reference
recursivelyParse _ (PDFStream s) = (PDFStream s) -- though some funky PDFs could put the length as a reference
recursivelyParse objectMap (PDFArray a) = (PDFArray (Prelude.map (recursivelyParse objectMap) a))

-- any remaining ones better not be recursively defined, because:
Expand Down Expand Up @@ -145,7 +146,7 @@ flattenPageTree' (PDFArray arr) = arr
flattenPageTree' obj@(PDFDict d) = case Map.lookup (PDFKey "Type") d of
Just (PDFSymbol "Pages") -> listOfKids where
kidTrees = case Map.lookup (PDFKey "Kids") d of
Just arr@(PDFArray kidArray) -> kidArray
Just (PDFArray kidArray) -> kidArray
_ -> error "wonky Pages node in Page Tree"
listOfKids = concat (Prelude.map flattenPageTree' kidTrees)
Just (PDFSymbol "Page") -> [obj]
Expand All @@ -154,7 +155,7 @@ flattenPageTree' obj@(PDFDict d) = case Map.lookup (PDFKey "Type") d of
Just dict@(PDFDict _id) -> flattenPageTree' dict
_ -> error "bad missing /Pages key in catalog dict"
_ -> error ("gak: neither Page nor Pages in flattenPageTree': " ++ (ppPDFObject 0 obj))
flattenPageTree' x = [(PDFError "how did this get into digestPageTree")]
flattenPageTree' _ = [(PDFError "how did this get into digestPageTree")]

-- parsec functions
run :: Show a => Parser a -> String -> IO ()
Expand Down
6 changes: 3 additions & 3 deletions Text/PDF/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import Data.Map as Map
import Data.Array as Array
import Data.Maybe

import Text.PDF.Types
import Text.PDF.Types hiding ( dictMap )

traversePDFReference :: PDFObject -> PDFObjectTreeFlattened -> PDFObject
traversePDFReference (PDFReference objNum _g) (PDFObjectTreeFlattened _ objMap ) =
Expand Down Expand Up @@ -50,8 +50,8 @@ ppPDFObject i (PDFDict m) = (indent i) ++ "Dict:\n" ++ (concat (Prelude.map (ppP

ppPDFObject i (PDFArray a) = (indent i) ++ "[" ++ (concat (Prelude.map (ppPDFObject (i+1)) a)) ++ "]"

ppPDFObject i (PDFSymbol s) = "/" ++ s ++ " "
ppPDFObject i (PDFInt n) = (show n) ++ " "
ppPDFObject _ (PDFSymbol s) = "/" ++ s ++ " "
ppPDFObject _ (PDFInt n) = (show n) ++ " "

ppPDFObject i o = (indent i) ++ (show o) ++ " "

Expand Down

0 comments on commit b83beca

Please # to comment.