aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt15
-rw-r--r--src/Text/Pandoc/App.hs15
-rw-r--r--src/Text/Pandoc/Options.hs2
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs52
4 files changed, 37 insertions, 47 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 2c9fdcbe6..d55cff12d 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -758,6 +758,12 @@ Options affecting specific writers
: Link to a CSS style sheet. This option can be used repeatedly to
include multiple files. They will be included in the order specified.
+ A stylesheet is required for generating EPUB. If none is
+ provided using this option (or the `stylesheet` metadata
+ field), pandoc will look for a file `epub.css` in the
+ user data directory (see `--data-dir`). If it is not
+ found there, sensible defaults will be used.
+
`--reference-doc=`*FILE*
: Use the specified file as a style reference in producing a
@@ -804,13 +810,6 @@ Options affecting specific writers
LibreOffice, modify the styles as you wish, and save the
file.
-`--epub-stylesheet=`*FILE*
-
-: Use the specified CSS file to style the EPUB. If no stylesheet
- is specified, pandoc will look for a file `epub.css` in the
- user data directory (see `--data-dir`). If it is not
- found there, sensible defaults will be used.
-
`--epub-cover-image=`*FILE*
: Use the specified image as the EPUB cover. It is recommended
@@ -847,7 +846,7 @@ Options affecting specific writers
line, be sure to escape them or put the whole filename in single quotes,
to prevent them from being interpreted by the shell. To use the
embedded fonts, you will need to add declarations like the following
- to your CSS (see `--epub-stylesheet`):
+ to your CSS (see `--css`):
@font-face {
font-family: DejaVuSans;
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 8c11a0ff7..27b3d50df 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -112,10 +112,6 @@ convertWithOpts opts = do
mapM_ (UTF8.hPutStrLn stdout) args
exitSuccess
- epubStylesheet <- case optEpubStylesheet opts of
- Nothing -> return Nothing
- Just fp -> Just <$> UTF8.readFile fp
-
epubMetadata <- case optEpubMetadata opts of
Nothing -> return Nothing
Just fp -> Just <$> UTF8.readFile fp
@@ -319,7 +315,6 @@ convertWithOpts opts = do
writerHighlightStyle = highlightStyle,
writerSetextHeaders = optSetextHeaders opts,
writerEpubMetadata = epubMetadata,
- writerEpubStylesheet = epubStylesheet,
writerEpubFonts = optEpubFonts opts,
writerEpubChapterLevel = optEpubChapterLevel opts,
writerTOCDepth = optTOCDepth opts,
@@ -493,7 +488,6 @@ data Opt = Opt
, optTopLevelDivision :: TopLevelDivision -- ^ Type of the top-level divisions
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
, optReferenceDoc :: Maybe FilePath -- ^ Path of reference doc
- , optEpubStylesheet :: Maybe FilePath -- ^ EPUB stylesheet
, optEpubMetadata :: Maybe FilePath -- ^ EPUB metadata
, optEpubFonts :: [FilePath] -- ^ EPUB fonts to embed
, optEpubChapterLevel :: Int -- ^ Header level at which to split chapters
@@ -559,7 +553,6 @@ defaultOpts = Opt
, optTopLevelDivision = TopLevelDefault
, optHTMLMathMethod = PlainMath
, optReferenceDoc = Nothing
- , optEpubStylesheet = Nothing
, optEpubMetadata = Nothing
, optEpubFonts = []
, optEpubChapterLevel = 1
@@ -1118,12 +1111,6 @@ options =
"FILENAME")
"" -- "Path of custom reference doc"
- , Option "" ["epub-stylesheet"]
- (ReqArg
- (\arg opt -> return opt { optEpubStylesheet = Just arg })
- "FILENAME")
- "" -- "Path of epub.css"
-
, Option "" ["epub-cover-image"]
(ReqArg
(\arg opt ->
@@ -1430,6 +1417,8 @@ handleUnrecognizedOption "--reference-odt" =
("--reference-odt has been removed. Use --reference-doc instead." :)
handleUnrecognizedOption "--parse-raw" =
(("--parse-raw/-R has been removed. Use +raw_html or +raw_tex extension.\n") :)
+handleUnrecognizedOption "--epub-stylesheet" =
+ (("--epub-stylesheet has been removed. Use --css instead.\n") :)
handleUnrecognizedOption "-R" = handleUnrecognizedOption "--parse-raw"
handleUnrecognizedOption x =
(("Unknown option " ++ x ++ ".") :)
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index bc62f87d0..41688af89 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -167,7 +167,6 @@ data WriterOptions = WriterOptions
-- (Nothing = no highlighting)
, writerSetextHeaders :: Bool -- ^ Use setext headers for levels 1-2 in markdown
, writerEpubMetadata :: Maybe String -- ^ Metadata to include in EPUB
- , writerEpubStylesheet :: Maybe String -- ^ EPUB stylesheet specified at command line
, writerEpubFonts :: [FilePath] -- ^ Paths to fonts to embed
, writerEpubChapterLevel :: Int -- ^ Header level for chapters (separate files)
, writerTOCDepth :: Int -- ^ Number of levels to include in TOC
@@ -203,7 +202,6 @@ instance Default WriterOptions where
, writerHighlightStyle = Just pygments
, writerSetextHeaders = True
, writerEpubMetadata = Nothing
- , writerEpubStylesheet = Nothing
, writerEpubFonts = []
, writerEpubChapterLevel = 1
, writerTOCDepth = 3
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 247014c20..17fa0bf3e 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -98,14 +98,10 @@ data EPUBMetadata = EPUBMetadata{
, epubCoverage :: Maybe String
, epubRights :: Maybe String
, epubCoverImage :: Maybe String
- , epubStylesheet :: Maybe Stylesheet
+ , epubStylesheets :: [FilePath]
, epubPageDirection :: Maybe ProgressionDirection
} deriving Show
-data Stylesheet = StylesheetPath FilePath
- | StylesheetContents String
- deriving Show
-
data Date = Date{
dateText :: String
, dateEvent :: Maybe String
@@ -240,6 +236,10 @@ metaValueToString (MetaBool True) = "true"
metaValueToString (MetaBool False) = "false"
metaValueToString _ = ""
+metaValueToPaths:: MetaValue -> [FilePath]
+metaValueToPaths (MetaList xs) = map metaValueToString xs
+metaValueToPaths x = [metaValueToString x]
+
getList :: String -> Meta -> (MetaValue -> a) -> [a]
getList s meta handleMetaValue =
case lookupMeta s meta of
@@ -307,7 +307,7 @@ metadataFromMeta opts meta = EPUBMetadata{
, epubCoverage = coverage
, epubRights = rights
, epubCoverImage = coverImage
- , epubStylesheet = stylesheet
+ , epubStylesheets = stylesheets
, epubPageDirection = pageDirection
}
where identifiers = getIdentifier meta
@@ -328,9 +328,9 @@ metadataFromMeta opts meta = EPUBMetadata{
rights = metaValueToString <$> lookupMeta "rights" meta
coverImage = lookup "epub-cover-image" (writerVariables opts) `mplus`
(metaValueToString <$> lookupMeta "cover-image" meta)
- stylesheet = (StylesheetContents <$> writerEpubStylesheet opts) `mplus`
- ((StylesheetPath . metaValueToString) <$>
- lookupMeta "stylesheet" meta)
+ stylesheets = maybe [] id
+ (metaValueToPaths <$> lookupMeta "stylesheet" meta) ++
+ [f | ("css",f) <- writerVariables opts]
pageDirection = case map toLower . metaValueToString <$>
lookupMeta "page-progression-direction" meta of
Just "ltr" -> Just LTR
@@ -374,10 +374,21 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
let writeHtml o = fmap UTF8.fromStringLazy .
writeHtmlStringForEPUB version o
epochtime <- floor <$> lift P.getPOSIXTime
+ metadata <- getEPUBMetadata opts meta
let mkEntry path content = toEntry path epochtime content
+
+ -- stylesheet
+ stylesheets <- case epubStylesheets metadata of
+ [] -> (\x -> [B.fromChunks [x]]) <$>
+ P.readDataFile (writerUserDataDir opts) "epub.css"
+ fs -> mapM P.readFileLazy fs
+ let stylesheetEntries = zipWith
+ (\bs n -> mkEntry ("stylesheet" ++ show n ++ ".css") bs)
+ stylesheets [(1 :: Int)..]
+
let vars = ("epub3", if epub3 then "true" else "false")
- : ("css", "stylesheet.css")
- : writerVariables opts
+ : map (\e -> ("css", eRelativePath e)) stylesheetEntries
+ ++ [(x,y) | (x,y) <- writerVariables opts, x /= "css"]
let opts' = opts{ writerEmailObfuscation = NoObfuscation
, writerSectionDivs = True
, writerVariables = vars
@@ -386,7 +397,6 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
then MathML
else writerHTMLMathMethod opts
, writerWrapText = WrapAuto }
- metadata <- getEPUBMetadata opts' meta
-- cover page
(cpgEntry, cpicEntry) <-
@@ -564,13 +574,14 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
, unode "manifest" $
[ unode "item" ! [("id","ncx"), ("href","toc.ncx")
,("media-type","application/x-dtbncx+xml")] $ ()
- , unode "item" ! [("id","style"), ("href","stylesheet.css")
- ,("media-type","text/css")] $ ()
, unode "item" ! ([("id","nav")
,("href","nav.xhtml")
,("media-type","application/xhtml+xml")] ++
[("properties","nav") | epub3 ]) $ ()
] ++
+ [ (unode "item" ! [("id","style"), ("href",fp)
+ ,("media-type","text/css")] $ ()) |
+ fp <- map eRelativePath stylesheetEntries ] ++
map chapterNode (cpgEntry ++ (tpEntry : chapterEntries)) ++
(case cpicEntry of
[] -> []
@@ -725,19 +736,12 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
unode "option" ! [("name","specified-fonts")] $ "true"
let appleEntry = mkEntry "META-INF/com.apple.ibooks.display-options.xml" apple
- -- stylesheet
- stylesheet <- case epubStylesheet metadata of
- Just (StylesheetPath fp) -> UTF8.toStringLazy <$> (lift $ P.readFileLazy fp)
- Just (StylesheetContents s) -> return s
- Nothing -> UTF8.toString `fmap`
- (lift $ P.readDataFile (writerUserDataDir opts) "epub.css")
- let stylesheetEntry = mkEntry "stylesheet.css" $ UTF8.fromStringLazy stylesheet
-
-- construct archive
let archive = foldr addEntryToArchive emptyArchive
- (mimetypeEntry : containerEntry : appleEntry : stylesheetEntry : tpEntry :
+ (mimetypeEntry : containerEntry : appleEntry : tpEntry :
contentsEntry : tocEntry : navEntry :
- (picEntries ++ cpicEntry ++ cpgEntry ++ chapterEntries ++ fontEntries))
+ (stylesheetEntries ++ picEntries ++ cpicEntry ++
+ cpgEntry ++ chapterEntries ++ fontEntries))
return $ fromArchive archive
metadataElement :: EPUBVersion -> EPUBMetadata -> UTCTime -> Element