module Text.PDF.Info
(
pdfInfo
,PDFInfo(..)
,PDFSize(..)
,PDFInfoError(..)
,ParsePDFInfo
,runParse
,parse
,parseSize
,parseDate
,readRight)
where
import Control.Applicative
import Control.Arrow
import Control.Exception as E
import Control.Monad.Error
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time
import Prelude
import System.Exit
import System.Locale
import System.Process.Text
data PDFInfo = PDFInfo {
pdfInfoTitle :: !(Maybe Text)
, pdfInfoSubject :: !(Maybe Text)
, pdfInfoAuthor :: !(Maybe Text)
, pdfInfoCreator :: !(Maybe Text)
, pdfInfoProducer :: !(Maybe Text)
, pdfInfoCreationDate :: !(Maybe UTCTime)
, pdfInfoModDate :: !(Maybe UTCTime)
, pdfInfoTagged :: !(Maybe Bool)
, pdfInfoPages :: !(Maybe Integer)
, pdfInfoEncrypted :: !(Maybe Bool)
, pdfInfoPageSize :: !(Maybe PDFSize)
, pdfInfoFileSize :: !(Maybe Integer)
, pdfInfoOptimized :: !(Maybe Bool)
, pdfInfoPDFVersion :: !(Maybe Double)
} deriving Show
data PDFInfoError
= ParseError !String
| ProcessFailure !Text
| ProcessError !IOException
| NoMessage
| SomeError String
deriving Show
data PDFSize = PDFSize { pdfSizeW :: !Float, pdfSizeH :: !Float }
deriving (Eq,Show)
instance Error PDFInfoError where noMsg = NoMessage; strMsg = SomeError
newtype ParsePDFInfo a = ParsePDFInfo { runParse :: Either PDFInfoError a }
deriving (Monad,Functor,MonadError PDFInfoError)
instance Applicative ParsePDFInfo where (<*>) = ap; pure = return
pdfInfo :: MonadIO m => FilePath -> m (Either PDFInfoError PDFInfo)
pdfInfo path = liftIO $ loadInfo `E.catch` ioErrorHandler where
loadInfo = do (code,out,err) <- readProcessWithExitCode "pdfinfo" ["-enc","UTF-8",path] ""
case code of
ExitSuccess -> return (parse out)
ExitFailure{} -> return (Left (ProcessFailure err))
ioErrorHandler = return . Left . ProcessError
parse :: Text -> Either PDFInfoError PDFInfo
parse out = runParse $
PDFInfo <$> string "Title"
<*> string "Subject"
<*> string "Author"
<*> string "Creator"
<*> string "Producer"
<*> date "CreationDate"
<*> date "ModDate"
<*> bool "Tagged"
<*> integer "Pages"
<*> bool "Encrypted"
<*> size "Page size"
<*> integer "File size"
<*> bool "Optimized"
<*> floating "PDF version"
where string = get id
date = get (>>= parseDate)
size = get (>>= parseSize)
bool = get $ fmap $ \yes -> yes == "yes"
floating = readIt
integer = readIt
readIt :: Read a => Text -> ParsePDFInfo (Maybe a)
readIt = get (>>= readRight)
properties = map split . T.lines $ out
get f name =
case lookup name properties of
Just ok -> catchError (Just <$> (f $ return $ T.strip ok))
(\_ -> return Nothing)
Nothing -> return Nothing
split = second (T.drop 2) . T.span (/=':')
parseSize :: Text -> ParsePDFInfo PDFSize
parseSize s =
case T.words s of
((readRight -> Right x):"x":(readRight -> Right y):_) ->
return $ PDFSize x y
_ -> throwError $ ParseError $ "Unable to read size: " ++ show s
parseDate :: Text -> ParsePDFInfo UTCTime
parseDate s =
case parseTime defaultTimeLocale "%a %b %e %H:%M:%S %Y" (T.unpack s) of
Just ok -> return ok
Nothing -> throwError $ ParseError $ "Unable to parse date: " ++ show s
readRight :: (MonadError PDFInfoError m,Read a) => Text -> m a
readRight s =
case reads (T.unpack s) of
[(v,_)] -> return v
_ -> throwError $ ParseError $ "Couldn't read value: " ++ show s