diff options
Diffstat (limited to 'src/Text')
| -rw-r--r-- | src/Text/Pandoc/App/CommandLineOptions.hs | 8 | ||||
| -rw-r--r-- | src/Text/Pandoc/App/Opt.hs | 5 | ||||
| -rw-r--r-- | src/Text/Pandoc/App/OutputSettings.hs | 1 | ||||
| -rw-r--r-- | src/Text/Pandoc/Options.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 30 |
5 files changed, 35 insertions, 11 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs index c3abe1ba1..c50ec6208 100644 --- a/src/Text/Pandoc/App/CommandLineOptions.hs +++ b/src/Text/Pandoc/App/CommandLineOptions.hs @@ -601,6 +601,14 @@ options = "true|false") "" -- "Make slide shows include all the needed js and css" + , Option "" ["link-images"] -- maybe True (\argStr -> argStr == "true") arg + (OptArg + (\arg opt -> do + boolValue <- readBoolFromOptArg "--link-images" arg + return opt { optLinkImages = boolValue }) + "true|false") + "" -- "Link images in ODT rather than embedding them" + , Option "" ["request-header"] (ReqArg (\arg opt -> do diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs index c1f16279c..b6050f117 100644 --- a/src/Text/Pandoc/App/Opt.hs +++ b/src/Text/Pandoc/App/Opt.hs @@ -119,6 +119,7 @@ data Opt = Opt , optIncremental :: Bool -- ^ Use incremental lists in Slidy/Slideous/S5 , optSelfContained :: Bool -- ^ Make HTML accessible offline (deprecated) , optEmbedResources :: Bool -- ^ Make HTML accessible offline + , optLinkImages :: Bool -- ^ Link ODT images rather than embedding , optHtmlQTags :: Bool -- ^ Use <q> tags in HTML , optHighlightStyle :: Maybe Text -- ^ Style to use for highlighted code , optSyntaxDefinitions :: [FilePath] -- ^ xml syntax defs to load @@ -201,6 +202,7 @@ instance FromJSON Opt where <*> o .:? "incremental" .!= optIncremental defaultOpts <*> o .:? "self-contained" .!= optSelfContained defaultOpts <*> o .:? "embed-resources" .!= optEmbedResources defaultOpts + <*> o .:? "link-images" .!= optLinkImages defaultOpts <*> o .:? "html-q-tags" .!= optHtmlQTags defaultOpts <*> o .:? "highlight-style" <*> o .:? "syntax-definitions" .!= optSyntaxDefinitions defaultOpts @@ -526,6 +528,8 @@ doOpt (k,v) = do parseJSON v >>= \x -> return (\o -> o{ optSelfContained = x }) "embed-resources" -> parseJSON v >>= \x -> return (\o -> o{ optEmbedResources = x }) + "link-images" -> + parseJSON v >>= \x -> return (\o -> o{ optLinkImages = x }) "html-q-tags" -> parseJSON v >>= \x -> return (\o -> o{ optHtmlQTags = x }) "highlight-style" -> @@ -738,6 +742,7 @@ defaultOpts = Opt , optIncremental = False , optSelfContained = False , optEmbedResources = False + , optLinkImages = False , optHtmlQTags = False , optHighlightStyle = Just "pygments" , optSyntaxDefinitions = [] diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs index d08cb626b..11d813e5e 100644 --- a/src/Text/Pandoc/App/OutputSettings.hs +++ b/src/Text/Pandoc/App/OutputSettings.hs @@ -262,6 +262,7 @@ optToOutputSettings scriptingEngine opts = do , writerReferenceDoc = optReferenceDoc opts , writerSyntaxMap = syntaxMap , writerPreferAscii = optAscii opts + , writerLinkImages = optLinkImages opts } return $ OutputSettings { outputFormat = format diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 20aec2624..e4ff56b77 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -325,6 +325,7 @@ data WriterOptions = WriterOptions , writerReferenceLocation :: ReferenceLocation -- ^ Location of footnotes and references for writing markdown , writerSyntaxMap :: SyntaxMap , writerPreferAscii :: Bool -- ^ Prefer ASCII representations of characters when possible + , writerLinkImages :: Bool -- ^ Use links rather than embedding ODT images } deriving (Show, Data, Typeable, Generic) instance Default WriterOptions where @@ -363,6 +364,7 @@ instance Default WriterOptions where , writerReferenceLocation = EndOfDocument , writerSyntaxMap = defaultSyntaxMap , writerPreferAscii = False + , writerLinkImages = False } instance HasSyntaxExtensions WriterOptions where diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 8464a01e0..29ee3bd47 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -24,7 +24,7 @@ import qualified Data.Map as Map import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Data.Time -import System.FilePath (takeDirectory, takeExtension, (<.>)) +import System.FilePath (takeDirectory, takeExtension, (<.>), (</>), isAbsolute) import Text.Collate.Lang (Lang (..), renderLang) import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang) import qualified Text.Pandoc.Class.PandocMonad as P @@ -48,7 +48,7 @@ import Text.Pandoc.XML import Text.Pandoc.XML.Light import Text.TeXMath import qualified Text.XML.Light as XL -import Network.URI (parseRelativeReference, URI(uriPath)) +import Network.URI (parseRelativeReference, URI(uriPath), isURI) import Skylighting newtype ODTState = ODTState { stEntries :: [Entry] @@ -272,15 +272,23 @@ transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = catchError Just dim -> Just $ Inch $ inInch opts dim Nothing -> Nothing let newattr = (id', cls, dims) - entries <- gets stEntries - let extension = maybe (takeExtension $ takeWhile (/='?') $ T.unpack src) T.unpack - (mbMimeType >>= extensionFromMimeType) - let newsrc = "Pictures/" ++ show (length entries) <.> extension - let toLazy = B.fromChunks . (:[]) - epochtime <- floor `fmap` lift P.getPOSIXTime - let entry = toEntry newsrc epochtime $ toLazy img - modify $ \st -> st{ stEntries = entry : entries } - return $ Image newattr lab (T.pack newsrc, t)) + src' <- if writerLinkImages opts + then + case T.unpack src of + s | isURI s -> return src + | isAbsolute s -> return src + | otherwise -> return $ T.pack $ ".." </> s + else do + entries <- gets stEntries + let extension = maybe (takeExtension $ takeWhile (/='?') $ T.unpack src) T.unpack + (mbMimeType >>= extensionFromMimeType) + let newsrc = "Pictures/" ++ show (length entries) <.> extension + let toLazy = B.fromChunks . (:[]) + epochtime <- floor `fmap` lift P.getPOSIXTime + let entry = toEntry newsrc epochtime $ toLazy img + modify $ \st -> st{ stEntries = entry : entries } + return $ T.pack newsrc + return $ Image newattr lab (src', t)) (\e -> do report $ CouldNotFetchResource src $ T.pack (show e) return $ Emph lab) |
