Added --epub-embed-font
option.
* This can be repeated for multiple fonts. * Added parameter for fonts to embed to writeEPUB. * Added ttf, otf to Mime types in Text.Pandoc.MIME.
This commit is contained in:
parent
34801acc69
commit
8f1bfec7b9
4 changed files with 69 additions and 6 deletions
32
README
32
README
|
@ -442,6 +442,38 @@ Options affecting specific writers
|
||||||
id="BookId">` (a randomly generated UUID). Any of these may be
|
id="BookId">` (a randomly generated UUID). Any of these may be
|
||||||
overridden by elements in the metadata file.
|
overridden by elements in the metadata file.
|
||||||
|
|
||||||
|
`--epub-embed-font=`*FILE*
|
||||||
|
: Embed the specified font in the EPUB. This option can be repeated
|
||||||
|
to embed multiple fonts. To use embedded fonts, you
|
||||||
|
will need to add declarations like the following to your CSS (see
|
||||||
|
``--epub-stylesheet`):
|
||||||
|
|
||||||
|
@font-face {
|
||||||
|
font-family: DejaVuSans;
|
||||||
|
font-style: normal;
|
||||||
|
font-weight: normal;
|
||||||
|
src:url("DejaVuSans-Regular.ttf");
|
||||||
|
}
|
||||||
|
@font-face {
|
||||||
|
font-family: DejaVuSans;
|
||||||
|
font-style: normal;
|
||||||
|
font-weight: bold;
|
||||||
|
src:url("DejaVuSans-Bold.ttf");
|
||||||
|
}
|
||||||
|
@font-face {
|
||||||
|
font-family: DejaVuSans;
|
||||||
|
font-style: italic;
|
||||||
|
font-weight: normal;
|
||||||
|
src:url("DejaVuSans-Oblique.ttf");
|
||||||
|
}
|
||||||
|
@font-face {
|
||||||
|
font-family: DejaVuSans;
|
||||||
|
font-style: italic;
|
||||||
|
font-weight: bold;
|
||||||
|
src:url("DejaVuSans-BoldOblique.ttf");
|
||||||
|
}
|
||||||
|
body { font-family: "DejaVuSans"; }
|
||||||
|
|
||||||
`--latex-engine=`*pdflatex|lualatex|xelatex*
|
`--latex-engine=`*pdflatex|lualatex|xelatex*
|
||||||
: Use the specified LaTeX engine when producing PDF output.
|
: Use the specified LaTeX engine when producing PDF output.
|
||||||
The default is `pdflatex`. If the engine is not in your PATH,
|
The default is `pdflatex`. If the engine is not in your PATH,
|
||||||
|
|
|
@ -295,6 +295,7 @@ getMimeType f = M.lookup (map toLower $ drop 1 $ takeExtension f) mimeTypes
|
||||||
,("oth","application/vnd.oasis.opendocument.text-web")
|
,("oth","application/vnd.oasis.opendocument.text-web")
|
||||||
,("otp","application/vnd.oasis.opendocument.presentation-template")
|
,("otp","application/vnd.oasis.opendocument.presentation-template")
|
||||||
,("ots","application/vnd.oasis.opendocument.spreadsheet-template")
|
,("ots","application/vnd.oasis.opendocument.spreadsheet-template")
|
||||||
|
,("otf","application/x-font-opentype")
|
||||||
,("ott","application/vnd.oasis.opendocument.text-template")
|
,("ott","application/vnd.oasis.opendocument.text-template")
|
||||||
,("oza","application/x-oz-application")
|
,("oza","application/x-oz-application")
|
||||||
,("p","text/x-pascal")
|
,("p","text/x-pascal")
|
||||||
|
@ -428,6 +429,7 @@ getMimeType f = M.lookup (map toLower $ drop 1 $ takeExtension f) mimeTypes
|
||||||
,("ts","text/texmacs")
|
,("ts","text/texmacs")
|
||||||
,("tsp","application/dsptype")
|
,("tsp","application/dsptype")
|
||||||
,("tsv","text/tab-separated-values")
|
,("tsv","text/tab-separated-values")
|
||||||
|
,("ttf","application/x-font-truetype")
|
||||||
,("txt","text/plain")
|
,("txt","text/plain")
|
||||||
,("udeb","application/x-debian-package")
|
,("udeb","application/x-debian-package")
|
||||||
,("uls","text/iuls")
|
,("uls","text/iuls")
|
||||||
|
|
|
@ -32,7 +32,7 @@ import Data.IORef
|
||||||
import Data.Maybe ( fromMaybe, isNothing )
|
import Data.Maybe ( fromMaybe, isNothing )
|
||||||
import Data.List ( findIndices, isPrefixOf )
|
import Data.List ( findIndices, isPrefixOf )
|
||||||
import System.Environment ( getEnv )
|
import System.Environment ( getEnv )
|
||||||
import System.FilePath ( (</>), (<.>), takeBaseName, takeExtension )
|
import System.FilePath ( (</>), (<.>), takeBaseName, takeExtension, takeFileName )
|
||||||
import qualified Data.ByteString.Lazy as B
|
import qualified Data.ByteString.Lazy as B
|
||||||
import Data.ByteString.Lazy.UTF8 ( fromString )
|
import Data.ByteString.Lazy.UTF8 ( fromString )
|
||||||
import Codec.Archive.Zip
|
import Codec.Archive.Zip
|
||||||
|
@ -47,13 +47,15 @@ import Text.Pandoc.Writers.HTML
|
||||||
import Text.Pandoc.Writers.Markdown ( writePlain )
|
import Text.Pandoc.Writers.Markdown ( writePlain )
|
||||||
import Data.Char ( toLower )
|
import Data.Char ( toLower )
|
||||||
import Network.URI ( unEscapeString )
|
import Network.URI ( unEscapeString )
|
||||||
|
import Text.Pandoc.MIME (getMimeType)
|
||||||
|
|
||||||
-- | Produce an EPUB file from a Pandoc document.
|
-- | Produce an EPUB file from a Pandoc document.
|
||||||
writeEPUB :: Maybe String -- ^ EPUB stylesheet specified at command line
|
writeEPUB :: Maybe String -- ^ EPUB stylesheet specified at command line
|
||||||
|
-> [FilePath] -- ^ Paths to fonts to embed
|
||||||
-> WriterOptions -- ^ Writer options
|
-> WriterOptions -- ^ Writer options
|
||||||
-> Pandoc -- ^ Document to convert
|
-> Pandoc -- ^ Document to convert
|
||||||
-> IO B.ByteString
|
-> IO B.ByteString
|
||||||
writeEPUB mbStylesheet opts doc@(Pandoc meta _) = do
|
writeEPUB mbStylesheet fonts opts doc@(Pandoc meta _) = do
|
||||||
epochtime <- floor `fmap` getPOSIXTime
|
epochtime <- floor `fmap` getPOSIXTime
|
||||||
let mkEntry path content = toEntry path epochtime content
|
let mkEntry path content = toEntry path epochtime content
|
||||||
let opts' = opts{ writerEmailObfuscation = NoObfuscation
|
let opts' = opts{ writerEmailObfuscation = NoObfuscation
|
||||||
|
@ -101,6 +103,10 @@ writeEPUB mbStylesheet opts doc@(Pandoc meta _) = do
|
||||||
return e{ eRelativePath = newsrc }
|
return e{ eRelativePath = newsrc }
|
||||||
picEntries <- mapM readPicEntry pics
|
picEntries <- mapM readPicEntry pics
|
||||||
|
|
||||||
|
-- handle fonts
|
||||||
|
let mkFontEntry f = mkEntry (takeFileName f) `fmap` B.readFile f
|
||||||
|
fontEntries <- mapM mkFontEntry fonts
|
||||||
|
|
||||||
-- body pages
|
-- body pages
|
||||||
let isH1 (Header 1 _) = True
|
let isH1 (Header 1 _) = True
|
||||||
isH1 _ = False
|
isH1 _ = False
|
||||||
|
@ -137,6 +143,10 @@ writeEPUB mbStylesheet opts doc@(Pandoc meta _) = do
|
||||||
("href", eRelativePath ent),
|
("href", eRelativePath ent),
|
||||||
("media-type", fromMaybe "application/octet-stream"
|
("media-type", fromMaybe "application/octet-stream"
|
||||||
$ imageTypeOf $ eRelativePath ent)] $ ()
|
$ imageTypeOf $ eRelativePath ent)] $ ()
|
||||||
|
let fontNode ent = unode "item" !
|
||||||
|
[("id", takeBaseName $ eRelativePath ent),
|
||||||
|
("href", eRelativePath ent),
|
||||||
|
("media-type", maybe "" id $ getMimeType $ eRelativePath ent)] $ ()
|
||||||
let plainify t = removeTrailingSpace $
|
let plainify t = removeTrailingSpace $
|
||||||
writePlain opts'{ writerStandalone = False } $
|
writePlain opts'{ writerStandalone = False } $
|
||||||
Pandoc meta [Plain t]
|
Pandoc meta [Plain t]
|
||||||
|
@ -156,7 +166,8 @@ writeEPUB mbStylesheet opts doc@(Pandoc meta _) = do
|
||||||
,("media-type","text/css")] $ ()
|
,("media-type","text/css")] $ ()
|
||||||
] ++
|
] ++
|
||||||
map chapterNode (cpgEntry ++ (tpEntry : chapterEntries)) ++
|
map chapterNode (cpgEntry ++ (tpEntry : chapterEntries)) ++
|
||||||
map pictureNode (cpicEntry ++ picEntries)
|
map pictureNode (cpicEntry ++ picEntries) ++
|
||||||
|
map fontNode fontEntries
|
||||||
, unode "spine" ! [("toc","ncx")] $
|
, unode "spine" ! [("toc","ncx")] $
|
||||||
case mbCoverImage of
|
case mbCoverImage of
|
||||||
Nothing -> []
|
Nothing -> []
|
||||||
|
@ -210,6 +221,13 @@ writeEPUB mbStylesheet opts doc@(Pandoc meta _) = do
|
||||||
,("media-type","application/oebps-package+xml")] $ ()
|
,("media-type","application/oebps-package+xml")] $ ()
|
||||||
let containerEntry = mkEntry "META-INF/container.xml" containerData
|
let containerEntry = mkEntry "META-INF/container.xml" containerData
|
||||||
|
|
||||||
|
-- com.apple.ibooks.display-options.xml
|
||||||
|
let apple = fromString $ ppTopElement $
|
||||||
|
unode "display_options" $
|
||||||
|
unode "platform" ! [("name","*")] $
|
||||||
|
unode "option" ! [("name","specified-fonts")] $ "true"
|
||||||
|
let appleEntry = mkEntry "META-INF/com.apple.ibooks.display-options.xml" apple
|
||||||
|
|
||||||
-- stylesheet
|
-- stylesheet
|
||||||
stylesheet <- case mbStylesheet of
|
stylesheet <- case mbStylesheet of
|
||||||
Just s -> return s
|
Just s -> return s
|
||||||
|
@ -218,9 +236,9 @@ writeEPUB mbStylesheet opts doc@(Pandoc meta _) = do
|
||||||
|
|
||||||
-- construct archive
|
-- construct archive
|
||||||
let archive = foldr addEntryToArchive emptyArchive
|
let archive = foldr addEntryToArchive emptyArchive
|
||||||
(mimetypeEntry : containerEntry : stylesheetEntry : tpEntry :
|
(mimetypeEntry : containerEntry : appleEntry : stylesheetEntry : tpEntry :
|
||||||
contentsEntry : tocEntry :
|
contentsEntry : tocEntry :
|
||||||
(picEntries ++ cpicEntry ++ cpgEntry ++ chapterEntries) )
|
(picEntries ++ cpicEntry ++ cpgEntry ++ chapterEntries ++ fontEntries) )
|
||||||
return $ fromArchive archive
|
return $ fromArchive archive
|
||||||
|
|
||||||
metadataElement :: String -> UUID -> String -> String -> [String] -> String -> Maybe a -> Element
|
metadataElement :: String -> UUID -> String -> String -> [String] -> String -> Maybe a -> Element
|
||||||
|
|
|
@ -113,6 +113,7 @@ data Opt = Opt
|
||||||
, optReferenceDocx :: Maybe FilePath -- ^ Path of reference.docx
|
, optReferenceDocx :: Maybe FilePath -- ^ Path of reference.docx
|
||||||
, optEPUBStylesheet :: Maybe String -- ^ EPUB stylesheet
|
, optEPUBStylesheet :: Maybe String -- ^ EPUB stylesheet
|
||||||
, optEPUBMetadata :: String -- ^ EPUB metadata
|
, optEPUBMetadata :: String -- ^ EPUB metadata
|
||||||
|
, optEPUBFonts :: [FilePath] -- ^ EPUB fonts to embed
|
||||||
, optDumpArgs :: Bool -- ^ Output command-line arguments
|
, optDumpArgs :: Bool -- ^ Output command-line arguments
|
||||||
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
|
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
|
||||||
, optStrict :: Bool -- ^ Use strict markdown syntax
|
, optStrict :: Bool -- ^ Use strict markdown syntax
|
||||||
|
@ -163,6 +164,7 @@ defaultOpts = Opt
|
||||||
, optReferenceDocx = Nothing
|
, optReferenceDocx = Nothing
|
||||||
, optEPUBStylesheet = Nothing
|
, optEPUBStylesheet = Nothing
|
||||||
, optEPUBMetadata = ""
|
, optEPUBMetadata = ""
|
||||||
|
, optEPUBFonts = []
|
||||||
, optDumpArgs = False
|
, optDumpArgs = False
|
||||||
, optIgnoreArgs = False
|
, optIgnoreArgs = False
|
||||||
, optStrict = False
|
, optStrict = False
|
||||||
|
@ -531,6 +533,13 @@ options =
|
||||||
"FILENAME")
|
"FILENAME")
|
||||||
"" -- "Path of epub metadata file"
|
"" -- "Path of epub metadata file"
|
||||||
|
|
||||||
|
, Option "" ["epub-embed-font"]
|
||||||
|
(ReqArg
|
||||||
|
(\arg opt -> do
|
||||||
|
return opt{ optEPUBFonts = arg : optEPUBFonts opt })
|
||||||
|
"FILE")
|
||||||
|
"" -- "Directory of fonts to embed"
|
||||||
|
|
||||||
, Option "" ["latex-engine"]
|
, Option "" ["latex-engine"]
|
||||||
(ReqArg
|
(ReqArg
|
||||||
(\arg opt -> do
|
(\arg opt -> do
|
||||||
|
@ -792,6 +801,7 @@ main = do
|
||||||
, optReferenceDocx = referenceDocx
|
, optReferenceDocx = referenceDocx
|
||||||
, optEPUBStylesheet = epubStylesheet
|
, optEPUBStylesheet = epubStylesheet
|
||||||
, optEPUBMetadata = epubMetadata
|
, optEPUBMetadata = epubMetadata
|
||||||
|
, optEPUBFonts = epubFonts
|
||||||
, optDumpArgs = dumpArgs
|
, optDumpArgs = dumpArgs
|
||||||
, optIgnoreArgs = ignoreArgs
|
, optIgnoreArgs = ignoreArgs
|
||||||
, optStrict = strict
|
, optStrict = strict
|
||||||
|
@ -1021,7 +1031,8 @@ main = do
|
||||||
case lookup writerName' writers of
|
case lookup writerName' writers of
|
||||||
Nothing
|
Nothing
|
||||||
| writerName' == "epub" ->
|
| writerName' == "epub" ->
|
||||||
writeEPUB epubStylesheet writerOptions doc2 >>= writeBinary
|
writeEPUB epubStylesheet epubFonts writerOptions doc2
|
||||||
|
>>= writeBinary
|
||||||
| writerName' == "odt" ->
|
| writerName' == "odt" ->
|
||||||
writeODT referenceODT writerOptions doc2 >>= writeBinary
|
writeODT referenceODT writerOptions doc2 >>= writeBinary
|
||||||
| writerName' == "docx" ->
|
| writerName' == "docx" ->
|
||||||
|
|
Loading…
Reference in a new issue