{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}
module PDF.ContentStream
( parseStream
, parseColorSpace
) where
import Data.Char (chr, ord)
import Data.String (fromString)
import Data.List (isPrefixOf, dropWhileEnd)
import Numeric (readOct, readHex)
import Data.Maybe (fromMaybe)
import qualified Data.Map as Map
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy.Char8 as BSLC (ByteString, pack)
import qualified Data.ByteString.Char8 as BSSC (unpack)
import qualified Data.ByteString.Lazy.UTF8 as BSLU (toString)
import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8)
import Text.Parsec hiding (many, (<|>))
import Text.Parsec.ByteString.Lazy
import Control.Applicative
import Debug.Trace
import PDF.Definition
import PDF.Object
import PDF.Character (pdfcharmap, extendedAscii, adobeJapanOneSixMap)
type PSParser a = GenParser Char PSR a
parseContentStream :: Parsec s u a -> u -> s -> Either ParseError a
parseContentStream Parsec s u a
p u
st = Parsec s u a -> u -> SourceName -> s -> Either ParseError a
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> SourceName -> s -> Either ParseError a
runParser Parsec s u a
p u
st SourceName
""
parseStream :: PSR -> PDFStream -> PDFStream
parseStream :: PSR -> PDFStream -> PDFStream
parseStream PSR
psr PDFStream
pdfstream =
case Parsec PDFStream PSR Text
-> PSR -> PDFStream -> Either ParseError Text
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> s -> Either ParseError a
parseContentStream ([Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT PDFStream PSR Identity [Text]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Text]
-> ParsecT PDFStream PSR Identity [Text]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parsec PDFStream PSR Text -> ParsecT PDFStream PSR Identity [Text]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
elems Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
skipOther))) PSR
psr PDFStream
pdfstream of
Left ParseError
err -> SourceName -> PDFStream
forall a. HasCallStack => SourceName -> a
error (SourceName -> PDFStream) -> SourceName -> PDFStream
forall a b. (a -> b) -> a -> b
$ SourceName
"Nothing to be parsed: " SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ (ParseError -> SourceName
forall a. Show a => a -> SourceName
show ParseError
err)
Right Text
str -> SourceName -> PDFStream
BSLC.pack (SourceName -> PDFStream) -> SourceName -> PDFStream
forall a b. (a -> b) -> a -> b
$ ByteString -> SourceName
BSSC.unpack (ByteString -> SourceName) -> ByteString -> SourceName
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
str
parseColorSpace :: PSR -> BSLC.ByteString -> [T.Text]
parseColorSpace :: PSR -> PDFStream -> [Text]
parseColorSpace PSR
psr PDFStream
pdfstream =
case ParsecT PDFStream PSR Identity [Text]
-> PSR -> PDFStream -> Either ParseError [Text]
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> s -> Either ParseError a
parseContentStream (Parsec PDFStream PSR Text -> ParsecT PDFStream PSR Identity [Text]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ([Parsec PDFStream PSR Text] -> Parsec PDFStream PSR Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
colorSpace
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT PDFStream PSR Identity [Text]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT PDFStream PSR Identity [Text]
xObject
, (Text
T.empty Text -> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Parsec PDFStream PSR Text
elems)
])) PSR
psr PDFStream
pdfstream of
Left ParseError
err -> SourceName -> [Text]
forall a. HasCallStack => SourceName -> a
error SourceName
"Nothing to be parsed"
Right [Text]
str -> [Text]
str
elems :: PSParser T.Text
elems :: Parsec PDFStream PSR Text
elems = [Parsec PDFStream PSR Text] -> Parsec PDFStream PSR Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopBT
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTf
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTD
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTd
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTm
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTc
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTs
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTw
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTL
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTz
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTj
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTJ
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTr
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfQuote
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfDoubleQuote
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopTast
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
letters Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
hexletters Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
array Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopGraphics
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
dashPattern
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Text]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT PDFStream PSR Identity [Text]
xObject
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
graphicState
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopcm
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text -> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Parsec PDFStream PSR Text
colorSpace
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text -> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Parsec PDFStream PSR Text
renderingIntent
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopBDC
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopBMC
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
pdfopEMC
, Parsec PDFStream PSR Text
unknowns
]
pdfopGraphics :: PSParser T.Text
pdfopGraphics :: Parsec PDFStream PSR Text
pdfopGraphics = do
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[Parsec PDFStream PSR Text] -> Parsec PDFStream PSR Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"qQ" Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"fFbBW" Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity [SourceName]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [SourceName]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [SourceName])
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [SourceName]
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"*") Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"nsS" Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity Double
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"jJM" Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity Double
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"dwi" Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"ml" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"vy" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"re" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"SCN" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"scn" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"SC" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"sc" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity [Double]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"c" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty Text
-> ParsecT PDFStream PSR Identity Char -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"h" Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
]
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
T.empty
graphicState :: PSParser T.Text
graphicState :: Parsec PDFStream PSR Text
graphicState = do
SourceName
gs <- SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space)
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"gs"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
T.empty
colorSpace :: PSParser T.Text
colorSpace :: Parsec PDFStream PSR Text
colorSpace = do
SourceName
gs <- [ParsecT PDFStream PSR Identity SourceName]
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space) ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"CS" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"cs") ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName
"DeviceRGB" SourceName
-> ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"rg" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName
"DeviceRGB" SourceName
-> ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"RG" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
, ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName
"DeviceGray" SourceName
-> ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"gG" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName
"DeviceCMYK" SourceName
-> ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity [Double]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Double
digitParam ParsecT PDFStream PSR Identity Double
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity Double
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces) ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"kK" ParsecT PDFStream PSR Identity [Double]
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Double]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
]
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s {colorspace :: SourceName
colorspace = SourceName
gs})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack SourceName
gs
dashPattern :: PSParser T.Text
dashPattern :: Parsec PDFStream PSR Text
dashPattern = do
Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'[' ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']' ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"d"
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
T.empty
renderingIntent :: PSParser T.Text
renderingIntent :: Parsec PDFStream PSR Text
renderingIntent = do
SourceName
ri <- [ParsecT PDFStream PSR Identity SourceName]
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space) ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"ri" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
, ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space) ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Intent" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
]
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack SourceName
ri
xObject :: PSParser [T.Text]
xObject :: ParsecT PDFStream PSR Identity [Text]
xObject = do
SourceName
n <- SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space)
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Do"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let xobjcs :: [SourceName]
xobjcs = PSR -> [SourceName]
xcolorspaces PSR
st
[Text] -> ParsecT PDFStream PSR Identity [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> ParsecT PDFStream PSR Identity [Text])
-> [Text] -> ParsecT PDFStream PSR Identity [Text]
forall a b. (a -> b) -> a -> b
$ (SourceName -> Text) -> [SourceName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map SourceName -> Text
T.pack [SourceName]
xobjcs
pdfopBT :: PSParser T.Text
pdfopBT :: Parsec PDFStream PSR Text
pdfopBT = do
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s{text_m :: (Double, Double, Double, Double, Double, Double)
text_m = (Double
1,Double
0,Double
0,Double
1,Double
0,Double
0), text_break :: Bool
text_break = Bool
False})
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"BT"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[Text]
t <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill Parsec PDFStream PSR Text
elems (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"ET")
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
t
pdfopBMC :: PSParser T.Text
pdfopBMC :: Parsec PDFStream PSR Text
pdfopBMC = do
SourceName
n <- SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space)
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"BMC"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill Parsec PDFStream PSR Text
elems (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"EMC")
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
T.empty
pdfopBDC :: PSParser T.Text
pdfopBDC :: Parsec PDFStream PSR Text
pdfopBDC = do
Text
n1 <- Parsec PDFStream PSR Text
name Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec PDFStream PSR Text
propertyList
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"BDC"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
T.empty
pdfopEMC :: PSParser T.Text
pdfopEMC :: Parsec PDFStream PSR Text
pdfopEMC = do
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"EMC"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
T.empty
propertyList :: PSParser T.Text
propertyList :: Parsec PDFStream PSR Text
propertyList = ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT PDFStream PSR Identity ()
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Parsec PDFStream PSR Text] -> Parsec PDFStream PSR Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
dictionary, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
name]
dictionary :: PSParser T.Text
dictionary :: Parsec PDFStream PSR Text
dictionary = [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT PDFStream PSR Identity [Text]
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"<<" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Text]
-> ParsecT PDFStream PSR Identity [Text]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Text]
-> ParsecT PDFStream PSR Identity [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill Parsec PDFStream PSR Text
dictEntry (ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
">>" ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ())
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
">"))))
dictEntry :: PSParser T.Text
dictEntry :: Parsec PDFStream PSR Text
dictEntry = [Parsec PDFStream PSR Text] -> Parsec PDFStream PSR Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
name
, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
letters
, SourceName -> Text
T.pack (SourceName -> Text)
-> ParsecT PDFStream PSR Identity SourceName
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity SourceName
forall u. ParsecT PDFStream u Identity SourceName
hex
, SourceName -> Text
T.pack (SourceName -> Text)
-> ParsecT PDFStream PSR Identity SourceName
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit)
] Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity () -> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
where
hex :: ParsecT PDFStream u Identity SourceName
hex = SourceName -> ParsecT PDFStream u Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"<" ParsecT PDFStream u Identity SourceName
-> ParsecT PDFStream u Identity SourceName
-> ParsecT PDFStream u Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT PDFStream u Identity Char
-> ParsecT PDFStream u Identity SourceName
-> ParsecT PDFStream u Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (SourceName -> ParsecT PDFStream u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"0123456789abcdefABCDEF") (ParsecT PDFStream u Identity SourceName
-> ParsecT PDFStream u Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream u Identity SourceName
-> ParsecT PDFStream u Identity SourceName)
-> ParsecT PDFStream u Identity SourceName
-> ParsecT PDFStream u Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream u Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
">"))
name :: PSParser T.Text
name :: Parsec PDFStream PSR Text
name = SourceName -> Text
T.pack (SourceName -> Text)
-> ParsecT PDFStream PSR Identity SourceName
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"><][)( \n\r/")) ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity ()
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
pdfopTj :: PSParser T.Text
pdfopTj :: Parsec PDFStream PSR Text
pdfopTj = do
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[Text]
t <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (Parsec PDFStream PSR Text
letters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
hexletters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
array) (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Tj")
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let needBreak :: Bool
needBreak = PSR -> Bool
text_break PSR
st
t' :: [Text]
t' = (if Bool
needBreak then (Text
"\n"Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
t) else [Text]
t)
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s{text_break :: Bool
text_break = Bool
False})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
t'
pdfopTJ :: PSParser T.Text
pdfopTJ :: Parsec PDFStream PSR Text
pdfopTJ = do
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[Text]
t <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill Parsec PDFStream PSR Text
array (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"TJ")
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let needBreak :: Bool
needBreak = PSR -> Bool
text_break PSR
st
t' :: [Text]
t' = (if Bool
needBreak then (Text
""Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
t) else [Text]
t)
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s{text_break :: Bool
text_break = Bool
False})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
t'
pdfDoubleQuote :: PSParser T.Text
pdfDoubleQuote :: Parsec PDFStream PSR Text
pdfDoubleQuote = do
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[Text]
t <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (Parsec PDFStream PSR Text
letters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
hexletters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
array) (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\"")
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
t
pdfQuote :: PSParser T.Text
pdfQuote :: Parsec PDFStream PSR Text
pdfQuote = do
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[Text]
t <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (Parsec PDFStream PSR Text
letters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
hexletters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
array) (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\'")
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
t
unknowns :: PSParser T.Text
unknowns :: Parsec PDFStream PSR Text
unknowns = do
SourceName
ps <- ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"\r\n")
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ case Parsec PDFStream PSR Text
-> PSR -> SourceName -> PDFStream -> Either ParseError Text
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> SourceName -> s -> Either ParseError a
runParser Parsec PDFStream PSR Text
elems PSR
st SourceName
"" (PDFStream -> Either ParseError Text)
-> PDFStream -> Either ParseError Text
forall a b. (a -> b) -> a -> b
$ SourceName -> PDFStream
BSLC.pack (((Char -> Bool) -> SourceName -> SourceName
forall a. (a -> Bool) -> [a] -> [a]
Data.List.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'\\') SourceName
ps)SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++SourceName
")Tj") of
Right Text
xs -> Text
xs
Left ParseError
e -> case Parsec PDFStream PSR Text
-> PSR -> SourceName -> PDFStream -> Either ParseError Text
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> SourceName -> s -> Either ParseError a
runParser Parsec PDFStream PSR Text
elems PSR
st SourceName
"" (PDFStream -> Either ParseError Text)
-> PDFStream -> Either ParseError Text
forall a b. (a -> b) -> a -> b
$ SourceName -> PDFStream
BSLC.pack (SourceName
"("SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++SourceName
ps) of
Right Text
xs -> Text
xs
Left ParseError
e -> case SourceName
ps of
SourceName
"" -> Text
""
SourceName
otherwise -> SourceName -> Text
T.pack (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$ SourceName
"[[[UNKNOWN STREAM:" SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ Int -> SourceName -> SourceName
forall a. Int -> [a] -> [a]
take Int
100 (SourceName -> SourceName
forall a. Show a => a -> SourceName
show SourceName
ps) SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ SourceName
"]]]"
skipOther :: PSParser T.Text
skipOther :: Parsec PDFStream PSR Text
skipOther = do
SourceName
a <- ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"\r\n")
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
array :: PSParser T.Text
array :: Parsec PDFStream PSR Text
array = do
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'['
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[Text]
str <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (Parsec PDFStream PSR Text
letters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
hexletters Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
kern) (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']')
let needBreak :: Bool
needBreak = PSR -> Bool
text_break PSR
st
t' :: [Text]
t' = (if Bool
needBreak then Text
"\n"Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
str else [Text]
str)
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s{text_break :: Bool
text_break = Bool
False})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
t'
letters :: PSParser T.Text
letters :: Parsec PDFStream PSR Text
letters = do
Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'('
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let cmap :: [(Int, SourceName)]
cmap = [(Int, SourceName)]
-> Maybe [(Int, SourceName)] -> [(Int, SourceName)]
forall a. a -> Maybe a -> a
fromMaybe [] (SourceName
-> [(SourceName, [(Int, SourceName)])] -> Maybe [(Int, SourceName)]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (PSR -> SourceName
curfont PSR
st) (PSR -> [(SourceName, [(Int, SourceName)])]
cmaps PSR
st))
letterParser :: Parsec PDFStream PSR Text
letterParser = case SourceName -> [(SourceName, Encoding)] -> Maybe Encoding
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (PSR -> SourceName
curfont PSR
st) (PSR -> [(SourceName, Encoding)]
fontmaps PSR
st) of
Just (Encoding [(Char, SourceName)]
m) -> [(Char, SourceName)] -> Parsec PDFStream PSR Text
psletter [(Char, SourceName)]
m
Just (CIDmap SourceName
s) -> SourceName -> Parsec PDFStream PSR Text
cidletter SourceName
s
Just (WithCharSet SourceName
s) -> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text)
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [(Int, SourceName)] -> Parsec PDFStream PSR Text
bytesletter [(Int, SourceName)]
cmap Parsec PDFStream PSR Text
-> Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parsec PDFStream PSR Text
cidletters
Just Encoding
NullMap -> [(Char, SourceName)] -> Parsec PDFStream PSR Text
psletter []
Maybe Encoding
Nothing -> (SourceName -> Text
T.pack) (SourceName -> Text)
-> ParsecT PDFStream PSR Identity SourceName
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ [ParsecT PDFStream PSR Identity Char]
-> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char
')' Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\)")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char
'(' Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\(")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
")"
])
[Text]
lets <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill Parsec PDFStream PSR Text
letterParser (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Text])
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Text]
forall a b. (a -> b) -> a -> b
$ (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')')
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
lets
bytesletter :: CMap -> PSParser T.Text
bytesletter :: [(Int, SourceName)] -> Parsec PDFStream PSR Text
bytesletter [(Int, SourceName)]
cmap = do
SourceName
txt <- (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ [ParsecT PDFStream PSR Identity Char]
-> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char
')' Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\)")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char
'(' Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\(")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
10) Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\n")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
13) Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\r")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
8) Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\b")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
9) Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\t")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
12) Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\f")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
92) Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\\\")
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
0) Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\NUL')
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ (Int -> Char
chr Int
32) Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
' ')
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Int -> Char
chr (Int -> Char)
-> ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\") ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT PDFStream PSR Identity Int
octnum)
, ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
")"
])
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [(Int, SourceName)] -> SourceName -> Text
byteStringToText [(Int, SourceName)]
cmap SourceName
txt
where
byteStringToText :: CMap -> String -> T.Text
byteStringToText :: [(Int, SourceName)] -> SourceName -> Text
byteStringToText [(Int, SourceName)]
cmap SourceName
str = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Int -> Text) -> [Int] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ([(Int, SourceName)] -> Int -> Text
toUcs [(Int, SourceName)]
cmap) ([Int] -> [Text]) -> [Int] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Int] -> [Int]
asInt16 ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ (Char -> Int) -> SourceName -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Int
ord SourceName
str
asInt16 :: [Int] -> [Int]
asInt16 :: [Int] -> [Int]
asInt16 [] = []
asInt16 (Int
a:[]) = [Int
a]
asInt16 (Int
a:Int
b:[Int]
rest) = (Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
256 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
b)Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:([Int] -> [Int]
asInt16 [Int]
rest)
hexletters :: PSParser T.Text
hexletters :: Parsec PDFStream PSR Text
hexletters = do
Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'<'
[Text]
lets <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill Parsec PDFStream PSR Text
hexletter (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'>')
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
lets
octletters :: PSParser T.Text
octletters :: Parsec PDFStream PSR Text
octletters = do
Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'('
[Text]
lets <- Parsec PDFStream PSR Text
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill Parsec PDFStream PSR Text
octletter (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')')
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
lets
adobeOneSix :: Int -> T.Text
adobeOneSix :: Int -> Text
adobeOneSix Int
a = case Int -> Map Int PDFStream -> Maybe PDFStream
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Int
a Map Int PDFStream
adobeJapanOneSixMap of
Just PDFStream
cs -> SourceName -> Text
T.pack (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$ PDFStream -> SourceName
BSLU.toString PDFStream
cs
Maybe PDFStream
Nothing -> SourceName -> Text
T.pack (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$ SourceName
"[" SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ (Int -> SourceName
forall a. Show a => a -> SourceName
show Int
a) SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ SourceName
"]"
toUcs :: CMap -> Int -> T.Text
toUcs :: [(Int, SourceName)] -> Int -> Text
toUcs [(Int, SourceName)]
m Int
h = case Int -> [(Int, SourceName)] -> Maybe SourceName
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Int
h [(Int, SourceName)]
m of
Just SourceName
ucs -> SourceName -> Text
T.pack SourceName
ucs
Maybe SourceName
Nothing -> if [(Int, SourceName)]
m [(Int, SourceName)] -> [(Int, SourceName)] -> Bool
forall a. Eq a => a -> a -> Bool
== [] then Int -> Text
adobeOneSix Int
h else SourceName -> Text
T.pack [Int -> Char
chr Int
h]
cidletters :: Parsec PDFStream PSR Text
cidletters = [Parsec PDFStream PSR Text] -> Parsec PDFStream PSR Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
hexletter, Parsec PDFStream PSR Text -> Parsec PDFStream PSR Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec PDFStream PSR Text
octletter]
hexletter :: PSParser T.Text
hexletter :: Parsec PDFStream PSR Text
hexletter = do
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let font :: SourceName
font = PSR -> SourceName
curfont PSR
st
cmap :: [(Int, SourceName)]
cmap = [(Int, SourceName)]
-> Maybe [(Int, SourceName)] -> [(Int, SourceName)]
forall a. a -> Maybe a -> a
fromMaybe [] (SourceName
-> [(SourceName, [(Int, SourceName)])] -> Maybe [(Int, SourceName)]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup SourceName
font (PSR -> [(SourceName, [(Int, SourceName)])]
cmaps PSR
st))
([(Int, SourceName)] -> [(Int, SourceName)] -> Text
forall a.
(Eq a, IsString a) =>
[(Int, SourceName)] -> [(Int, a)] -> Text
hexToString [(Int, SourceName)]
cmap ([(Int, SourceName)] -> Text)
-> (SourceName -> [(Int, SourceName)]) -> SourceName -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceName -> [(Int, SourceName)]
forall a. (Eq a, Num a) => ReadS a
readHex) (SourceName -> Text)
-> ParsecT PDFStream PSR Identity SourceName
-> Parsec PDFStream PSR Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsecT PDFStream PSR Identity SourceName]
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ Int
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
4 (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"0123456789ABCDEFabcdef"
, ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ Int
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
2 (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"0123456789ABCDEFabcdef"
, ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ (Char -> SourceName -> SourceName
forall a. a -> [a] -> [a]
:SourceName
"0") (Char -> SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"0123456789ABCDEFabcdef")
]
where hexToString :: [(Int, SourceName)] -> [(Int, a)] -> Text
hexToString [(Int, SourceName)]
m [(Int
h,a
"")] = [(Int, SourceName)] -> Int -> Text
toUcs [(Int, SourceName)]
m Int
h
hexToString [(Int, SourceName)]
_ [(Int, a)]
_ = Text
"????"
octletter :: PSParser T.Text
octletter :: Parsec PDFStream PSR Text
octletter = do
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let cmap :: [(Int, SourceName)]
cmap = [(Int, SourceName)]
-> Maybe [(Int, SourceName)] -> [(Int, SourceName)]
forall a. a -> Maybe a -> a
fromMaybe [] (SourceName
-> [(SourceName, [(Int, SourceName)])] -> Maybe [(Int, SourceName)]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (PSR -> SourceName
curfont PSR
st) (PSR -> [(SourceName, [(Int, SourceName)])]
cmaps PSR
st))
Int
o <- ParsecT PDFStream PSR Identity Int
octnum
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [(Int, SourceName)] -> Int -> Text
toUcs [(Int, SourceName)]
cmap Int
o
psletter :: [(Char,String)] -> PSParser T.Text
psletter :: [(Char, SourceName)] -> Parsec PDFStream PSR Text
psletter [(Char, SourceName)]
fontmap = do
Char
c <- ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"\\()")
ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([(Int, SourceName)] -> Char
forall a. (Eq a, IsString a) => [(Int, a)] -> Char
octToChar ([(Int, SourceName)] -> Char)
-> (SourceName -> [(Int, SourceName)]) -> SourceName -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceName -> [(Int, SourceName)]
forall a. (Eq a, Num a) => ReadS a
readOct (SourceName -> Char)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Int
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
3 (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"01234567")))
ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
"\\"
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ [(Char, SourceName)] -> Char -> Text
replaceWithDiff [(Char, SourceName)]
fontmap Char
c
where replaceWithDiff :: [(Char, SourceName)] -> Char -> Text
replaceWithDiff [(Char, SourceName)]
m Char
c' = case Char -> [(Char, SourceName)] -> Maybe SourceName
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Char
c' [(Char, SourceName)]
m of
Just SourceName
s -> SourceName -> Text
replaceWithCharDict SourceName
s
Maybe SourceName
Nothing -> SourceName -> Text
T.pack [Char
c']
replaceWithCharDict :: SourceName -> Text
replaceWithCharDict SourceName
s = case SourceName -> Map SourceName Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup SourceName
s Map SourceName Text
pdfcharmap of
Just Text
cs -> Text
cs
Maybe Text
Nothing -> if SourceName
"/uni" SourceName -> SourceName -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` SourceName
s
then SourceName -> Text
readUni SourceName
s
else SourceName -> Text
T.pack SourceName
s
readUni :: SourceName -> Text
readUni SourceName
s = case SourceName -> [(Int, SourceName)]
forall a. (Eq a, Num a) => ReadS a
readHex (Int -> SourceName -> SourceName
forall a. Int -> [a] -> [a]
drop Int
4 SourceName
s) of
[(Int
i,SourceName
"")] -> Char -> Text
T.singleton (Char -> Text) -> Char -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Char
chr Int
i
[(Int
i,SourceName
x)] -> SourceName -> Text
T.pack (Int -> Char
chr Int
i Char -> SourceName -> SourceName
forall a. a -> [a] -> [a]
: SourceName
" ")
[(Int, SourceName)]
_ -> SourceName -> Text
T.pack SourceName
s
octToChar :: [(Int, a)] -> Char
octToChar [(Int
o,a
"")] = case Int -> Map Int Char -> Maybe Char
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Int
o Map Int Char
extendedAscii of
Just Char
c -> Char
c
Maybe Char
Nothing -> Int -> Char
chr Int
o
octToChar [(Int, a)]
_ = Char
'?'
cidletter :: String -> PSParser T.Text
cidletter :: SourceName -> Parsec PDFStream PSR Text
cidletter SourceName
cidmapName = do
Int
o1 <- ParsecT PDFStream PSR Identity Int
octnum
Int
o2 <- ParsecT PDFStream PSR Identity Int
octnum
let d :: Int
d = Int
256 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
o1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
o2
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$
if SourceName
cidmapName SourceName -> SourceName -> Bool
forall a. Eq a => a -> a -> Bool
== SourceName
"Adobe-Japan1"
then Int -> Text
adobeOneSix Int
d
else SourceName -> Text
forall a. HasCallStack => SourceName -> a
error (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$ SourceName
"Unknown cidmap" SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ SourceName
cidmapName
octnum :: PSParser Int
octnum :: ParsecT PDFStream PSR Identity Int
octnum = do
Int
d <- [ParsecT PDFStream PSR Identity Int]
-> ParsecT PDFStream PSR Identity Int
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int)
-> ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int
forall a b. (a -> b) -> a -> b
$ Char -> Int
escapedToDec (Char -> Int)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"nrtbf()\\")
, ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int)
-> ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int
forall a b. (a -> b) -> a -> b
$ [(Int, SourceName)] -> Int
forall a p. (Eq a, IsString a) => [(p, a)] -> p
octToDec ([(Int, SourceName)] -> Int)
-> (SourceName -> [(Int, SourceName)]) -> SourceName -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceName -> [(Int, SourceName)]
forall a. (Eq a, Num a) => ReadS a
readOct (SourceName -> Int)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Int
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
3 (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"01234567"))
, ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int)
-> ParsecT PDFStream PSR Identity Int
-> ParsecT PDFStream PSR Identity Int
forall a b. (a -> b) -> a -> b
$ Char -> Int
ord (Char -> Int)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceName -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
"\\"
]
Int -> ParsecT PDFStream PSR Identity Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ParsecT PDFStream PSR Identity Int)
-> Int -> ParsecT PDFStream PSR Identity Int
forall a b. (a -> b) -> a -> b
$ Int
d
where
octToDec :: [(p, a)] -> p
octToDec [(p
o, a
"")] = p
o
octToDec [(p, a)]
_ = SourceName -> p
forall a. HasCallStack => SourceName -> a
error SourceName
"Unable to take Character in Octet"
escapedToDec :: Char -> Int
escapedToDec Char
'n' = Char -> Int
ord Char
'\n'
escapedToDec Char
'r' = Char -> Int
ord Char
'\r'
escapedToDec Char
't' = Char -> Int
ord Char
'\t'
escapedToDec Char
'b' = Char -> Int
ord Char
'\b'
escapedToDec Char
'f' = Char -> Int
ord Char
'\f'
escapedToDec Char
'\\' = Char -> Int
ord Char
'\\'
escapedToDec Char
_ = Int
0
kern :: PSParser T.Text
kern :: Parsec PDFStream PSR Text
kern = do
Double
t <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ if Double
t Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< -Double
60.0 then Text
" " else Text
""
pdfopTf :: PSParser T.Text
pdfopTf :: Parsec PDFStream PSR Text
pdfopTf = do
SourceName
font <- SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"/" ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space)
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
t <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Tf"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s{ curfont :: SourceName
curfont = SourceName
font
, fontfactor :: Double
fontfactor = Double
t
, linex :: Double
linex = Double
t
, liney :: Double
liney = Double
t})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
pdfopTD :: PSParser T.Text
pdfopTD :: Parsec PDFStream PSR Text
pdfopTD = do
Double
t1 <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
t2 <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"TD"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ax :: Double
ax = PSR -> Double
absolutex PSR
st
ay :: Double
ay = PSR -> Double
absolutey PSR
st
lx :: Double
lx = PSR -> Double
linex PSR
st
ly :: Double
ly = PSR -> Double
liney PSR
st
lm :: Double
lm = PSR -> Double
leftmargin PSR
st
ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(Double
a,Double
b,Double
c,Double
d,Double
tmx,Double
tmy) = PSR -> (Double, Double, Double, Double, Double, Double)
text_m PSR
st
needBreakByX :: Bool
needBreakByX = Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
ax
needBreakByY :: Bool
needBreakByY = Double -> Double
forall a. Num a => a -> a
abs (Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
ay) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ff
needBreak :: Bool
needBreak = (Bool
needBreakByX Bool -> Bool -> Bool
|| Bool
needBreakByY) Bool -> Bool -> Bool
&& Bool -> Bool
not (PSR -> Bool
text_break PSR
st)
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s { absolutex :: Double
absolutex = if Bool
needBreak then Double
0 else Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx
, absolutey :: Double
absolutey = Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy
, liney :: Double
liney = -Double
t2
, text_m :: (Double, Double, Double, Double, Double, Double)
text_m = (Double
a,Double
b,Double
c,Double
d, Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx, Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy)
, text_break :: Bool
text_break = Bool
needBreak
})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ if Bool
needBreak
then (Double -> Double -> Double -> Double -> Double -> Double -> Text
desideParagraphBreak Double
t1 Double
t2 Double
lx Double
ly Double
lm Double
ff)
else if Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ax Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
2Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
ff
then Text
" " else Text
""
pdfopTd :: PSParser T.Text
pdfopTd :: Parsec PDFStream PSR Text
pdfopTd = do
Double
t1 <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
t2 <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Td"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ax :: Double
ax = PSR -> Double
absolutex PSR
st
ay :: Double
ay = PSR -> Double
absolutey PSR
st
lx :: Double
lx = PSR -> Double
linex PSR
st
ly :: Double
ly = PSR -> Double
liney PSR
st
lm :: Double
lm = PSR -> Double
leftmargin PSR
st
ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(Double
a,Double
b,Double
c,Double
d,Double
tmx,Double
tmy) = PSR -> (Double, Double, Double, Double, Double, Double)
text_m PSR
st
needBreakByX :: Bool
needBreakByX = Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
ax
needBreakByY :: Bool
needBreakByY = Double -> Double
forall a. Num a => a -> a
abs (Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
ay) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ff
needBreak :: Bool
needBreak = (Bool
needBreakByX Bool -> Bool -> Bool
|| Bool
needBreakByY) Bool -> Bool -> Bool
&& Bool -> Bool
not (PSR -> Bool
text_break PSR
st)
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s { absolutex :: Double
absolutex = if Bool
needBreak then Double
0 else Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx
, absolutey :: Double
absolutey = Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy
, linex :: Double
linex = Double
lx
, liney :: Double
liney = Double
ly
, text_m :: (Double, Double, Double, Double, Double, Double)
text_m = (Double
a,Double
b,Double
c,Double
d, Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx, Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy)
, text_break :: Bool
text_break = Bool
needBreak
})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ if Bool
needBreak
then (Double -> Double -> Double -> Double -> Double -> Double -> Text
desideParagraphBreak Double
t1 Double
t2 Double
lx Double
ly Double
lm Double
ff)
else if Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
t2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ax Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
2Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
ff
then Text
" " else Text
""
pdfopTw :: PSParser T.Text
pdfopTw :: Parsec PDFStream PSR Text
pdfopTw = do
Double
tw <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Tw"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s { fontfactor :: Double
fontfactor = Double
tw
})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
""
pdfopTL :: PSParser T.Text
pdfopTL :: Parsec PDFStream PSR Text
pdfopTL = do
Double
tl <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"TL"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s { liney :: Double
liney = Double
ff Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tl
})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
""
pdfopTz :: PSParser T.Text
pdfopTz :: Parsec PDFStream PSR Text
pdfopTz = do
Double
tz <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Tz"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s { linex :: Double
linex = Double
ff Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tz
})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
""
pdfopTc :: PSParser T.Text
pdfopTc :: Parsec PDFStream PSR Text
pdfopTc = do
Double
tc <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Tc"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
""
pdfopTr :: PSParser T.Text
pdfopTr :: Parsec PDFStream PSR Text
pdfopTr = do
Double
tr <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Tr"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ff :: Double
ff = PSR -> Double
fontfactor PSR
st
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
""
pdfopTs :: PSParser T.Text
pdfopTs :: Parsec PDFStream PSR Text
pdfopTs = do
Double
tc <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Ts"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
""
desideParagraphBreak :: Double -> Double -> Double -> Double -> Double -> Double
-> T.Text
desideParagraphBreak :: Double -> Double -> Double -> Double -> Double -> Double -> Text
desideParagraphBreak Double
t1 Double
t2 Double
lx Double
ly Double
lm Double
ff = SourceName -> Text
T.pack (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$
(if Double -> Double
forall a. Num a => a -> a
abs Double
t2 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
1.8Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
ly Bool -> Bool -> Bool
|| (Double
lx Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
t1) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
lm
then SourceName
" "
else SourceName
"")
pdfopTm :: PSParser T.Text
pdfopTm :: Parsec PDFStream PSR Text
pdfopTm = do
Double
a <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
b <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
c <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
d <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
e <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
f <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"Tm"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ax :: Double
ax = PSR -> Double
absolutex PSR
st
ay :: Double
ay = PSR -> Double
absolutey PSR
st
lx :: Double
lx = PSR -> Double
linex PSR
st
ly :: Double
ly = PSR -> Double
liney PSR
st
lm :: Double
lm = PSR -> Double
leftmargin PSR
st
ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(Double
_,Double
_,Double
_,Double
_,Double
tmx,Double
tmy) = PSR -> (Double, Double, Double, Double, Double, Double)
text_m PSR
st
newff :: Double
newff = Double -> Double
forall a. Num a => a -> a
abs (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ (Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
+Double
d)Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2
needBreakByX :: Bool
needBreakByX = Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmx Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmy Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
e Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
ax
needBreakByY :: Bool
needBreakByY = Double -> Double
forall a. Num a => a -> a
abs (Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmx Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmy Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
f Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
ay) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ff
needBreak :: Bool
needBreak = (Bool
needBreakByX Bool -> Bool -> Bool
|| Bool
needBreakByY) Bool -> Bool -> Bool
&& Bool -> Bool
not (PSR -> Bool
text_break PSR
st)
newst :: PSR
newst = PSR
st { absolutex :: Double
absolutex = Double
e
, absolutey :: Double
absolutey = Double
f
, linex :: Double
linex = Double
lx
, liney :: Double
liney = Double
ly
, text_lm :: (Double, Double, Double, Double, Double, Double)
text_lm = (Double
a,Double
b,Double
c,Double
d,Double
e,Double
f)
, text_m :: (Double, Double, Double, Double, Double, Double)
text_m = (Double
a,Double
b,Double
c,Double
d,Double
e,Double
f)
, text_break :: Bool
text_break = Bool
needBreak
}
PSR -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
putState PSR
newst
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parsec PDFStream PSR Text)
-> Text -> Parsec PDFStream PSR Text
forall a b. (a -> b) -> a -> b
$ Text
T.empty
pdfopcm :: PSParser T.Text
pdfopcm :: Parsec PDFStream PSR Text
pdfopcm = do
Double
a <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
b <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
c <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
d <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
e <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Double
f <- ParsecT PDFStream PSR Identity Double
digitParam
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"cm"
ParsecT PDFStream PSR Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ax :: Double
ax = PSR -> Double
absolutex PSR
st
ay :: Double
ay = PSR -> Double
absolutey PSR
st
lx :: Double
lx = PSR -> Double
linex PSR
st
ly :: Double
ly = PSR -> Double
liney PSR
st
lm :: Double
lm = PSR -> Double
leftmargin PSR
st
ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(Double
_,Double
_,Double
_,Double
_,Double
tmx,Double
tmy) = PSR -> (Double, Double, Double, Double, Double, Double)
text_m PSR
st
needBreakByX :: Bool
needBreakByX = Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmx Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmy Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
e Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
ax
needBreakByY :: Bool
needBreakByY = Double -> Double
forall a. Num a => a -> a
abs (Double
bDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmx Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tmy Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
f Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
ay) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ff
needBreak :: Bool
needBreak = (Bool
needBreakByX Bool -> Bool -> Bool
|| Bool
needBreakByY) Bool -> Bool -> Bool
&& Bool -> Bool
not (PSR -> Bool
text_break PSR
st)
newst :: PSR
newst = PSR
st { absolutex :: Double
absolutex = Double
ax
, absolutey :: Double
absolutey = Double
ay
, linex :: Double
linex = Double
lx
, liney :: Double
liney = Double
ly
, text_lm :: (Double, Double, Double, Double, Double, Double)
text_lm = (Double
a,Double
b,Double
c,Double
d,Double
e,Double
f)
, text_m :: (Double, Double, Double, Double, Double, Double)
text_m = (Double
a,Double
b,Double
c,Double
d,Double
e,Double
f)
, text_break :: Bool
text_break = Bool
needBreak
}
PSR -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
putState PSR
newst
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
T.empty
pdfopTast :: PSParser T.Text
pdfopTast :: Parsec PDFStream PSR Text
pdfopTast = do
SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"T*"
PSR
st <- ParsecT PDFStream PSR Identity PSR
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let ax :: Double
ax = PSR -> Double
absolutex PSR
st
ay :: Double
ay = PSR -> Double
absolutey PSR
st
lx :: Double
lx = PSR -> Double
linex PSR
st
ly :: Double
ly = PSR -> Double
liney PSR
st
lm :: Double
lm = PSR -> Double
leftmargin PSR
st
ff :: Double
ff = PSR -> Double
fontfactor PSR
st
(Double
a,Double
b,Double
c,Double
d,Double
tmx,Double
tmy) = PSR -> (Double, Double, Double, Double, Double, Double)
text_m PSR
st
needBreakByX :: Bool
needBreakByX = Double
tmx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
ax
needBreakByY :: Bool
needBreakByY = Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
ly Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ly
needBreak :: Bool
needBreak = Bool
needBreakByX Bool -> Bool -> Bool
|| Bool
needBreakByY
(PSR -> PSR) -> ParsecT PDFStream PSR Identity ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\PSR
s -> PSR
s { absolutex :: Double
absolutex = if Bool
needBreak then Double
0 else Double
tmx
, absolutey :: Double
absolutey = Double
tmy Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
ly
, linex :: Double
linex = Double
lx
, liney :: Double
liney = Double
ly
, text_m :: (Double, Double, Double, Double, Double, Double)
text_m = (Double
a,Double
b,Double
c,Double
d, Double
cDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
ly Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmx, Double
dDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
ly Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
tmy)
, text_break :: Bool
text_break = Bool
needBreak
})
Text -> Parsec PDFStream PSR Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
digitParam :: PSParser Double
digitParam :: ParsecT PDFStream PSR Identity Double
digitParam = do
SourceName
sign <- ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'-'
SourceName
num <- (SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((SourceName
"0"SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++) (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SourceName -> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
".")) ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit)
ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit) ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
(++) (SourceName -> SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity (SourceName -> SourceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName)
-> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.') ParsecT PDFStream PSR Identity (SourceName -> SourceName)
-> ParsecT PDFStream PSR Identity SourceName
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT PDFStream PSR Identity Char
-> ParsecT PDFStream PSR Identity SourceName
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT PDFStream PSR Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit))
Double -> ParsecT PDFStream PSR Identity Double
forall (m :: * -> *) a. Monad m => a -> m a
return (Double -> ParsecT PDFStream PSR Identity Double)
-> Double -> ParsecT PDFStream PSR Identity Double
forall a b. (a -> b) -> a -> b
$ SourceName -> Double
forall a. Read a => SourceName -> a
read (SourceName -> Double) -> SourceName -> Double
forall a b. (a -> b) -> a -> b
$ SourceName
sign SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ SourceName
num
hexParam :: Parser T.Text
hexParam :: Parser Text
hexParam = do
Char -> ParsecT PDFStream () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'<'
SourceName
lets <- ParsecT PDFStream () Identity Char
-> ParsecT PDFStream () Identity Char
-> ParsecT PDFStream () Identity SourceName
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (SourceName -> ParsecT PDFStream () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"0123456789abcdefABCDEF") (ParsecT PDFStream () Identity Char
-> ParsecT PDFStream () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT PDFStream () Identity Char
-> ParsecT PDFStream () Identity Char)
-> ParsecT PDFStream () Identity Char
-> ParsecT PDFStream () Identity Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT PDFStream () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'>')
Text -> Parser Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parser Text) -> Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack SourceName
lets