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
This commit is contained in:
parent
ecbf3388d4
commit
9551e36389
2 changed files with 6 additions and 16 deletions
|
@ -1,4 +1,3 @@
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
|
||||||
{-
|
{-
|
||||||
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
|
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.
|
Functions for producing an ODT file from OpenDocument XML.
|
||||||
-}
|
-}
|
||||||
module Text.Pandoc.ODT ( saveOpenDocumentAsODT ) where
|
module Text.Pandoc.ODT ( saveOpenDocumentAsODT ) where
|
||||||
import Text.Pandoc.TH ( makeZip )
|
|
||||||
import Data.List ( find )
|
import Data.List ( find )
|
||||||
import System.FilePath ( (</>), takeFileName )
|
import System.FilePath ( (</>), takeFileName )
|
||||||
import qualified Data.ByteString.Lazy as B
|
import qualified Data.ByteString.Lazy as B
|
||||||
|
@ -39,6 +37,8 @@ import Codec.Archive.Zip
|
||||||
import Control.Applicative ( (<$>) )
|
import Control.Applicative ( (<$>) )
|
||||||
import Text.ParserCombinators.Parsec
|
import Text.ParserCombinators.Parsec
|
||||||
import System.Time
|
import System.Time
|
||||||
|
import Text.Pandoc.Shared ( inDirectory )
|
||||||
|
import Paths_pandoc ( getDataFileName )
|
||||||
|
|
||||||
-- | Produce an ODT file from OpenDocument XML.
|
-- | Produce an ODT file from OpenDocument XML.
|
||||||
saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.
|
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.
|
-> String -- ^ OpenDocument XML contents.
|
||||||
-> IO ()
|
-> IO ()
|
||||||
saveOpenDocumentAsODT destinationODTPath sourceDirRelative xml = do
|
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
|
-- handle pictures
|
||||||
let (newContents, pics) =
|
let (newContents, pics) =
|
||||||
case runParser pPictures [] "OpenDocument XML contents" xml of
|
case runParser pPictures [] "OpenDocument XML contents" xml of
|
||||||
|
|
|
@ -30,8 +30,7 @@ Template haskell functions used by Pandoc modules.
|
||||||
-}
|
-}
|
||||||
module Text.Pandoc.TH (
|
module Text.Pandoc.TH (
|
||||||
contentsOf,
|
contentsOf,
|
||||||
binaryContentsOf,
|
binaryContentsOf
|
||||||
makeZip
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.TH
|
import Language.Haskell.TH
|
||||||
|
@ -40,8 +39,6 @@ import qualified Data.ByteString as B
|
||||||
import Data.ByteString.Internal ( w2c )
|
import Data.ByteString.Internal ( w2c )
|
||||||
import Prelude hiding ( readFile )
|
import Prelude hiding ( readFile )
|
||||||
import System.IO.UTF8
|
import System.IO.UTF8
|
||||||
import Codec.Archive.Zip
|
|
||||||
import Text.Pandoc.Shared ( inDirectory )
|
|
||||||
|
|
||||||
-- | Insert contents of text file into a template.
|
-- | Insert contents of text file into a template.
|
||||||
contentsOf :: FilePath -> ExpQ
|
contentsOf :: FilePath -> ExpQ
|
||||||
|
@ -54,12 +51,3 @@ binaryContentsOf p = lift =<< (runIO $ B.readFile p)
|
||||||
|
|
||||||
instance Lift B.ByteString where
|
instance Lift B.ByteString where
|
||||||
lift x = return (LitE (StringL $ map w2c $ B.unpack x))
|
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 ["."])
|
|
||||||
|
|
||||||
|
|
Loading…
Add table
Reference in a new issue