aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/App.hs25
-rw-r--r--src/Text/Pandoc/Class.hs54
-rw-r--r--src/Text/Pandoc/Lua/PandocModule.hs6
-rw-r--r--src/Text/Pandoc/Options.hs2
-rw-r--r--src/Text/Pandoc/PDF.hs7
-rw-r--r--src/Text/Pandoc/Readers/RST.hs2
-rw-r--r--src/Text/Pandoc/Readers/Txt2Tags.hs10
-rw-r--r--src/Text/Pandoc/SelfContained.hs110
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs2
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs2
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs2
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs2
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs2
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs2
-rw-r--r--test/Tests/Readers/Muse.hs6
-rw-r--r--test/Tests/Readers/Txt2Tags.hs6
-rw-r--r--test/pandoc.tix1
17 files changed, 118 insertions, 123 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 9b3055b35..503d7b0ac 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -78,7 +78,8 @@ import Text.Pandoc.Builder (setMeta)
import Text.Pandoc.Class (PandocIO, extractMedia, fillMediaBag, getLog,
setResourcePath, getMediaBag, setTrace, report,
setUserDataDir, readFileStrict, readDataFile,
- readDefaultDataFile, setTranslations)
+ readDefaultDataFile, setTranslations,
+ setInputFiles, setOutputFile)
import Text.Pandoc.Highlighting (highlightingStyles)
import Text.Pandoc.BCP47 (parseBCP47, Lang(..))
import Text.Pandoc.Lua (runLuaFilter, LuaException(..))
@@ -169,14 +170,13 @@ pdfWriterAndProg mWriter mEngine = do
convertWithOpts :: Opt -> IO ()
convertWithOpts opts = do
- let args = optInputFiles opts
let outputFile = fromMaybe "-" (optOutputFile opts)
let filters = optFilters opts
let verbosity = optVerbosity opts
when (optDumpArgs opts) $
do UTF8.hPutStrLn stdout outputFile
- mapM_ (UTF8.hPutStrLn stdout) args
+ mapM_ (UTF8.hPutStrLn stdout) (optInputFiles opts)
exitSuccess
epubMetadata <- case optEpubMetadata opts of
@@ -197,7 +197,7 @@ convertWithOpts opts = do
let filters' = if needsCiteproc then "pandoc-citeproc" : filters
else filters
- let sources = case args of
+ let sources = case optInputFiles opts of
[] -> ["-"]
xs | optIgnoreArgs opts -> ["-"]
| otherwise -> xs
@@ -261,15 +261,6 @@ convertWithOpts opts = do
_ -> e
let standalone = optStandalone opts || not (isTextFormat format) || pdfOutput
- let sourceURL = case sources of
- [] -> Nothing
- (x:_) -> case parseURI x of
- Just u
- | uriScheme u `elem` ["http:","https:"] ->
- Just $ show u{ uriQuery = "",
- uriFragment = "" }
- _ -> Nothing
-
let addStringAsVariable varname s vars = return $ (varname, s) : vars
highlightStyle <- lookupHighlightStyle $ optHighlightStyle opts
@@ -347,6 +338,8 @@ convertWithOpts opts = do
runIO' $ do
setUserDataDir datadir
+ setInputFiles (optInputFiles opts)
+ setOutputFile (optOutputFile opts)
variables <-
withList (addStringAsVariable "sourcefile")
@@ -449,7 +442,6 @@ convertWithOpts opts = do
, writerColumns = optColumns opts
, writerEmailObfuscation = optEmailObfuscation opts
, writerIdentifierPrefix = optIdentifierPrefix opts
- , writerSourceURL = sourceURL
, writerHtmlQTags = optHtmlQTags opts
, writerTopLevelDivision = optTopLevelDivision opts
, writerListings = optListings opts
@@ -509,7 +501,7 @@ convertWithOpts opts = do
setResourcePath (optResourcePath opts)
doc <- sourceToDoc sources >>=
( (if isJust (optExtractMedia opts)
- then fillMediaBag (writerSourceURL writerOptions)
+ then fillMediaBag
else return)
>=> return . flip (foldr addMetadata) metadata
>=> applyLuaFilters datadir (optLuaFilters opts) format
@@ -545,8 +537,7 @@ convertWithOpts opts = do
if optSelfContained opts && htmlFormat
-- TODO not maximally efficient; change type
-- of makeSelfContained so it works w/ Text
- then T.pack <$> makeSelfContained writerOptions
- (T.unpack output)
+ then T.pack <$> makeSelfContained (T.unpack output)
else return output
type Transform = Pandoc -> Pandoc
diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs
index f60062d6c..cc24c1c30 100644
--- a/src/Text/Pandoc/Class.hs
+++ b/src/Text/Pandoc/Class.hs
@@ -66,7 +66,9 @@ module Text.Pandoc.Class ( PandocMonad(..)
, getUserDataDir
, fetchItem
, getInputFiles
+ , setInputFiles
, getOutputFile
+ , setOutputFile
, setResourcePath
, getResourcePath
, PandocIO(..)
@@ -251,12 +253,29 @@ insertMedia fp mime bs = do
let mb' = MB.insertMedia fp mime bs mb
setMediaBag mb'
-getInputFiles :: PandocMonad m => m (Maybe [FilePath])
+getInputFiles :: PandocMonad m => m [FilePath]
getInputFiles = getsCommonState stInputFiles
+setInputFiles :: PandocMonad m => [FilePath] -> m ()
+setInputFiles fs = do
+ let sourceURL = case fs of
+ [] -> Nothing
+ (x:_) -> case parseURI x of
+ Just u
+ | uriScheme u `elem` ["http:","https:"] ->
+ Just $ show u{ uriQuery = "",
+ uriFragment = "" }
+ _ -> Nothing
+
+ modifyCommonState $ \st -> st{ stInputFiles = fs
+ , stSourceURL = sourceURL }
+
getOutputFile :: PandocMonad m => m (Maybe FilePath)
getOutputFile = getsCommonState stOutputFile
+setOutputFile :: PandocMonad m => Maybe FilePath -> m ()
+setOutputFile mbf = modifyCommonState $ \st -> st{ stOutputFile = mbf }
+
setResourcePath :: PandocMonad m => [FilePath] -> m ()
setResourcePath ps = modifyCommonState $ \st -> st{stResourcePath = ps}
@@ -289,12 +308,14 @@ data CommonState = CommonState { stLog :: [LogMessage]
-- ^ A list of log messages in reverse order
, stUserDataDir :: Maybe FilePath
-- ^ Directory to search for data files
+ , stSourceURL :: Maybe String
+ -- ^ Absolute URL + dir of 1st source file
, stMediaBag :: MediaBag
-- ^ Media parsed from binary containers
, stTranslations :: Maybe
(Lang, Maybe Translations)
-- ^ Translations for localization
- , stInputFiles :: Maybe [FilePath]
+ , stInputFiles :: [FilePath]
-- ^ List of input files from command line
, stOutputFile :: Maybe FilePath
-- ^ Output file from command line
@@ -311,9 +332,10 @@ data CommonState = CommonState { stLog :: [LogMessage]
instance Default CommonState where
def = CommonState { stLog = []
, stUserDataDir = Nothing
+ , stSourceURL = Nothing
, stMediaBag = mempty
, stTranslations = Nothing
- , stInputFiles = Nothing
+ , stInputFiles = []
, stOutputFile = Nothing
, stResourcePath = ["."]
, stVerbosity = WARNING
@@ -473,20 +495,19 @@ getUserDataDir = getsCommonState stUserDataDir
-- | Fetch an image or other item from the local filesystem or the net.
-- Returns raw content and maybe mime type.
fetchItem :: PandocMonad m
- => Maybe String
- -> String
+ => String
-> m (B.ByteString, Maybe MimeType)
-fetchItem sourceURL s = do
+fetchItem s = do
mediabag <- getMediaBag
case lookupMedia s mediabag of
Just (mime, bs) -> return (BL.toStrict bs, Just mime)
- Nothing -> downloadOrRead sourceURL s
+ Nothing -> downloadOrRead s
downloadOrRead :: PandocMonad m
- => Maybe String
- -> String
+ => String
-> m (B.ByteString, Maybe MimeType)
-downloadOrRead sourceURL s =
+downloadOrRead s = do
+ sourceURL <- getsCommonState stSourceURL
case (sourceURL >>= parseURIReference' .
ensureEscaped, ensureEscaped s) of
(Just u, s') -> -- try fetching from relative path at source
@@ -637,10 +658,9 @@ withPaths (p:ps) action fp =
-- | Fetch local or remote resource (like an image) and provide data suitable
-- for adding it to the MediaBag.
fetchMediaResource :: PandocMonad m
- => Maybe String -> String
- -> m (FilePath, Maybe MimeType, BL.ByteString)
-fetchMediaResource sourceUrl src = do
- (bs, mt) <- downloadOrRead sourceUrl src
+ => String -> m (FilePath, Maybe MimeType, BL.ByteString)
+fetchMediaResource src = do
+ (bs, mt) <- downloadOrRead src
let ext = fromMaybe (takeExtension src)
(mt >>= extensionFromMimeType)
let bs' = BL.fromChunks [bs]
@@ -650,15 +670,15 @@ fetchMediaResource sourceUrl src = do
-- | Traverse tree, filling media bag for any images that
-- aren't already in the media bag.
-fillMediaBag :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc
-fillMediaBag sourceURL d = walkM handleImage d
+fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc
+fillMediaBag d = walkM handleImage d
where handleImage :: PandocMonad m => Inline -> m Inline
handleImage (Image attr lab (src, tit)) = catchError
(do mediabag <- getMediaBag
case lookupMedia src mediabag of
Just (_, _) -> return $ Image attr lab (src, tit)
Nothing -> do
- (fname, mt, bs) <- fetchMediaResource sourceURL src
+ (fname, mt, bs) <- fetchMediaResource src
insertMedia fname mt bs
return $ Image attr lab (fname, tit))
(\e ->
diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs
index ffd681d30..326de1886 100644
--- a/src/Text/Pandoc/Lua/PandocModule.hs
+++ b/src/Text/Pandoc/Lua/PandocModule.hs
@@ -136,11 +136,9 @@ mediaDirectoryFn mbRef = do
insertResource :: IORef MB.MediaBag
-> String
- -> OrNil String
-> Lua NumResults
-insertResource mbRef src sourceUrlOrNil = do
- (fp, mimeType, bs) <- liftIO . runIOorExplode $
- fetchMediaResource (toMaybe sourceUrlOrNil) src
+insertResource mbRef src = do
+ (fp, mimeType, bs) <- liftIO . runIOorExplode $ fetchMediaResource src
liftIO $ print (fp, mimeType)
insertMediaFn mbRef fp (OrNil mimeType) bs
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 345245855..f936658f4 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -207,7 +207,6 @@ data WriterOptions = WriterOptions
, writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails
, writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML
-- and for footnote marks in markdown
- , writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file
, writerCiteMethod :: CiteMethod -- ^ How to print cites
, writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
, writerSlideLevel :: Maybe Int -- ^ Force header level of slides
@@ -244,7 +243,6 @@ instance Default WriterOptions where
, writerColumns = 72
, writerEmailObfuscation = NoObfuscation
, writerIdentifierPrefix = ""
- , writerSourceURL = Nothing
, writerCiteMethod = Citeproc
, writerHtmlQTags = False
, writerSlideLevel = Nothing
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index b2b7da54f..26f831c6d 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -129,7 +129,7 @@ makePDF program writer opts verbosity mediabag doc = do
else withTempDir
resourcePath <- getResourcePath
liftIO $ withTemp "tex2pdf." $ \tmpdir -> do
- doc' <- handleImages verbosity opts resourcePath mediabag tmpdir doc
+ doc' <- handleImages verbosity resourcePath mediabag tmpdir doc
source <- runIOorExplode $ do
setVerbosity verbosity
writer opts doc'
@@ -141,18 +141,17 @@ makePDF program writer opts verbosity mediabag doc = do
_ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program
handleImages :: Verbosity
- -> WriterOptions
-> [FilePath]
-> MediaBag
-> FilePath -- ^ temp dir to store images
-> Pandoc -- ^ document
-> IO Pandoc
-handleImages verbosity opts resourcePath mediabag tmpdir doc = do
+handleImages verbosity resourcePath mediabag tmpdir doc = do
doc' <- runIOorExplode $ do
setVerbosity verbosity
setResourcePath resourcePath
setMediaBag mediabag
- fillMediaBag (writerSourceURL opts) doc >>=
+ fillMediaBag doc >>=
extractMedia tmpdir
walkM (convertImages verbosity tmpdir) doc'
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index daaeff2f0..2d6bb979f 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -850,7 +850,7 @@ csvTableDirective top fields rawcsv = do
rawcsv' <- case trim <$>
lookup "file" fields `mplus` lookup "url" fields of
Just u -> do
- (bs, _) <- fetchItem Nothing u
+ (bs, _) <- fetchItem u
return $ UTF8.toString bs
Nothing -> return rawcsv
let res = parseCSV opts (T.pack $ case explicitHeader of
diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs
index f000646c2..2d3e541cf 100644
--- a/src/Text/Pandoc/Readers/Txt2Tags.hs
+++ b/src/Text/Pandoc/Readers/Txt2Tags.hs
@@ -70,14 +70,8 @@ instance Default T2TMeta where
-- | Get the meta information required by Txt2Tags macros
getT2TMeta :: PandocMonad m => m T2TMeta
getT2TMeta = do
- mbInps <- P.getInputFiles
- let inps = case mbInps of
- Just x -> x
- Nothing -> []
- mbOutp <- P.getOutputFile
- let outp = case mbOutp of
- Just x -> x
- Nothing -> ""
+ inps <- P.getInputFiles
+ outp <- fromMaybe "" <$> P.getOutputFile
curDate <- formatTime defaultTimeLocale "%F" <$> P.getZonedTime
let getModTime = fmap (formatTime defaultTimeLocale "%T") .
P.getModificationTime
diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs
index 55df147b6..787ea1954 100644
--- a/src/Text/Pandoc/SelfContained.hs
+++ b/src/Text/Pandoc/SelfContained.hs
@@ -42,10 +42,11 @@ import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as L
import Data.Char (isAlphaNum, isAscii, toLower)
import Data.List (isPrefixOf)
-import Network.URI (URI (..), escapeURIString, parseURI)
+import Network.URI (escapeURIString)
import System.FilePath (takeDirectory, takeExtension, (</>))
import Text.HTML.TagSoup
-import Text.Pandoc.Class (PandocMonad (..), fetchItem, report)
+import Text.Pandoc.Class (PandocMonad (..), fetchItem, report,
+ getInputFiles, setInputFiles)
import Text.Pandoc.Error
import Text.Pandoc.Logging
import Text.Pandoc.MIME (MimeType)
@@ -68,29 +69,29 @@ makeDataURI (mime, raw) =
then mime ++ ";charset=utf-8"
else mime -- mime type already has charset
-convertTags :: PandocMonad m => Maybe String -> [Tag String] -> m [Tag String]
-convertTags _ [] = return []
-convertTags sourceURL (t@TagOpen{}:ts)
- | fromAttrib "data-external" t == "1" = (t:) <$> convertTags sourceURL ts
-convertTags sourceURL (t@(TagOpen tagname as):ts)
+convertTags :: PandocMonad m => [Tag String] -> m [Tag String]
+convertTags [] = return []
+convertTags (t@TagOpen{}:ts)
+ | fromAttrib "data-external" t == "1" = (t:) <$> convertTags ts
+convertTags (t@(TagOpen tagname as):ts)
| tagname `elem`
["img", "embed", "video", "input", "audio", "source", "track"] = do
as' <- mapM processAttribute as
- rest <- convertTags sourceURL ts
+ rest <- convertTags ts
return $ TagOpen tagname as' : rest
where processAttribute (x,y) =
if x == "src" || x == "data-src" || x == "href" || x == "poster"
then do
- enc <- getDataURI sourceURL (fromAttrib "type" t) y
+ enc <- getDataURI (fromAttrib "type" t) y
return (x, enc)
else return (x,y)
-convertTags sourceURL (t@(TagOpen "script" as):TagClose "script":ts) =
+convertTags (t@(TagOpen "script" as):TagClose "script":ts) =
case fromAttrib "src" t of
- [] -> (t:) <$> convertTags sourceURL ts
+ [] -> (t:) <$> convertTags ts
src -> do
let typeAttr = fromAttrib "type" t
- res <- getData sourceURL typeAttr src
- rest <- convertTags sourceURL ts
+ res <- getData typeAttr src
+ rest <- convertTags ts
case res of
Left dataUri -> return $ TagOpen "script"
(("src",dataUri) : [(x,y) | (x,y) <- as, x /= "src"]) :
@@ -110,21 +111,21 @@ convertTags sourceURL (t@(TagOpen "script" as):TagClose "script":ts) =
(("src",makeDataURI (mime, bs)) :
[(x,y) | (x,y) <- as, x /= "src"]) :
TagClose "script" : rest
-convertTags sourceURL (t@(TagOpen "link" as):ts) =
+convertTags (t@(TagOpen "link" as):ts) =
case fromAttrib "href" t of
- [] -> (t:) <$> convertTags sourceURL ts
+ [] -> (t:) <$> convertTags ts
src -> do
- res <- getData sourceURL (fromAttrib "type" t) src
+ res <- getData (fromAttrib "type" t) src
case res of
Left dataUri -> do
- rest <- convertTags sourceURL ts
+ rest <- convertTags ts
return $ TagOpen "link"
(("href",dataUri) : [(x,y) | (x,y) <- as, x /= "href"]) :
rest
Right (mime, bs)
| "text/css" `isPrefixOf` mime
&& not ("</" `B.isInfixOf` bs) -> do
- rest <- convertTags sourceURL $
+ rest <- convertTags $
dropWhile (==TagClose "link") ts
return $
TagOpen "style" [("type", mime)]
@@ -132,16 +133,16 @@ convertTags sourceURL (t@(TagOpen "link" as):ts) =
: TagClose "style"
: rest
| otherwise -> do
- rest <- convertTags sourceURL ts
+ rest <- convertTags ts
return $ TagOpen "link"
(("href",makeDataURI (mime, bs)) :
[(x,y) | (x,y) <- as, x /= "href"]) : rest
-convertTags sourceURL (t:ts) = (t:) <$> convertTags sourceURL ts
+convertTags (t:ts) = (t:) <$> convertTags ts
cssURLs :: PandocMonad m
- => Maybe String -> FilePath -> ByteString -> m ByteString
-cssURLs sourceURL d orig = do
- res <- runParserT (parseCSSUrls sourceURL d) () "css" orig
+ => FilePath -> ByteString -> m ByteString
+cssURLs d orig = do
+ res <- runParserT (parseCSSUrls d) () "css" orig
case res of
Left e -> do
report $ CouldNotParseCSS (show e)
@@ -149,17 +150,16 @@ cssURLs sourceURL d orig = do
Right bs -> return bs
parseCSSUrls :: PandocMonad m
- => Maybe String -> FilePath -> ParsecT ByteString () m ByteString
-parseCSSUrls sourceURL d = B.concat <$> P.many
- (pCSSWhite <|> pCSSComment <|> pCSSImport sourceURL d <|>
- pCSSUrl sourceURL d <|> pCSSOther)
+ => FilePath -> ParsecT ByteString () m ByteString
+parseCSSUrls d = B.concat <$> P.many
+ (pCSSWhite <|> pCSSComment <|> pCSSImport d <|> pCSSUrl d <|> pCSSOther)
-pCSSImport :: PandocMonad m => Maybe String -> FilePath
- -> ParsecT ByteString () m ByteString
-pCSSImport sourceURL d = P.try $ do
+pCSSImport :: PandocMonad m
+ => FilePath -> ParsecT ByteString () m ByteString
+pCSSImport d = P.try $ do
P.string "@import"
P.spaces
- res <- (pQuoted <|> pUrl) >>= handleCSSUrl sourceURL d
+ res <- (pQuoted <|> pUrl) >>= handleCSSUrl d
P.spaces
P.char ';'
P.spaces
@@ -184,9 +184,9 @@ pCSSOther = do
(B.singleton <$> P.char '/')
pCSSUrl :: PandocMonad m
- => Maybe String -> FilePath -> ParsecT ByteString () m ByteString
-pCSSUrl sourceURL d = P.try $ do
- res <- pUrl >>= handleCSSUrl sourceURL d
+ => FilePath -> ParsecT ByteString () m ByteString
+pCSSUrl d = P.try $ do
+ res <- pUrl >>= handleCSSUrl d
case res of
Left b -> return b
Right (mt,b) -> do
@@ -215,41 +215,41 @@ pUrl = P.try $ do
return (url, fallback)
handleCSSUrl :: PandocMonad m
- => Maybe String -> FilePath -> (String, ByteString)
+ => FilePath -> (String, ByteString)
-> ParsecT ByteString () m
(Either ByteString (MimeType, ByteString))
-handleCSSUrl sourceURL d (url, fallback) = do
+handleCSSUrl d (url, fallback) = do
-- pipes are used in URLs provided by Google Code fonts
-- but parseURI doesn't like them, so we escape them:
case escapeURIString (/='|') (trim url) of
'#':_ -> return $ Left fallback
'd':'a':'t':'a':':':_ -> return $ Left fallback
u -> do let url' = if isURI u then u else d </> u
- res <- lift $ getData sourceURL "" url'
+ res <- lift $ getData "" url'
case res of
Left uri -> return $ Left (B.pack $ "url(" ++ uri ++ ")")
Right (mt, raw) -> do
-- note that the downloaded CSS may
-- itself contain url(...).
b <- if "text/css" `isPrefixOf` mt
- then cssURLs sourceURL d raw
+ then cssURLs d raw
else return raw
return $ Right (mt, b)
-getDataURI :: PandocMonad m => Maybe String -> MimeType -> String -> m String
-getDataURI sourceURL mimetype src = do
- res <- getData sourceURL mimetype src
+getDataURI :: PandocMonad m => MimeType -> String -> m String
+getDataURI mimetype src = do
+ res <- getData mimetype src
case res of
Left uri -> return uri
Right x -> return $ makeDataURI x
getData :: PandocMonad m
- => Maybe String -> MimeType -> String
+ => MimeType -> String
-> m (Either String (MimeType, ByteString))
-getData _ _ src@('d':'a':'t':'a':':':_) = return $ Left src-- already data: uri
-getData sourceURL mimetype src = do
+getData _ src@('d':'a':'t':'a':':':_) = return $ Left src-- already data: uri
+getData mimetype src = do
let ext = map toLower $ takeExtension src
- (raw, respMime) <- fetchItem sourceURL src
+ (raw, respMime) <- fetchItem src
let raw' = if ext == ".gz"
then B.concat $ L.toChunks $ Gzip.decompress $ L.fromChunks
$ [raw]
@@ -259,15 +259,13 @@ getData sourceURL mimetype src = do
$ "Could not determine mime type for `" ++ src ++ "'"
(x, Nothing) -> return x
(_, Just x ) -> return x
- let cssSourceURL = case parseURI src of
- Just u
- | uriScheme u `elem` ["http:","https:"] ->
- Just $ show u{ uriPath = "",
- uriQuery = "",
- uriFragment = "" }
- _ -> Nothing
result <- if "text/css" `isPrefixOf` mime
- then cssURLs cssSourceURL (takeDirectory src) raw'
+ then do
+ oldInputs <- getInputFiles
+ setInputFiles [src]
+ res <- cssURLs (takeDirectory src) raw'
+ setInputFiles oldInputs
+ return res
else return raw'
return $ Right (mime, result)
@@ -275,8 +273,8 @@ getData sourceURL mimetype src = do
-- | Convert HTML into self-contained HTML, incorporating images,
-- scripts, and CSS using data: URIs.
-makeSelfContained :: PandocMonad m => WriterOptions -> String -> m String
-makeSelfContained opts inp = do
+makeSelfContained :: PandocMonad m => String -> m String
+makeSelfContained inp = do
let tags = parseTags inp
- out' <- convertTags (writerSourceURL opts) tags
+ out' <- convertTags tags
return $ renderTags' out'
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 3d6eb9fe5..6102d97ed 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -1295,7 +1295,7 @@ inlineToOpenXML' opts (Image attr alt (src, title)) = do
Just (_,_,_,elt,_) -> return [elt]
Nothing -> do
catchError
- (do (img, mt) <- P.fetchItem (writerSourceURL opts) src
+ (do (img, mt) <- P.fetchItem src
ident <- ("rId"++) `fmap` ((lift . lift) getUniqueId)
let (xpt,ypt) = desiredSizeInPoints opts attr
(either (const def) id (imageSize opts img))
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 04126fbb7..6bae65b6b 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -918,7 +918,7 @@ modifyMediaRef opts oldsrc = do
case lookup oldsrc media of
Just (n,_) -> return n
Nothing -> catchError
- (do (img, mbMime) <- P.fetchItem (writerSourceURL opts) oldsrc
+ (do (img, mbMime) <- P.fetchItem oldsrc
let new = "media/file" ++ show (length media) ++
fromMaybe (takeExtension (takeWhile (/='?') oldsrc))
(('.':) <$> (mbMime >>= extensionFromMimeType))
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 4c764d987..36c572b63 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -255,7 +255,7 @@ fetchImage href link = do
else return Nothing
(True, Just _) -> return Nothing -- not base64-encoded
_ -> do
- catchError (do (bs, mbmime) <- P.fetchItem Nothing link
+ catchError (do (bs, mbmime) <- P.fetchItem link
case mbmime of
Nothing -> do
report $ CouldNotDetermineMimeType link
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 37df58e65..650a1c012 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -543,7 +543,7 @@ styleToStrAttr style =
imageICML :: PandocMonad m => WriterOptions -> Style -> Attr -> Target -> WS m Doc
imageICML opts style attr (src, _) = do
imgS <- catchError
- (do (img, _) <- P.fetchItem (writerSourceURL opts) src
+ (do (img, _) <- P.fetchItem src
case imageSize opts img of
Right size -> return size
Left msg -> do
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 4c74ef469..90b7c3501 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -180,7 +180,7 @@ addLang lang = everywhere' (mkT updateLangAttr)
-- | transform both Image and Math elements
transformPicMath :: PandocMonad m => WriterOptions ->Inline -> O m Inline
transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = catchError
- (do (img, mbMimeType) <- P.fetchItem (writerSourceURL opts) src
+ (do (img, mbMimeType) <- P.fetchItem src
(ptX, ptY) <- case imageSize opts img of
Right s -> return $ sizeInPoints s
Left msg -> do
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 48d31c7bf..d4de3112c 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -56,7 +56,7 @@ import Text.Printf (printf)
-- If file not found or filetype not jpeg or png, leave the inline unchanged.
rtfEmbedImage :: PandocMonad m => WriterOptions -> Inline -> m Inline
rtfEmbedImage opts x@(Image attr _ (src,_)) = catchError
- (do result <- P.fetchItem (writerSourceURL opts) src
+ (do result <- P.fetchItem src
case result of
(imgdata, Just mime)
| mime == "image/jpeg" || mime == "image/png" -> do
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index f89c58d3f..158f5788e 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -13,10 +13,8 @@ import Text.Pandoc.Class
muse :: Text -> Pandoc
muse = purely $ \s -> do
- putCommonState
- def { stInputFiles = Just ["in"]
- , stOutputFile = Just "out"
- }
+ setInputFiles ["in"]
+ setOutputFile (Just "out")
readMuse def s
infix 4 =:
diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs
index 580815279..041918e70 100644
--- a/test/Tests/Readers/Txt2Tags.hs
+++ b/test/Tests/Readers/Txt2Tags.hs
@@ -14,10 +14,8 @@ import Text.Pandoc.Class
t2t :: Text -> Pandoc
-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
t2t = purely $ \s -> do
- putCommonState
- def { stInputFiles = Just ["in"]
- , stOutputFile = Just "out"
- }
+ setInputFiles ["in"]
+ setOutputFile (Just "out")
readTxt2Tags def s
infix 4 =:
diff --git a/test/pandoc.tix b/test/pandoc.tix
new file mode 100644
index 000000000..c678d9e18
--- /dev/null
+++ b/test/pandoc.tix
@@ -0,0 +1 @@
+Tix [ TixModule "pandoc-2.0-3BMtEkU5Hqi529URohVtzN/Text.Pandoc.Class" 286124609 1293 [0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,16,0,0,16,98,98,98,98,16,0,0,16,16,98,114,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,36,36,36,0,36,36,36,36,729,729,729,729,729,729,729,236,0,0,0,236,493,493,729,729,729,2877,1411,2877,2877,2877,2877,2877,2877,2877,2339,2339,2339,2339,2339,220,220,35,35,35,255,255,255,255,255,220,0,220,220,255,475,22,22,22,0,0,0,22,22,22,0,0,0,0,98,98,98,0,831,831,98,98,98,98,98,98,1488,1488,1488,1488,1488,1488,1488,98,98,98,98,98,98,98,98,48,48,0,0,0,0,0,0,0,0,0,0,48,48,48,48,0,0,0,0,0,0,0,98,98,98,98,0,98,98,98,98,0,0,98,82,48,82,82,98,98,98,0,0,0,98,98,98,98,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,98,98,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,98,98,98,98,98,2339,1411,53,1411,1411,2339,2339,0,11,11,11,11,11,0,6,0,0,0,0,0,0,6,0,0,0,0,6,6,6,98,2437,2437,2339,2339,2339,2339,2339,2339,98,98,98,98,0,0,0,0,0,0,98,98,98,98,98,98,0,0,0,0,0,0,0,2339,1411,1028,1411,1411,2339,2339,4280,4280,4280,4280,4280,4280,4280,4280,4280,36,36,4280,4280,3903,0,0,0,0,3903,3903,4280,4280,4280,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,2339,2339,2339,2339,1411,406,1411,1411,2339,2339,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,2877,2877,11,11,0,0,98,98,0,0,98,98,40931,40931,4720,4720,45426,50121,50121,50121,11303,11303,8136,11303,11303,11303,0,0,0,0,0,0,0,0,0,0,0,0,0,2339,2339,11,2339,2339,0,0,2339,2339,2339,0,31,92,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,34,34,34,34,0,0,0,0,0,0,0,0,0,0,0,0,0,2496,2496,2496,1536,1536,1536,1536,18,18,18,18,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,3,3,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,9004,9004,9004,978,978,978,978,3,3,3,3,36,36,36,36,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,255,255,255,255,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,11501,11501,11501,305,305,305,305,15,15,15,15,40931,40931,40931,40931,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,40931,40931,40931,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,36,36,36,36,11,11,11,11,11,11,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,255,255,255,255,98,98,98,98,376,376,376,376,376,0,0,0,0,0,0,0,0,2339,2339,2339,2339,2339,11303,11303,8136,11303,11303,11303,11303,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,36,0,53,11,0,0,0,0,0,1411,1411], TixModule "pandoc-2.0-3BMtEkU5Hqi529URohVtzN/Text.Pandoc.Writers.HTML" 519911631 3376 [68,470,470,470,470,470,470,68,56,56,56,56,68,68,68,68,68,68,470,470,470,470,0,0,0,35,35,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,2496,415,334,253,1494,2496,2496,33,33,33,33,33,33,33,33,33,33,33,33,33,33,6,6,6,6,6,6,6,6,0,0,0,0,0,0,0,0,0,0,0,33,33,52,52,52,52,0,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,104,104,104,12,12,12,12,12,12,4,4,4,4,4,4,4,4,4,4,88,104,104,52,52,52,52,52,52,16,16,16,16,16,10,2273,2273,2273,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,22,809,809,809,809,22,787,22,22,22,22,0,22,22,22,22,22,22,22,0,0,0,0,0,0,0,0,0,22,787,787,787,787,809,809,809,809,824,0,824,824,824,824,824,824,824,824,824,824,2218,2218,2218,674,1544,674,674,674,2218,2218,2218,2218,222,1996,222,222,222,222,222,2218,2218,2218,2218,2218,2218,838,2166,674,2166,2166,2166,2166,30,30,30,30,30,0,30,0,30,30,30,30,30,30,30,30,30,30,30,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,30,6,10,0,16,52,10,52,52,52,0,52,52,52,52,52,52,52,52,52,52,590,590,590,590,10863,10863,10863,10863,0,10863,0,10863,10863,10863,10863,121,121,121,121,121,121,121,121,121,15,890,6,890,15,9,6,9,6,15,15,15,9,6,9,9,9,9,9,9,6,6,6,0,6,0,0,0,0,0,0,6,6,6,6,6,6,6,15,15,890,890,890,875,15,875,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,890,890,890,890,1585,1585,1585,1585,1585,1585,688,688,688,688,688,688,688,688,688,403,403,403,403,403,403,403,285,285,285,285,285,285,285,82,82,82,82,82,43531,43531,43531,43531,43449,43449,82,82,82,82,82,43531,0,43613,313,2499,2499,1002,2499,2499,2499,2499,1002,690,312,690,690,690,690,690,690,690,690,312,312,312,1002,1002,2499,2499,1497,1002,1497,1002,1002,1002,2499,2499,2499,2499,2499,2499,2499,2499,2499,2499,2499,2499,797,797,797,124,673,124,673,797,797,801,124,677,677,677,677,677,415,262,415,262,801,801,801,2499,2499,2499,2499,2499,797,801,797,801,801,801,801,801,801,801,801,801,801,801,801,801,801,801,801,801,801,801,0,27,27,27,27,27,27,27,27,27,27,21,6,21,6,6,6,6,27,27,27,27,0,27,0,0,27,0,27,27,27,27,27,27,21,6,21,21,21,21,21,21,21,21,21,21,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,27,27,27,27,0,0,445,3778,3778,6,37,37,0,37,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,27,27,27,27,27,27,27,0,0,0,0,0,0,0,0,0,3509,3509,3509,3509,0,3509,0,0,3509,3509,0,635,3509,3509,3509,3509,3509,3509,3509,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,165,165,0,165,165,165,83,0,83,0,0,0,83,83,83,83,165,165,165,165,165,165,165,165,165,165,165,0,111,111,165,0,165,0,0,0,0,0,0,165,165,165,165,0,165,165,165,0,165,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,30,165,165,165,165,165,165,165,165,165,165,165,165,452,452,452,402,50,402,402,402,402,50,50,50,50,15,15,15,15,50,35,35,35,0,0,35,50,0,50,0,0,0,0,0,0,0,0,50,0,0,0,50,50,50,50,50,50,452,452,195,195,195,195,117,78,117,78,195,195,195,216,216,216,30,30,30,30,30,10,20,20,20,20,20,20,20,10,10,10,20,216,216,216,10,206,30,30,30,30,30,10,20,10,20,30,10,10,10,206,216,216,216,10,206,10,10,10,10,10,10,10,10,10,206,216,216,216,216,216,216,0,20,20,20,0,216,0,216,20,216,0,0,216,216,216,196,196,196,0,0,0,0,196,196,0,196,196,196,196,196,196,196,196,196,196,196,196,196,196,20,20,20,20,20,0,20,20,20,20,20,20,20,20,216,216,125,125,125,125,125,0,125,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,45,125,125,125,125,125,125,125,125,125,125,125,125,125,125,125,125,0,737,737,0,737,737,737,737,0,0,0,0,0,0,0,737,0,737,0,0,0,0,0,0,0,0,0,0,0,0,0,0,737,737,737,737,737,737,737,737,0,737,0,0,0,737,737,426,426,237,237,44,44,15,15,15,15,0,0,0,0,737,737,737,737,153,403,403,403,403,403,403,403,150,285,285,285,255,285,102,0,102,102,102,102,102,102,285,285,285,60,225,60,60,60,60,60,225,285,285,285,285,0,285,0,0,0,285,285,285,285,285,255,30,255,153,102,153,153,108,9,18,9,9,0,153,153,153,102,102,102,102,102,102,102,102,255,30,285,285,285,285,285,285,285,285,255,285,285,285,285,285,271,271,0,271,0,0,271,271,16,271,271,271,271,346,346,346,346,346,346,271,271,61,271,271,271,271,271,271,271,271,271,271,271,75,75,271,271,271,271,271,271,271,271,121,121,121,121,121,121,121,252,252,153,99,153,153,11,99,99,99,99,99,99,99,99,99,99,252,66,252,231,231,231,231,231,231,231,231,248,248,252,252,186,66,186,66,66,66,231,183,48,183,183,183,183,183,183,183,183,183,48,48,48,48,48,48,48,231,231,231,231,66,66,66,66,66,66,66,66,252,252,204,252,252,128,124,128,128,124,124,124,124,124,124,124,124,124,124,124,124,124,124,124,124,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,252,66,66,66,252,206,46,206,46,46,46,46,46,46,46,46,46,46,46,46,46,46,252,252,252,10265,4795,297,297,4795,4795,4795,1035,4718,4795,4795,4789,4789,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,0,75,0,75,75,75,75,75,75,75,75,75,75,75,75,75,75,0,0,0,0,0,0,0,0,0,0,0,0,0,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,0,0,0,0,0,75,75,75,75,75,75,75,75,75,75,75,1151,10562,10562,10562,10562,10562,10562,10562,10562,98,45941,45941,26523,26523,26523,26523,16206,16206,16206,16206,832,832,832,0,0,772,772,60,60,832,832,31,31,25,6,25,6,31,31,31,31,31,16,40,40,0,40,0,40,16,40,40,0,40,0,40,16,40,40,0,40,0,40,40,40,40,40,40,40,0,40,0,0,0,0,0,0,40,40,16,16,16,16,16,40,40,40,40,40,181,41,41,0,41,41,41,17,41,41,41,41,41,41,0,489,489,489,489,489,489,0,167,167,167,167,167,167,205,205,205,205,0,5,5,5,205,5,205,0,0,205,205,5,205,200,200,200,0,0,0,0,200,200,0,200,200,200,200,200,200,200,200,200,5,5,0,5,5,5,5,0,5,5,5,5,5,5,5,5,205,0,15,15,15,15,15,15,0,8,8,8,8,8,8,8,8,8,0,60,60,60,60,60,60,0,45,45,45,45,45,45,240,150,150,150,150,150,90,90,90,90,90,240,240,240,0,240,0,0,0,0,0,0,0,0,0,0,0,0,240,240,240,240,240,240,45,240,240,240,240,135,39,135,135,135,124,124,124,124,124,109,15,109,15,124,124,124,124,135,135,11,11,11,11,11,11,11,11,11,11,11,11,0,0,0,0,0,0,11,11,11,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,34,124,124,124,0,124,124,124,124,124,124,124,124,124,15,9,6,9,6,15,15,124,124,109,15,15,15,15,15,124,124,124,135,135,15,15,15,0,15,0,0,0,0,15,0,15,15,15,15,15,15,15,804,804,804,30,774,0,30,30,30,30,30,30,30,30,30,30,0,774,774,144,774,774,144,144,144,0,144,0,144,144,144,144,144,144,144,144,144,630,774,774,774,774,774,774,774,774,774,774,774,774,774,774,774,774,53,721,53,53,53,53,53,53,721,721,721,721,774,774,0,774,774,774,774,774,774,774,639,135,639,135,135,135,135,135,774,774,774,52,52,52,0,52,52,52,52,52,52,52,52,52,52,0,52,0,0,0,0,0,52,52,52,52,52,52,52,52,15,37,15,15,15,15,52,52,52,52,52,0,52,52,52,52,52,0,52,52,52,52,52,52,52,40,12,40,12,52,52,52,52,52,52,52,52,52,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,0,75,0,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,0,75,0,75,75,75,75,75,75,75,75,75,0,0,0,0,0,75,75,75,75,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,46035,46035,46035,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1541,4380,4380,736,736,736,736,736,36,36,36,736,736,0,0,0,0,0,0,0,0,0,736,736,0,736,736,736,36,736,736,36,36,36,736,736,736,736,736,736,736,0,736,0,0,736,736,736,736,736,736,736,0,0,0,736,736,736,736,736,0,736,736,736,736,736,736,736,0,0,0,3305,1619,1940,0,0,0,0,0,0,1940,3305,3305,296,3601,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,571,621,736,736,0,736,0,0,0,621,736,736,115,621,0,621,621,621,736,736,736,36,36,36,36,36,36,36,36,36,36,36,36,36,36,736,0,736,0,736,736,36,700,36,736,736,700,700,736,36,36,736,36,700,36,736,736,700,700,736,36,700,36,36,36,36,736,736,736,736,736,736,736,36,0,36,0,36,36,36,736,736,736,736,736,736,736,0,736,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,736,736,736,736,36,700,36,36,36,36,36,36,36,36,36,36,36,700,585,585,700,592,700,700,700,700,700,700,700,736,736,736,736,5116,891,0,0,0,0,0,39,39,0,39,39,59,891,59,59,59,59,39,59,59,59,59,59,59,59,59,59,59,18,18,18,18,18,18,18,891,891,891,891,891,891,873,18,873,18,18,18,891,891,891,891,891,0,0,0,891,0,891,0,0,0,0,0,0,59,891,891,891,159,159,891,891,891,18,448,891,891,891,891,891,15,891,891,891,891,891,891,891,891,39,39,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,39,39,39,39,11,11,11,11,0,11,11,11,11,11,11,11,11,11,11,11,0,0,0,0,28,39,39,39,59,59,20,39,20,20,20,20,20,20,0,20,39,59,59,59,39,20,39,39,39,39,20,59,59,59,59,0,59,59,59,59,59,59,59,59,0,0,59,59,59,0,0,59,59,59,59,59,20,39,39,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,59,890,59,890,890,890,890,890,890,890,890,890,890,890,831,831,831,831,59,59,59,59,59,59,59,59,59,59,59,59,59,59,39,20,39,39,0,20,20,20,20,20,20,20,20,20,20,0,20,20,20,20,20,20,20,20,20,59,59,59,59,59,59,59,59,59,59,890,890,890,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,590,20,59,39,0,0,0,15,572,590,590,850,143,850,850,850,0,0,0,0,0,22,16,22,22,22,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,18,18,18,0,18,0,0,0,0,18,18,18,18,0,0,0,18,18,18,0,0,0,0,0,0,0,0,0,965,965,59,59,59,59,59,59,0,0,736,736,1994,1994,150,150,2050,2050]]