{- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Functions for exporting wiki pages in various formats. -} module Network.Gitit.Export ( exportFormats ) where import Control.Exception (throwIO) import Text.Pandoc hiding (HTMLMathMethod(..), getDataFileName) import qualified Text.Pandoc as Pandoc import Text.Pandoc.PDF (makePDF) import Text.Pandoc.SelfContained as SelfContained import qualified Text.Pandoc.UTF8 as UTF8 import Network.Gitit.Server import Network.Gitit.Framework (pathForPage) import Network.Gitit.State (getConfig) import Network.Gitit.Types import Network.Gitit.Cache (cacheContents, lookupCache) import Control.Monad.Trans (liftIO) import Control.Monad (unless) import Text.XHtml (noHtml) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L import System.FilePath ((), takeDirectory) import System.Directory (doesFileExist) import Text.HTML.SanitizeXSS import Text.Pandoc.Writers.RTF (writeRTF) import Data.ByteString.Lazy (fromStrict) import Data.Text (Text) import qualified Data.Text as T import Data.Text.Encoding (encodeUtf8) import Data.List (isPrefixOf) import Skylighting (styleToCss, pygments) import Paths_gitit (getDataFileName) defaultRespOptions :: WriterOptions defaultRespOptions = def { writerHighlightStyle = Just pygments } respondX :: String -> String -> String -> (WriterOptions -> Pandoc -> PandocIO L.ByteString) -> WriterOptions -> String -> Pandoc -> Handler respondX templ mimetype ext fn opts page doc = do cfg <- getConfig doc' <- if ext `elem` ["odt","pdf","beamer","epub","docx","rtf"] then fixURLs page doc else return doc doc'' <- liftIO $ runIO $ do setUserDataDir $ pandocUserData cfg template <- getDefaultTemplate templ fn opts{ writerTemplate = Just template } doc' either (liftIO . throwIO) (ok . setContentType mimetype . (if null ext then id else setFilename (page ++ "." ++ ext)) . toResponseBS B.empty) doc'' respondS :: String -> String -> String -> (WriterOptions -> Pandoc -> PandocIO Text) -> WriterOptions -> String -> Pandoc -> Handler respondS templ mimetype ext fn = respondX templ mimetype ext (\o d -> fromStrict . encodeUtf8 <$> fn o d) respondSlides :: String -> (WriterOptions -> Pandoc -> PandocIO Text) -> String -> Pandoc -> Handler respondSlides templ fn page doc = do cfg <- getConfig let math = case mathMethod cfg of MathML -> Pandoc.MathML WebTeX u -> Pandoc.WebTeX u _ -> Pandoc.PlainMath let opts' = defaultRespOptions { writerIncremental = True , writerHTMLMathMethod = math} -- We sanitize the body only, to protect against XSS attacks. -- (Sanitizing the whole HTML page would strip out javascript -- needed for the slides.) We then pass the body into the -- slide template using the 'body' variable. Pandoc meta blocks <- fixURLs page doc docOrError <- liftIO $ runIO $ do setUserDataDir $ pandocUserData cfg body' <- writeHtml5String opts' (Pandoc meta blocks) -- just body let body'' = T.unpack $ (if xssSanitize cfg then sanitizeBalance else id) $ body' variables' <- if mathMethod cfg == MathML then do s <- readDataFile "MathMLinHTML.js" return [("mathml-script", UTF8.toString s)] else return [] template <- getDefaultTemplate templ dzcore <- if templ == "dzslides" then do dztempl <- readDataFile $ "dzslides" "template.html" return $ unlines $ dropWhile (not . isPrefixOf "