aboutsummaryrefslogtreecommitdiff
path: root/Text
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-08-03 08:43:28 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-08-03 08:43:28 +0000
commited4b00399778204bc589135e005620c40c988258 (patch)
tree0b02b65bed4f08f67281e47ee6254163366e4c41 /Text
parentb63d1c5e3200909eefe5bbd3bf0d6092593a4cb2 (diff)
downloadpandoc-ed4b00399778204bc589135e005620c40c988258.tar.gz
Added 'utf8' configuration flag to pandoc.cabal.
This makes it possible to compile pandoc without utf8, using '-f-utf8' at configuration time. Utf-8 support is still the default. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1373 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'Text')
-rw-r--r--Text/Pandoc/ODT.hs12
1 files changed, 8 insertions, 4 deletions
diff --git a/Text/Pandoc/ODT.hs b/Text/Pandoc/ODT.hs
index 08ecf7d06..b44cb303f 100644
--- a/Text/Pandoc/ODT.hs
+++ b/Text/Pandoc/ODT.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TemplateHaskell, CPP #-}
{-
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
@@ -32,9 +32,6 @@ module Text.Pandoc.ODT ( saveOpenDocumentAsODT ) where
import Text.Pandoc.TH ( binaryContentsOf )
import Data.Maybe ( fromJust )
import Data.List ( partition, intersperse )
-import Prelude hiding ( writeFile, readFile, getContents )
-import System.IO.UTF8
-import System.IO ( stderr )
import System.Directory
import System.FilePath ( (</>), takeDirectory, takeFileName, splitDirectories )
import System.Process ( runProcess, waitForProcess )
@@ -45,6 +42,13 @@ import Text.Pandoc.Shared ( withTempDir )
import Network.URI ( isURI )
import qualified Data.ByteString as B ( writeFile, pack )
import Data.ByteString.Internal ( c2w )
+import Prelude hiding ( writeFile, readFile )
+#ifdef UTF_8
+import System.IO.UTF8
+import System.IO ( stderr )
+#else
+import System.IO
+#endif
-- | Produce an ODT file from OpenDocument XML.
saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.