aboutsummaryrefslogtreecommitdiff
path: root/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'Text/Pandoc')
-rw-r--r--Text/Pandoc/ASCIIMathML.hs2
-rw-r--r--Text/Pandoc/DefaultHeaders.hs2
-rw-r--r--Text/Pandoc/ODT.hs4
-rw-r--r--Text/Pandoc/Shared.hs20
-rw-r--r--Text/Pandoc/TH.hs51
-rw-r--r--Text/Pandoc/Writers/S5.hs3
6 files changed, 62 insertions, 20 deletions
diff --git a/Text/Pandoc/ASCIIMathML.hs b/Text/Pandoc/ASCIIMathML.hs
index 829779e41..233040dcc 100644
--- a/Text/Pandoc/ASCIIMathML.hs
+++ b/Text/Pandoc/ASCIIMathML.hs
@@ -2,7 +2,7 @@
-- | Definitions for use of ASCIIMathML in HTML.
-- (See <http://www1.chapman.edu/~jipsen/mathml/asciimath.html>.)
module Text.Pandoc.ASCIIMathML ( asciiMathMLScript ) where
-import Text.Pandoc.Shared ( contentsOf )
+import Text.Pandoc.TH ( contentsOf )
import System.FilePath ( (</>) )
-- | String containing ASCIIMathML javascript.
diff --git a/Text/Pandoc/DefaultHeaders.hs b/Text/Pandoc/DefaultHeaders.hs
index 596313b1b..e9c1f17e5 100644
--- a/Text/Pandoc/DefaultHeaders.hs
+++ b/Text/Pandoc/DefaultHeaders.hs
@@ -38,7 +38,7 @@ module Text.Pandoc.DefaultHeaders (
) where
import Text.Pandoc.Writers.S5
import System.FilePath ( (</>) )
-import Text.Pandoc.Shared ( contentsOf )
+import Text.Pandoc.TH ( contentsOf )
defaultLaTeXHeader :: String
#ifndef __HADDOCK__
diff --git a/Text/Pandoc/ODT.hs b/Text/Pandoc/ODT.hs
index 3e5b2a158..423623d5b 100644
--- a/Text/Pandoc/ODT.hs
+++ b/Text/Pandoc/ODT.hs
@@ -29,7 +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 Text.Pandoc.TH ( binaryContentsOf )
import Data.Maybe ( fromJust, isJust )
import Data.List ( partition, intersperse )
import Prelude hiding ( writeFile, readFile )
@@ -61,7 +61,7 @@ saveOpenDocumentAsODT destinationODTPath sourceDirRelative xml = do
"Windows: See http://gnuwin32.sourceforge.net/packages/zip.htm"
withTempDir "pandoc-odt" $ \tempDir -> do
let tempODT = tempDir </> "reference.odt"
- B.writeFile tempODT $ B.pack $(contentsOf $ "odt-styles" </> "reference.odt")
+ B.writeFile tempODT $ B.pack $(binaryContentsOf $ "odt-styles" </> "reference.odt")
createDirectory $ tempDir </> "Pictures"
xml' <- handlePictures tempODT sourceDirRelative xml
writeFile (tempDir </> "content.xml") xml'
diff --git a/Text/Pandoc/Shared.hs b/Text/Pandoc/Shared.hs
index a310daaf0..eb924239d 100644
--- a/Text/Pandoc/Shared.hs
+++ b/Text/Pandoc/Shared.hs
@@ -1,4 +1,3 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
{-
Copyright (C) 2006-8 John MacFarlane <jgm@berkeley.edu>
@@ -101,9 +100,7 @@ module Text.Pandoc.Shared (
WriterOptions (..),
defaultWriterOptions,
-- * File handling
- withTempDir,
- -- * Template haskell
- contentsOf
+ withTempDir
) where
import Text.Pandoc.Definition
@@ -118,9 +115,6 @@ 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
@@ -912,6 +906,10 @@ defaultWriterOptions =
, writerWrapText = True
}
+--
+-- File handling
+--
+
-- | Perform a function in a temporary directory and clean up.
withTempDir :: FilePath -> (FilePath -> IO a) -> IO a
withTempDir baseName func = do
@@ -929,11 +927,3 @@ createTempDir num baseName = do
\e -> if isAlreadyExistsError e
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/Text/Pandoc/TH.hs b/Text/Pandoc/TH.hs
new file mode 100644
index 000000000..5e486b039
--- /dev/null
+++ b/Text/Pandoc/TH.hs
@@ -0,0 +1,51 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-
+Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
+
+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
+-}
+
+{- |
+ Module : Text.Pandoc.TH
+ Copyright : Copyright (C) 2006-8 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <jgm@berkeley.edu>
+ Stability : alpha
+ Portability : portable
+
+Template haskell functions used by Pandoc modules.
+-}
+module Text.Pandoc.TH (
+ contentsOf,
+ binaryContentsOf
+ ) where
+
+import Language.Haskell.TH
+import Language.Haskell.TH.Syntax (Lift (..))
+import qualified Data.ByteString as B
+import Data.ByteString.Internal ( w2c )
+
+-- | Insert contents of text file into a template.
+contentsOf :: FilePath -> ExpQ
+contentsOf p = lift =<< (runIO $ readFile p)
+
+-- | Insert contents of binary file into a template.
+-- Note that @Data.ByteString.readFile@ uses binary mode on windows.
+binaryContentsOf :: FilePath -> ExpQ
+binaryContentsOf p = lift =<< (runIO $ B.readFile p)
+
+instance Lift B.ByteString where
+ lift x = return (LitE (StringL $ map w2c $ B.unpack x))
diff --git a/Text/Pandoc/Writers/S5.hs b/Text/Pandoc/Writers/S5.hs
index a00182ef0..59e1a40ab 100644
--- a/Text/Pandoc/Writers/S5.hs
+++ b/Text/Pandoc/Writers/S5.hs
@@ -40,7 +40,8 @@ module Text.Pandoc.Writers.S5 (
writeS5String,
insertS5Structure
) where
-import Text.Pandoc.Shared ( joinWithSep, WriterOptions, contentsOf )
+import Text.Pandoc.Shared ( joinWithSep, WriterOptions )
+import Text.Pandoc.TH ( contentsOf )
import Text.Pandoc.Writers.HTML ( writeHtml, writeHtmlString )
import Text.Pandoc.Definition
import Text.XHtml.Strict