Reuse Parser type in PDF.Body (and generalize the type of the comment parser)

This commit is contained in:
Tissevert 2019-05-15 09:04:17 +02:00
parent 91292d6401
commit 44508a204c
2 changed files with 5 additions and 7 deletions

View File

@ -1,16 +1,13 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
module PDF.Body ( module PDF.Body where
populate
) where
import Data.ByteString.Lazy.Char8 (ByteString) import Data.ByteString.Lazy.Char8 (ByteString)
import qualified Data.ByteString.Lazy.Char8 as BS (drop, pack) import qualified Data.ByteString.Lazy.Char8 as BS (drop, pack)
import Data.Functor.Identity (Identity)
import Data.Int (Int64) import Data.Int (Int64)
import qualified Data.Map as Map (insert, lookup) import qualified Data.Map as Map (insert, lookup)
import PDF.Object ( import PDF.Object (
Content(..), DirectObject(..), IndirectObjCoordinates(..), Object(..) Content(..), DirectObject(..), IndirectObjCoordinates(..), Object(..)
, Occurrence(..), XRefEntry(..), XRefSection, XRefSubSection(..) , Occurrence(..), Parser, XRefEntry(..), XRefSection, XRefSubSection(..)
, eol, eolCharset, dictionary, directObject, integer, line , eol, eolCharset, dictionary, directObject, integer, line
) )
import Text.Parsec import Text.Parsec
@ -20,7 +17,7 @@ data UserState = UserState {
, content :: Content , content :: Content
} }
type SParser = ParsecT ByteString UserState Identity type SParser = Parser UserState
modifyContent :: (Content -> Content) -> SParser () modifyContent :: (Content -> Content) -> SParser ()
modifyContent f = modifyState $ \state -> state {content = f $ content state} modifyContent f = modifyState $ \state -> state {content = f $ content state}
@ -35,7 +32,7 @@ pushOccurrence newOccurrence = modifyContent $ \content -> content {
body = newOccurrence : (body content) body = newOccurrence : (body content)
} }
comment :: SParser String comment :: Parser u String
comment = char '%' *> many (noneOf eolCharset) <* eol comment = char '%' *> many (noneOf eolCharset) <* eol
lookupOffset :: Int -> XRefSection -> Maybe Int64 lookupOffset :: Int -> XRefSection -> Maybe Int64

View File

@ -6,6 +6,7 @@ module PDF.Object (
, IndirectObjCoordinates(..) , IndirectObjCoordinates(..)
, Object(..) , Object(..)
, Occurrence(..) , Occurrence(..)
, Parser
, XRefEntry(..) , XRefEntry(..)
, XRefSection , XRefSection
, XRefSubSection(..) , XRefSubSection(..)