diff options
Diffstat (limited to 'src/Text')
| -rw-r--r-- | src/Text/Pandoc/App.hs | 25 | ||||
| -rw-r--r-- | src/Text/Pandoc/Class.hs | 54 | ||||
| -rw-r--r-- | src/Text/Pandoc/Lua/PandocModule.hs | 6 | ||||
| -rw-r--r-- | src/Text/Pandoc/Options.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/PDF.hs | 7 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Txt2Tags.hs | 10 | ||||
| -rw-r--r-- | src/Text/Pandoc/SelfContained.hs | 110 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/FB2.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/ICML.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 2 | 
14 files changed, 113 insertions, 115 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 | 
