{- 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 Text.Pandoc hiding (HTMLMathMethod(..)) import qualified Text.Pandoc as Pandoc import Text.Pandoc.SelfContained as SelfContained import Text.Pandoc.Shared (escapeStringUsing, readDataFile) import Network.Gitit.Server import Network.Gitit.Framework (pathForPage, getWikiBase) import Network.Gitit.Util (withTempDir, readFileUTF8) import Network.Gitit.State (getConfig) import Network.Gitit.Types import Network.Gitit.Cache (cacheContents, lookupCache) import Control.Monad.Trans (liftIO) import Control.Monad (unless, when) import Text.XHtml (noHtml) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L import Data.ByteString.Lazy.UTF8 (fromString) import System.FilePath ((<.>), (), takeDirectory) import Control.Exception (throwIO) import System.Environment (getEnvironment) import System.Exit (ExitCode(..)) import System.IO (openTempFile) import System.Directory (getCurrentDirectory, setCurrentDirectory, removeFile) import System.Process (runProcess, waitForProcess) import Codec.Binary.UTF8.String (encodeString) import Text.HTML.SanitizeXSS import qualified Data.Text as T import Data.List (isPrefixOf) defaultRespOptions :: WriterOptions defaultRespOptions = defaultWriterOptions { writerStandalone = True } respond :: String -> String -> (Pandoc -> IO L.ByteString) -> String -> Pandoc -> Handler respond mimetype ext fn page doc = liftIO (fn doc) >>= ok . setContentType mimetype . (if null ext then id else setFilename (page ++ "." ++ ext)) . toResponseBS B.empty respondX :: String -> String -> String -> (WriterOptions -> Pandoc -> IO L.ByteString) -> WriterOptions -> String -> Pandoc -> Handler respondX templ mimetype ext fn opts page doc = do cfg <- getConfig template' <- liftIO $ getDefaultTemplate (pandocUserData cfg) templ template <- case template' of Right t -> return t Left e -> liftIO $ throwIO e doc' <- if ext `elem` ["odt","pdf","epub","docx","rtf"] then fixURLs page doc else return doc doc'' <- if ext == "rtf" then liftIO $ bottomUpM rtfEmbedImage doc' else return doc' respond mimetype ext (fn opts{writerTemplate = template ,writerSourceDirectory = repositoryPath cfg ,writerUserDataDir = pandocUserData cfg}) page doc'' respondS :: String -> String -> String -> (WriterOptions -> Pandoc -> String) -> WriterOptions -> String -> Pandoc -> Handler respondS templ mimetype ext fn = respondX templ mimetype ext (\o d -> return $ fromString $ fn o d) respondSlides :: String -> HTMLSlideVariant -> String -> Pandoc -> Handler respondSlides templ slideVariant page doc = do cfg <- getConfig base' <- getWikiBase let math = case mathMethod cfg of MathML -> Pandoc.MathML Nothing WebTeX u -> Pandoc.WebTeX u JsMathScript -> Pandoc.JsMath (Just $ base' ++ "/js/jsMath/easy/load.js") _ -> Pandoc.PlainMath let opts' = defaultRespOptions { writerSlideVariant = slideVariant ,writerIncremental = True ,writerHtml5 = templ == "dzslides" ,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 let body' = writeHtmlString opts'{writerStandalone = False} (Pandoc meta blocks) -- just body let body'' = T.unpack $ (if xssSanitize cfg then sanitizeBalance else id) $ T.pack body' variables' <- if mathMethod cfg == MathML then do s <- liftIO $ readDataFile (pandocUserData cfg) $ "data""MathMLinHTML.js" return [("mathml-script", s)] else return [] template' <- liftIO $ getDefaultTemplate (pandocUserData cfg) templ template <- case template' of Right t -> return t Left e -> liftIO $ throwIO e dzcore <- if templ == "dzslides" then do dztempl <- liftIO $ readDataFile (pandocUserData cfg) $ "dzslides" "template.html" return $ unlines $ dropWhile (not . isPrefixOf "