summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:11:04 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:11:04 +0000
commit9551e363891c2cf31c8a82941c9101571d32987e (patch)
tree86b837fa2ad06eb950b7f445dbc4d0164f549d6c /src/Text/Pandoc
parentecbf3388d4bf00649a47d11360be1065a67ff0b3 (diff)
Removed need for TH in ODT module.
Instead get reference zip file directly from the file at run time. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1690 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/ODT.hs8
-rw-r--r--src/Text/Pandoc/TH.hs14
2 files changed, 6 insertions, 16 deletions
diff --git a/src/Text/Pandoc/ODT.hs b/src/Text/Pandoc/ODT.hs
index f9e4dd8f1..d2e8f45f8 100644
--- a/src/Text/Pandoc/ODT.hs
+++ b/src/Text/Pandoc/ODT.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE TemplateHaskell #-}
{-
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
@@ -29,7 +28,6 @@ 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.TH ( makeZip )
import Data.List ( find )
import System.FilePath ( (</>), takeFileName )
import qualified Data.ByteString.Lazy as B
@@ -39,6 +37,8 @@ import Codec.Archive.Zip
import Control.Applicative ( (<$>) )
import Text.ParserCombinators.Parsec
import System.Time
+import Text.Pandoc.Shared ( inDirectory )
+import Paths_pandoc ( getDataFileName )
-- | Produce an ODT file from OpenDocument XML.
saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.
@@ -46,7 +46,9 @@ saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.
-> String -- ^ OpenDocument XML contents.
-> IO ()
saveOpenDocumentAsODT destinationODTPath sourceDirRelative xml = do
- let refArchive = read $(makeZip $ "data" </> "odt-styles")
+ refArchivePath <- getDataFileName $ "data" </> "odt-styles"
+ refArchive <- inDirectory refArchivePath $
+ addFilesToArchive [OptRecursive] emptyArchive ["."]
-- handle pictures
let (newContents, pics) =
case runParser pPictures [] "OpenDocument XML contents" xml of
diff --git a/src/Text/Pandoc/TH.hs b/src/Text/Pandoc/TH.hs
index 0dc5a6719..dfd6be28b 100644
--- a/src/Text/Pandoc/TH.hs
+++ b/src/Text/Pandoc/TH.hs
@@ -30,8 +30,7 @@ Template haskell functions used by Pandoc modules.
-}
module Text.Pandoc.TH (
contentsOf,
- binaryContentsOf,
- makeZip
+ binaryContentsOf
) where
import Language.Haskell.TH
@@ -40,8 +39,6 @@ import qualified Data.ByteString as B
import Data.ByteString.Internal ( w2c )
import Prelude hiding ( readFile )
import System.IO.UTF8
-import Codec.Archive.Zip
-import Text.Pandoc.Shared ( inDirectory )
-- | Insert contents of text file into a template.
contentsOf :: FilePath -> ExpQ
@@ -54,12 +51,3 @@ binaryContentsOf p = lift =<< (runIO $ B.readFile p)
instance Lift B.ByteString where
lift x = return (LitE (StringL $ map w2c $ B.unpack x))
-
-instance Lift Archive where
- lift x = return (LitE (StringL $ show x ))
-
--- | Construct zip file from files in a directory, and
--- insert into a template.
-makeZip :: FilePath -> ExpQ
-makeZip path = lift =<< (runIO $ inDirectory path $ addFilesToArchive [OptRecursive] emptyArchive ["."])
-