diff options
-rw-r--r-- | Text/Pandoc/ODT.hs | 9 | ||||
-rw-r--r-- | Text/Pandoc/Shared.hs | 14 | ||||
-rw-r--r-- | pandoc.cabal | 6 |
3 files changed, 22 insertions, 7 deletions
diff --git a/Text/Pandoc/ODT.hs b/Text/Pandoc/ODT.hs index 487bcdedc..c254f6013 100644 --- a/Text/Pandoc/ODT.hs +++ b/Text/Pandoc/ODT.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE TemplateHaskell, OverloadedStrings #-} {- Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu> @@ -28,6 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Functions for producing an ODT file from OpenDocument XML. -} module Text.Pandoc.ODT ( saveOpenDocumentAsODT ) where +import Text.Pandoc.Shared ( contentsOf ) import Data.Maybe ( fromJust ) import Data.List ( partition, intersperse ) import Prelude hiding ( writeFile, readFile ) @@ -41,7 +43,7 @@ import Text.XML.Light import Text.XML.Light.Cursor import Text.Pandoc.Shared ( withTempDir ) import Network.URI ( isURI ) -import Paths_pandoc +import qualified Data.ByteString.Char8 as B ( writeFile ) -- | Produce an ODT file from OpenDocument XML. saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced. @@ -59,10 +61,10 @@ saveOpenDocumentAsODT destinationODTPath sourceDirRelative xml = do "It can be obtained from http://www.info-zip.org/Zip.html\n" ++ "Debian (and Debian-based) linux: apt-get install zip\n" ++ "Windows: See http://gnuwin32.sourceforge.net/packages/zip.htm" - referenceODTPath <- getDataFileName "reference.odt" withTempDir "pandoc-odt" $ \tempDir -> do let tempODT = tempDir </> "reference.odt" - copyFile referenceODTPath tempODT + copyFile "odt-styles/reference.odt" tempODT + B.writeFile tempODT $(contentsOf "odt-styles/reference.odt") createDirectory $ tempDir </> "Pictures" xml' <- handlePictures tempODT sourceDirRelative xml writeFile (tempDir </> "content.xml") xml' @@ -138,3 +140,4 @@ handleContent tempODT sourceDirRelative content@(Elem el) = do else return content handleContent _ _ c = return c -- not Element + diff --git a/Text/Pandoc/Shared.hs b/Text/Pandoc/Shared.hs index 3c202db0f..ea576472d 100644 --- a/Text/Pandoc/Shared.hs +++ b/Text/Pandoc/Shared.hs @@ -100,7 +100,9 @@ module Text.Pandoc.Shared ( WriterOptions (..), defaultWriterOptions, -- * File handling - withTempDir + withTempDir, + -- * Template haskell + contentsOf ) where import Text.Pandoc.Definition @@ -115,6 +117,9 @@ import Network.URI ( parseURI, URI (..), isAllowedInURI ) import System.FilePath ( (</>), (<.>) ) import System.IO.Error ( catch, ioError, isAlreadyExistsError ) import System.Directory +import Language.Haskell.TH +import Language.Haskell.TH.Syntax (Lift (..)) +import qualified Data.ByteString.Char8 as B -- -- List processing @@ -924,3 +929,10 @@ createTempDir num baseName = do then createTempDir (num + 1) baseName else ioError e +-- | Template haskell function to insert bytestring contents of file into a template. +contentsOf :: FilePath -> ExpQ +contentsOf p = lift =<< runIO (B.readFile p) + +instance Lift B.ByteString where + lift x = return (LitE (StringL $ B.unpack x)) + diff --git a/pandoc.cabal b/pandoc.cabal index 349238ce9..3c2ab5061 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -53,11 +53,11 @@ Extra-Source-Files: README, INSTALL, COPYRIGHT, COPYING, templates/ui/default/pretty.css, templates/ui/default/opera.css, templates/ui/default/outline.css, - templates/ui/default/print.css + templates/ui/default/print.css, + odt-styles/reference.odt Extra-Tmp-Files: Text/Pandoc/ASCIIMathML.hs, Text/Pandoc/DefaultHeaders.hs, Text/Pandoc/Writers/S5.hs -Data-Files: odt-styles/reference.odt Flag splitBase Description: Choose the new, smaller, split-up base package. Default: True @@ -79,7 +79,7 @@ Library if flag(highlighting) Build-depends: highlighting-kate cpp-options: -DHIGHLIGHTING - Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory, utf8-string + Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory, utf8-string, template-haskell, bytestring Hs-Source-Dirs: . Exposed-Modules: Text.Pandoc, Text.Pandoc.Blocks, |