diff options
| author | John MacFarlane <jgm@berkeley.edu> | 2017-01-27 10:27:34 +0100 | 
|---|---|---|
| committer | John MacFarlane <jgm@berkeley.edu> | 2017-01-27 10:27:34 +0100 | 
| commit | f5dd1238198450c4917707214f19e2f0da8c3cb4 (patch) | |
| tree | 9e80e45c3f5cc3eb0ce9a4c4425380a903cd666c /src | |
| parent | b6c1d491f5379f1924657f525540766dbbc1ae0f (diff) | |
| download | pandoc-f5dd1238198450c4917707214f19e2f0da8c3cb4.tar.gz | |
HTML writer: export writeHtmlStringForEPUB.
Options: Remove writerEPUBVersion.
Diffstat (limited to 'src')
| -rw-r--r-- | src/Text/Pandoc/Options.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 36 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 32 | 
3 files changed, 42 insertions, 28 deletions
| diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 39fee298d..755ab9add 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -175,7 +175,6 @@ data WriterOptions = WriterOptions    , writerHighlightStyle   :: Maybe Style  -- ^ Style to use for highlighting                                             -- (Nothing = no highlighting)    , writerSetextHeaders    :: Bool       -- ^ Use setext headers for levels 1-2 in markdown -  , writerEpubVersion      :: Maybe EPUBVersion -- ^ Nothing or EPUB version    , writerEpubMetadata     :: String     -- ^ Metadata to include in EPUB    , writerEpubStylesheet   :: Maybe String -- ^ EPUB stylesheet specified at command line    , writerEpubFonts        :: [FilePath] -- ^ Paths to fonts to embed @@ -214,7 +213,6 @@ instance Default WriterOptions where                        , writerListings         = False                        , writerHighlightStyle   = Just pygments                        , writerSetextHeaders    = True -                      , writerEpubVersion      = Nothing                        , writerEpubMetadata     = ""                        , writerEpubStylesheet   = Nothing                        , writerEpubFonts        = [] diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index c2fc4422e..ae77c10a2 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -59,10 +59,9 @@ import Control.Monad (mplus, when, zipWithM)  import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs                        , strContent, lookupAttr, Node(..), QName(..), parseXML                        , onlyElems, node, ppElement) -import Text.Pandoc.Writers.HTML ( writeHtml4, writeHtml5 ) +import Text.Pandoc.Writers.HTML ( writeHtmlStringForEPUB )  import Data.Char ( toLower, isDigit, isAlphaNum )  import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType) -import Text.Blaze.Html.Renderer.Utf8 (renderHtml)  import Text.HTML.TagSoup (Tag(TagOpen), fromAttrib, parseTags)  import Control.Monad.Except (throwError, catchError)  import Text.Pandoc.Error @@ -361,16 +360,18 @@ writeEPUB epubVersion opts doc =    let initState = EPUBState { stMediaPaths = []                              }    in -    evalStateT (pandocToEPUB opts{ writerEpubVersion = Just epubVersion } doc) +    evalStateT (pandocToEPUB epubVersion opts doc)        initState  pandocToEPUB :: PandocMonad m -             => WriterOptions +             => EPUBVersion +             -> WriterOptions               -> Pandoc               -> E m B.ByteString -pandocToEPUB opts doc@(Pandoc meta _) = do -  let version = fromMaybe EPUB2 (writerEpubVersion opts) -  let epub3 = writerEpubVersion opts == Just EPUB3 +pandocToEPUB version opts doc@(Pandoc meta _) = do +  let epub3 = version == EPUB3 +  let writeHtml o = fmap UTF8.fromStringLazy . +                         writeHtmlStringForEPUB version o    epochtime <- floor <$> lift P.getPOSIXTime    let mkEntry path content = toEntry path epochtime content    let vars = ("epub3", if epub3 then "true" else "false") @@ -384,9 +385,6 @@ pandocToEPUB opts doc@(Pandoc meta _) = do                            then MathML Nothing                            else writerHTMLMathMethod opts                    , writerWrapText = WrapAuto } -  let writeHtml = if epub3 -                     then writeHtml5 -                     else writeHtml4    metadata <- getEPUBMetadata opts' meta    -- cover page @@ -395,17 +393,17 @@ pandocToEPUB opts doc@(Pandoc meta _) = do                       Nothing   -> return ([],[])                       Just img  -> do                         let coverImage = "media/" ++ takeFileName img -                       cpContent <- renderHtml <$> (lift $ writeHtml +                       cpContent <- lift $ writeHtml                              opts'{ writerVariables = ("coverpage","true"):vars } -                            (Pandoc meta [RawBlock (Format "html") $ "<div id=\"cover-image\">\n<img src=\"" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"])) +                            (Pandoc meta [RawBlock (Format "html") $ "<div id=\"cover-image\">\n<img src=\"" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"])                         imgContent <- lift $ P.readFileLazy img                         return ( [mkEntry "cover.xhtml" cpContent]                                , [mkEntry coverImage imgContent] )    -- title page -  tpContent <- renderHtml <$> (lift $ writeHtml opts'{ +  tpContent <- lift $ writeHtml opts'{                                    writerVariables = ("titlepage","true"):vars } -                               (Pandoc meta [])) +                               (Pandoc meta [])    let tpEntry = mkEntry "title_page.xhtml" tpContent    -- handle pictures @@ -504,9 +502,8 @@ pandocToEPUB opts doc@(Pandoc meta _) = do                   chapters'    let chapToEntry num (Chapter mbnum bs) = -       (mkEntry (showChapter num) . renderHtml) <$> -        (writeHtml opts'{ writerNumberOffset = -                          fromMaybe [] mbnum } +       mkEntry (showChapter num) <$> +        (writeHtml opts'{ writerNumberOffset = fromMaybe [] mbnum }           $ case bs of               (Header _ _ xs : _) ->                 -- remove notes or we get doubled footnotes @@ -702,11 +699,10 @@ pandocToEPUB opts doc@(Pandoc meta _) = do                              ]                            ]                       else [] -  navData <- renderHtml <$> (lift $ writeHtml -                      opts'{ writerVariables = ("navpage","true"):vars } +  navData <- lift $ writeHtml opts'{ writerVariables = ("navpage","true"):vars }              (Pandoc (setMeta "title"                       (walk removeNote $ fromList $ docTitle' meta) nullMeta) -               (navBlocks ++ landmarks))) +               (navBlocks ++ landmarks))    let navEntry = mkEntry "nav.xhtml" navData    -- mimetype diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index ee1f260b6..518848139 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -29,8 +29,12 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to HTML.  -}  module Text.Pandoc.Writers.HTML ( -  writeHtml4, writeHtml4String, -  writeHtml5, writeHtml5String ) where +  writeHtml4, +  writeHtml4String, +  writeHtml5, +  writeHtml5String, +  writeHtmlStringForEPUB +  ) where  import Text.Pandoc.Definition  import Text.Pandoc.Walk  import Data.Monoid ((<>)) @@ -83,12 +87,14 @@ data WriterState = WriterState      , stSecNum           :: [Int]   -- ^ Number of current section      , stElement          :: Bool    -- ^ Processing an Element      , stHtml5            :: Bool    -- ^ Use HTML5 +    , stEPUBVersion      :: Maybe EPUBVersion -- ^ EPUB version if for epub      }  defaultWriterState :: WriterState  defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False,                                    stHighlighting = False, stSecNum = [], -                                  stElement = False, stHtml5 = False} +                                  stElement = False, stHtml5 = False, +                                  stEPUBVersion = Nothing}  -- Helpers to render HTML with the appropriate function. @@ -121,6 +127,18 @@ writeHtml4String = writeHtmlString' False  writeHtml4 :: PandocMonad m => WriterOptions -> Pandoc -> m Html  writeHtml4 = writeHtml' False +-- | Convert Pandoc document to Html appropriate for an epub version. +writeHtmlStringForEPUB :: PandocMonad m +                       => EPUBVersion -> WriterOptions -> Pandoc -> m String +writeHtmlStringForEPUB version opts d = do +  (body, context) <- evalStateT (pandocToHtml opts d) +                      defaultWriterState{ stHtml5 = version == EPUB3, +                                          stEPUBVersion = Just version } +  return $ case writerTemplate opts of +             Nothing  -> renderHtml body +             Just tpl -> renderTemplate' tpl $ +                           defField "body" (renderHtml body) context +  writeHtmlString' :: PandocMonad m => Bool -> WriterOptions -> Pandoc -> m String  writeHtmlString' html5 opts d = do    (body, context) <- evalStateT (pandocToHtml opts d) @@ -892,6 +910,7 @@ inlineToHtml opts inline = do                          let number = (length notes) + 1                          let ref = show number                          htmlContents <- blockListToNote opts ref contents +                        epubVersion <- gets stEPUBVersion                          -- push contents onto front of notes                          modify $ \st -> st {stNotes = (htmlContents:notes)}                          let revealSlash = ['/' | writerSlideVariant opts @@ -901,11 +920,11 @@ inlineToHtml opts inline = do                                           writerIdentifierPrefix opts ++ "fn" ++ ref)                                         ! A.class_ "footnoteRef"                                         ! prefixedId opts ("fnref" ++ ref) -                                       $ (if isJust (writerEpubVersion opts) +                                       $ (if isJust epubVersion                                               then id                                               else H.sup)                                         $ toHtml ref -                        return $ case writerEpubVersion opts of +                        return $ case epubVersion of                                        Just EPUB3 -> link ! customAttribute "epub:type" "noteref"                                        _          -> link      (Cite cits il)-> do contents <- inlineListToHtml opts il @@ -933,7 +952,8 @@ blockListToNote opts ref blocks =                                                   Plain backlink]    in  do contents <- blockListToHtml opts blocks'           let noteItem = H.li ! (prefixedId opts ("fn" ++ ref)) $ contents -         let noteItem' = case writerEpubVersion opts of +         epubVersion <- gets stEPUBVersion +         let noteItem' = case epubVersion of                                Just EPUB3 -> noteItem ! customAttribute "epub:type" "footnote"                                _          -> noteItem           return $ nl opts >> noteItem' | 
